iota-0.1.0.0
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Trie.Binary.Magma

Synopsis

Examples

ABC308G Minimum Xor Pair Query

Expand
data A = Done !Word | Partial !Word

-- non-associative
instance Magma A where
    magma = m
      where
        m (Done x) (Done y) = Done (min x y)
        m (Done x) Partial{} = Done x
        m Partial{} (Done y) = Done y
        m (Partial x) (Partial y) = Done (xor x y)
    {-# INLINE magma #-}

type B = Int

tip :: Word -> B -> A
tip w b
    | b >= 2 = Done 0
    | otherwise = Partial w
{-# INLINE tip #-}

ins :: Maybe B -> Maybe B
ins = Just . maybe 1 (+ 1)
{-# INLINE ins #-}

del :: Maybe B -> Maybe B
del ma = case ma of
    Just a | a > 1 -> Just (a - 1)
    _ -> Nothing
{-# INLINE del #-}

insert :: (KnownNat h) => Word -> Trie h A B -> Trie h A B
insert = alterWith tip ins
{-# INLINE insert #-}

delete :: (KnownNat h) => Word -> Trie h A B -> Trie h A B
delete = alterWith tip del
{-# INLINE delete #-}

magmaAll :: Trie h A B -> Maybe A
magmaAll = magmaAllWith tip
{-# INLINE magmaAll #-}

Binary Trie

data Trie (h :: Nat) a b Source #

Constructors

Bin !a !(Trie h a b) !(Trie h a b) 
Tip !Word !b 
Nil 

Instances

Instances details
(Show a, Show b) => Show (Trie h a b) Source # 
Instance details

Defined in Data.Trie.Binary.Magma

Methods

showsPrec :: Int -> Trie h a b -> ShowS #

show :: Trie h a b -> String #

showList :: [Trie h a b] -> ShowS #

magmaAllWith Source #

Arguments

:: (Word -> b -> a)

Tip to Magma

-> Trie h a b 
-> Maybe a 

binWith Source #

Arguments

:: Magma a 
=> (Word -> b -> a)

Tip to Magma

-> Trie h a b

left child

-> Trie h a b

right child

-> Trie h a b 

alterWith Source #

Arguments

:: forall h a b. (Magma a, KnownNat h) 
=> (Word -> b -> a)

Tip to Magma

-> (Maybe b -> Maybe b)

insert/delete

-> Word 
-> Trie h a b 
-> Trie h a b 

Magma

class Magma a where Source #

Methods

magma :: a -> a -> a Source #

Instances

Instances details
Semigroup m => Magma (WrappedSemigroup m) Source # 
Instance details

Defined in Data.Trie.Binary.Magma

newtype WrappedSemigroup m Source #

Constructors

WrapSemigroup m 

Instances

Instances details
Semigroup m => Magma (WrappedSemigroup m) Source # 
Instance details

Defined in Data.Trie.Binary.Magma