Safe Haskell | None |
---|---|
Language | GHC2021 |
Extra module of pre-defined SegAct
instances.
Be warned that they're not 100% guaranteed to be correct.
Since: 1.0.0
Synopsis
- class Monoid f => SegAct f a where
- segAct :: f -> a -> a
- segActWithLength :: Int -> f -> a -> a
- newtype Affine1 a = Affine1 (Affine1Repr a)
- type Affine1Repr a = (a, a)
- newtype RangeAdd a = RangeAdd a
- newtype RangeAddId a = RangeAddId a
- newtype RangeSet a = RangeSet (RangeSetRepr a)
- newtype RangeSetId a = RangeSetId (RangeSetIdRepr a)
SegAct (re-export)
class Monoid f => SegAct f a where #
Typeclass reprentation of the LazySegTree
properties. User can implement either segAct
or
segActWithLength
.
Instances should satisfy the follwing:
- Left monoid action
segAct
(f2<>
f1) x =segAct
f2 (segAct
f1 x)- Identity map
segAct
mempty
x = x- Endomorphism
segAct
f (x1<>
x2) = (segAct
f x1)<>
(segAct
f x2)
If you implement segActWithLength
, satisfy one more propety:
- Linear left monoid action
.segActWithLength
len f a =stimes
len (segAct
f a) a
Note that in SegAct
instances, new semigroup values are always given from the left: new
.<>
old
Example instance
Take Affine1
as an example of type \(F\).
{-# LANGUAGE TypeFamilies #-} import AtCoder.LazySegTree qualified as LST import AtCoder.LazySegTree (SegAct (..)) import Data.Monoid import Data.Vector.Generic qualified as VG import Data.Vector.Generic.Mutable qualified as VGM import Data.Vector.Unboxed qualified as VU import Data.Vector.Unboxed.Mutable qualified as VUM -- | f x = a * x + b. It's implemented as a newtype of `(a, a)` for easyUnbox
deriving. newtypeAffine1
a =Affine1
(Affine1
a) deriving newtype (Eq
,Ord
,Show
) -- | This type alias makes theUnbox
deriving easier, described velow. typeAffine1Repr
a = (a, a) instance (Num
a) =>Semigroup
(Affine1
a) where {-# INLINE (<>
) #-} (Affine1
(!a1, !b1))<>
(Affine1
(!a2, !b2)) =Affine1
(a1 * a2, a1 * b2 + b1) instance (Num
a) =>Monoid
(Affine1
a) where {-# INLINEmempty
#-}mempty
=Affine1
(1, 0) instance (Num
a) =>SegAct
(Affine1
a) (Sum
a) where {-# INLINE segActWithLength #-}segActWithLength
len (Affine1
(!a, !b)) !x = a * x + b * fromIntegral len
Deriving Unbox
is very easy for such a newtype (though the efficiency is
not the maximum):
newtype instance VU.MVector s (Affine1
a) = MV_Affine1 (VU.MVector s (Affine1
a)) newtype instance VU.Vector (Affine1
a) = V_Affine1 (VU.Vector (Affine1
a)) deriving instance (VU.Unbox a) => VGM.MVector VUM.MVector (Affine1
a) deriving instance (VU.Unbox a) => VG.Vector VU.Vector (Affine1
a) instance (VU.Unbox a) => VU.Unbox (Affine1
a)
Example contest template
Define your monoid action F
and your acted monoid X
:
{-# LANGUAGE TypeFamilies #-} import AtCoder.LazySegTree qualified as LST import AtCoder.LazySegTree (SegAct (..)) import Data.Vector.Generic qualified as VG import Data.Vector.Generic.Mutable qualified as VGM import Data.Vector.Unboxed qualified as VU import Data.Vector.Unboxed.Mutable qualified as VUM {- ORMOLU_DISABLE -} -- |F
is a custom monoid action, defined as a newtype ofFRepr
. newtype F = F FRepr deriving newtype (Eq, Ord, Show) ; unF :: F -> FRepr ; unF (F x) = x ; newtype instance VU.MVector s F = MV_F (VU.MVector s FRepr) ; newtype instance VU.Vector F = V_F (VU.Vector FRepr) ; deriving instance VGM.MVector VUM.MVector F ; deriving instance VG.Vector VU.Vector F ; instance VU.Unbox F ; {- ORMOLU_ENABLE -} -- | Affine: f x = a * x + b type FRepr = (Int, Int) instance Semigroup F where --new <> old
{-# INLINE (<>) #-} (F (!a1, !b1)) <> (F (!a2, !b2)) = F (a1 * a2, a1 * b2 + b1) instance Monoid F where {-# INLINE mempty #-} mempty = F (1, 0) {- ORMOLU_DISABLE -} -- |X
is a custom acted monoid, defined as a newtype ofXRepr
. newtype X = X XRepr deriving newtype (Eq, Ord, Show) ; unX :: X -> XRepr ; unX (X x) = x; newtype instance VU.MVector s X = MV_X (VU.MVector s XRepr) ; newtype instance VU.Vector X = V_X (VU.Vector XRepr) ; deriving instance VGM.MVector VUM.MVector X ; deriving instance VG.Vector VU.Vector X ; instance VU.Unbox X ; {- ORMOLU_ENABLE -} -- | ActedInt
(same as `Sum Int`). type XRepr = Int deriving instance Num X; -- in our caseX
is aNum
. instance Semigroup X where {-# INLINE (<>) #-} (X x1) <> (X x2) = X $! x1 + x2 instance Monoid X where {-# INLINE mempty #-} mempty = X 0 instance SegAct F X where -- {-# INLINE segAct #-} -- segAct len (F (!a, !b)) (X x) = X $! a * x + b {-# INLINE segActWithLength #-} segActWithLength len (F (!a, !b)) (X x) = X $! a * x + len * b
It's tested as below:
expect :: (Eq a, Show a) => String -> a -> a -> ()
expect msg a b
| a == b = ()
| otherwise = error $ msg ++ ": expected " ++ show a ++ ", found " ++ show b
main :: IO ()
main = do
seg <- LST.build _
F @X $ VU.map X $ VU.fromList [1, 2, 3, 4]
LST.applyIn seg 1 3 $ F (2, 1) -- [1, 5, 7, 4]
LST.write seg 3 $ X 10 -- [1, 5, 7, 10]
LST.modify seg (+ (X 1)) 0 -- [2, 5, 7, 10]
!_ <- (expect "test 1" (X 5)) <$> LST.read seg 1
!_ <- (expect "test 2" (X 14)) <$> LST.prod seg 0 3 -- reads an interval [0, 3)
!_ <- (expect "test 3" (X 24)) <$> LST.allProd seg
!_ <- (expect "test 4" 2) <$> LST.maxRight seg 0 (<= (X 10)) -- sum [0, 2) = 7 <= 10
!_ <- (expect "test 5" 3) <$> LST.minLeft seg 4 (<= (X 10)) -- sum [3, 4) = 10 <= 10
putStrLn "=> test passed!"
Since: 1.0.0
Nothing
Lazy segment tree action \(f(x)\).
Since: 1.0.0
segActWithLength :: Int -> f -> a -> a #
Lazy segment tree action \(f(x)\) with the target monoid's length.
If you implement SegAct
with this function, you don't have to store the monoid's length,
since it's given externally.
Since: 1.0.0
Instances
Affine1
SegAct
instance of one-dimensional affine transformation
\(f: x \rightarrow a \times x + b\).
Composition and dual
Semigroup
for Affine1
is implemented like function composition, and rightmost affine
transformation is applied first: \((f_1 \circ f_2) v := f_1 (f_2(v))\). If you need foldr
of \([f_l, f_{l+1}, .., f_r)\) on a segment tree, be sure to wrap Affine1
in
Dual
.
Example
>>>
import AtCoder.Extra.Monoid (SegAct(..), Affine1(..))
>>>
import AtCoder.LazySegTree qualified as LST
>>>
seg <- LST.build @_ @(Affine1 Int) @(Sum Int) $ VU.generate 3 Sum -- [0, 1, 2]
>>>
LST.applyIn seg 0 3 $ Affine1 (2, 1) -- [1, 3, 5]
>>>
getSum <$> LST.allProd seg
9
Since: 1.0.0
Affine1 (Affine1Repr a) |
Instances
type Affine1Repr a = (a, a) #
Range add
Range set monoid action.
Example
>>>
import AtCoder.Extra.Monoid (SegAct(..), RangeAdd(..))
>>>
import AtCoder.LazySegTree qualified as LST
>>>
import Data.Semigroup (Max(..))
>>>
seg <- LST.build @_ @(RangeAdd Int) @(Sum Int) $ VU.generate 3 Sum -- [0, 1, 2]
>>>
LST.applyIn seg 0 3 $ RangeAdd 5 -- [5, 6, 7]
>>>
getSum <$> LST.prod seg 0 3
18
Since: 1.0.0
RangeAdd a |
Instances
newtype RangeAddId a #
Range set monoid action.
Example
>>>
import AtCoder.Extra.Monoid (SegAct(..), RangeAddId(..))
>>>
import AtCoder.LazySegTree qualified as LST
>>>
import Data.Semigroup (Max(..))
>>>
seg <- LST.build @_ @(RangeAddId Int) @(Max Int) $ VU.generate 3 Max -- [0, 1, 2]
>>>
LST.applyIn seg 0 3 $ RangeAddId 5 -- [5, 6, 7]
>>>
getMax <$> LST.prod seg 0 3
7
Since: 1.0.0
Instances
Range set
SegAct
instance of range set action.
Example
>>>
import AtCoder.Extra.Monoid (SegAct(..), RangeSet(..))
>>>
import AtCoder.LazySegTree qualified as LST
>>>
import Data.Semigroup (Product(..))
>>>
seg <- LST.build @_ @(RangeSet (Product Int)) @(Product Int) $ VU.generate 4 Product -- [0, 1, 2, 3]
>>>
LST.applyIn seg 0 3 $ RangeSet (True, Product 5) -- [5, 5, 5, 3]
>>>
getProduct <$> LST.prod seg 0 4
375
Since: 1.0.0
RangeSet (RangeSetRepr a) |
Instances
newtype RangeSetId a #
SegAct
instance of range set action over ideomponent monoids.
Example
>>>
import AtCoder.Extra.Monoid (SegAct(..), RangeSetId(..))
>>>
import AtCoder.LazySegTree qualified as LST
>>>
import Data.Semigroup (Max(..))
>>>
seg <- LST.build @_ @(RangeSetId (Max Int)) @(Max Int) $ VU.generate 3 (Max . (+ 10)) -- [10, 11, 12]
>>>
LST.applyIn seg 0 2 $ RangeSetId (True, Max 5) -- [5, 5, 12]
>>>
getMax <$> LST.prod seg 0 3
12
Since: 1.0.0
RangeSetId (RangeSetIdRepr a) |