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

AtCoder.Extra.Monoid.Mat2x2

Description

Monoid action \(f: x \rightarrow ax + b\). Less efficient than Affine1, but compatible with inverse opereations.

Since: 1.1.0.0

Synopsis

Mat2x2

newtype Mat2x2 a Source #

Monoid action \(f: x \rightarrow ax + b\). Less efficient than Affine1, but compatible with inverse opereations.

Composition and dual

The affine transformation acts as a left monoid action: \(f_2 (f_1 v) = (f_2 \circ f_1) v\). To apply the leftmost transformation first in a segment tree, wrap Mat2x2 in Data.Monoid.Dual.

Example

Expand
>>> import AtCoder.Extra.Monoid.Mat2x2 qualified as Mat2x2
>>> import AtCoder.Extra.Monoid.V2 qualified as V2
>>> import AtCoder.Extra.Monoid (SegAct(..), Mat2x2(..), V2(..))
>>> import AtCoder.LazySegTree qualified as LST
>>> seg <- LST.build @_ @(Mat2x2 Int) @(V2 Int) $ VU.generate 3 V2.new -- [0, 1, 2]
>>> LST.applyIn seg 0 3 $ Mat2x2.new 2 1 -- [1, 3, 5]
>>> V2.unV2 <$> LST.allProd seg
9

Since: 1.1.0.0

Constructors

Mat2x2 (Mat2x2Repr a) 

Instances

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

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.Mat2x2

Methods

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

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

basicLength :: Vector (Mat2x2 a) -> Int

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

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

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

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

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

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.Mat2x2

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

Num a => Monoid (Mat2x2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.Mat2x2

Methods

mempty :: Mat2x2 a #

mappend :: Mat2x2 a -> Mat2x2 a -> Mat2x2 a #

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

Num a => Semigroup (Mat2x2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.Mat2x2

Methods

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

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

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

Show a => Show (Mat2x2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.Mat2x2

Methods

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

show :: Mat2x2 a -> String #

showList :: [Mat2x2 a] -> ShowS #

Eq a => Eq (Mat2x2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.Mat2x2

Methods

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

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

Ord a => Ord (Mat2x2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.Mat2x2

Methods

compare :: Mat2x2 a -> Mat2x2 a -> Ordering #

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

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

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

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

max :: Mat2x2 a -> Mat2x2 a -> Mat2x2 a #

min :: Mat2x2 a -> Mat2x2 a -> Mat2x2 a #

Unbox a => Unbox (Mat2x2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.Mat2x2

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 (Mat2x2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.Mat2x2

newtype MVector s (Mat2x2 a) = MV_Mat2x2 (MVector s (Mat2x2Repr a))
newtype Vector (Mat2x2 a) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.Mat2x2

newtype Vector (Mat2x2 a) = V_Mat2x2 (Vector (Mat2x2Repr a))

type Mat2x2Repr a = (a, a, a, a) Source #

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

Since: 1.1.0.0

Constructors

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

\(O(1)\) Creates a one-dimensional affine transformation: \(f: x \rightarrow a \times x + b\).

Since: 1.1.0.0

unMat2x2 :: Mat2x2 a -> Mat2x2Repr a Source #

\(O(1)\) Retrieves the four components of Mat2x2.

Since: 1.1.0.0

ident :: Num a => Mat2x2 a Source #

\(O(1)\) Identity transformation.

Since: 1.1.0.0

zero :: Num a => Mat2x2 a Source #

\(O(1)\) Transformation to zero.

Since: 1.1.0.0

Actions

act :: Num a => Mat2x2 a -> V2 a -> V2 a Source #

\(O(1)\) Multiplies Mat2x2 to V2.

Since: 1.1.0.0

Operators

map :: (a -> b) -> Mat2x2 a -> Mat2x2 b Source #

\(O(1)\) Maps the every component of Mat2x2.

Since: 1.1.0.0

det :: Fractional e => Mat2x2 e -> e Source #

\(O(1)\) Returns the determinan of the matrix.

Since: 1.1.0.0

inv :: (HasCallStack, Fractional e, Eq e) => Mat2x2 e -> Mat2x2 e Source #

\(O(1)\) Returns the inverse matrix, based on Fractional instance (mainly for ModInt).

Constraints

  • The determinant (det) of the matrix must be non-zero, otherwise an error is thrown.

Since: 1.1.0.0