Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Monoid action \(f: x \rightarrow ax + b\). Less efficient than Affine1
, but compatible with
inverse opereations.
Since: 1.1.0.0
Synopsis
- newtype Mat2x2 a = Mat2x2 (Mat2x2Repr a)
- type Mat2x2Repr a = (a, a, a, a)
- new :: Num a => a -> a -> Mat2x2 a
- unMat2x2 :: Mat2x2 a -> Mat2x2Repr a
- ident :: Num a => Mat2x2 a
- zero :: Num a => Mat2x2 a
- act :: Num a => Mat2x2 a -> V2 a -> V2 a
- map :: (a -> b) -> Mat2x2 a -> Mat2x2 b
- det :: Fractional e => Mat2x2 e -> e
- inv :: (HasCallStack, Fractional e, Eq e) => Mat2x2 e -> Mat2x2 e
Mat2x2
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
>>>
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
Mat2x2 (Mat2x2Repr a) |
Instances
type Mat2x2Repr a = (a, a, a, a) Source #
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
Actions
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