Safe Haskell | None |
---|---|
Language | GHC2021 |
AtCoder.Extra.Monoid.V2
Contents
Description
A monoid acted on by Mat2x2
or Affine1
, an affine transformation target.
As an Affine1
action target
Compared to Sum
, V2
hold the length in the second value.
Since: 1.1.0.0
V2
A monoid acted on by Mat2x2
, an affine transformation target.
Example
>>>
import AtCoder.Extra.Monoid.Mat2x2 (Mat2x2(..))
>>>
import AtCoder.Extra.Monoid.Mat2x2 qualified as Mat2x2
>>>
import AtCoder.Extra.Monoid.V2 (V2(..))
>>>
import AtCoder.Extra.Monoid.V2 qualified as V2
>>>
import AtCoder.LazySegTree qualified as LST
>>>
import Data.Vector.Unboxed qualified as VU
>>>
seg <- LST.build @_ @(Mat2x2 Int) @(V2 Int) . VU.map V2.new $ VU.fromList [1, 2, 3, 4]
>>>
LST.applyIn seg 1 3 $ Mat2x2.new 2 1 -- [1, 5, 7, 4]
>>>
V2.unV2 <$> LST.prod seg 1 3
12
Since: 1.1.0.0
Instances
Unbox a => Vector Vector (V2 a) Source # | Since: 1.1.0.0 |
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 () | |
Unbox a => MVector MVector (V2 a) Source # | Since: 1.1.0.0 |
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 |
Num a => Semigroup (V2 a) Source # | Since: 1.1.0.0 |
Show a => Show (V2 a) Source # | Since: 1.1.0.0 |
Eq a => Eq (V2 a) Source # | Since: 1.1.0.0 |
Ord a => Ord (V2 a) Source # | Since: 1.1.0.0 |
Unbox a => Unbox (V2 a) Source # | Since: 1.1.0.0 |
Defined in AtCoder.Extra.Monoid.V2 | |
Num a => SegAct (Affine1 a) (V2 a) Source # | Since: 1.2.2.0 |
Num a => SegAct (Mat2x2 a) (V2 a) Source # | Since: 1.1.0.0 |
Num a => SegAct (Dual (Affine1 a)) (V2 a) Source # | Since: 1.2.2.0 |
Num a => SegAct (Dual (Mat2x2 a)) (V2 a) Source # | Since: 1.1.0.0 |
newtype MVector s (V2 a) Source # | Since: 1.1.0.0 |
newtype Vector (V2 a) Source # | Since: 1.1.0.0 |
Constructors
\(O(1)\) Retrieves the value of V2
, discarding the length information.
Since: 1.1.0.0