ac-library-hs-1.1.0.0: Data structures and algorithms
Safe HaskellSafe-Inferred
LanguageGHC2021

AtCoder.Extra.Monoid.V2

Description

A monoid acted on by Mat2x2, an affine transformation target.

Since: 1.1.0.0

Synopsis

V2

newtype V2 a Source #

A monoid acted on by Mat2x2, an affine transformation target.

Since: 1.1.0.0

Constructors

V2 (V2Repr a) 

Instances

Instances details
Unbox a => Vector Vector (V2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.V2

Methods

basicUnsafeFreeze :: Mutable Vector s (V2 a) -> ST s (Vector (V2 a))

basicUnsafeThaw :: Vector (V2 a) -> ST s (Mutable Vector s (V2 a))

basicLength :: Vector (V2 a) -> Int

basicUnsafeSlice :: Int -> Int -> Vector (V2 a) -> Vector (V2 a)

basicUnsafeIndexM :: Vector (V2 a) -> Int -> Box (V2 a)

basicUnsafeCopy :: Mutable Vector s (V2 a) -> Vector (V2 a) -> ST s ()

elemseq :: Vector (V2 a) -> V2 a -> b -> b

Unbox a => MVector MVector (V2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.V2

Methods

basicLength :: MVector s (V2 a) -> Int

basicUnsafeSlice :: Int -> Int -> MVector s (V2 a) -> MVector s (V2 a)

basicOverlaps :: MVector s (V2 a) -> MVector s (V2 a) -> Bool

basicUnsafeNew :: Int -> ST s (MVector s (V2 a))

basicInitialize :: MVector s (V2 a) -> ST s ()

basicUnsafeReplicate :: Int -> V2 a -> ST s (MVector s (V2 a))

basicUnsafeRead :: MVector s (V2 a) -> Int -> ST s (V2 a)

basicUnsafeWrite :: MVector s (V2 a) -> Int -> V2 a -> ST s ()

basicClear :: MVector s (V2 a) -> ST s ()

basicSet :: MVector s (V2 a) -> V2 a -> ST s ()

basicUnsafeCopy :: MVector s (V2 a) -> MVector s (V2 a) -> ST s ()

basicUnsafeMove :: MVector s (V2 a) -> MVector s (V2 a) -> ST s ()

basicUnsafeGrow :: MVector s (V2 a) -> Int -> ST s (MVector s (V2 a))

Num a => Monoid (V2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.V2

Methods

mempty :: V2 a #

mappend :: V2 a -> V2 a -> V2 a #

mconcat :: [V2 a] -> V2 a #

Num a => Semigroup (V2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.V2

Methods

(<>) :: V2 a -> V2 a -> V2 a #

sconcat :: NonEmpty (V2 a) -> V2 a #

stimes :: Integral b => b -> V2 a -> V2 a #

Show a => Show (V2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.V2

Methods

showsPrec :: Int -> V2 a -> ShowS #

show :: V2 a -> String #

showList :: [V2 a] -> ShowS #

Eq a => Eq (V2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.V2

Methods

(==) :: V2 a -> V2 a -> Bool #

(/=) :: V2 a -> V2 a -> Bool #

Ord a => Ord (V2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.V2

Methods

compare :: V2 a -> V2 a -> Ordering #

(<) :: V2 a -> V2 a -> Bool #

(<=) :: V2 a -> V2 a -> Bool #

(>) :: V2 a -> V2 a -> Bool #

(>=) :: V2 a -> V2 a -> Bool #

max :: V2 a -> V2 a -> V2 a #

min :: V2 a -> V2 a -> V2 a #

Unbox a => Unbox (V2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.V2

Num a => SegAct (Mat2x2 a) (V2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.Mat2x2

Methods

segAct :: Mat2x2 a -> V2 a -> V2 a Source #

segActWithLength :: Int -> Mat2x2 a -> V2 a -> V2 a Source #

Num a => SegAct (Dual (Mat2x2 a)) (V2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.Mat2x2

Methods

segAct :: Dual (Mat2x2 a) -> V2 a -> V2 a Source #

segActWithLength :: Int -> Dual (Mat2x2 a) -> V2 a -> V2 a Source #

newtype MVector s (V2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.V2

newtype MVector s (V2 a) = MV_V2 (MVector s (V2Repr a))
newtype Vector (V2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.V2

newtype Vector (V2 a) = V_V2 (Vector (V2Repr a))

type V2Repr a = (a, a) Source #

V2 internal representation. Tuples are not the fastest representation, but it's easier to implement Unbox.

Since: 1.1.0.0

Constructor

new :: Num a => a -> V2 a Source #

\(O(1)\) Creates V2 of length \(1\).

Since: 1.1.0.0

unV2 :: V2 a -> a Source #

\(O(1)\) Retrieves the value of V2, discarding the length information.

Since: 1.1.0.0