hegg-0.5.0.0: Fast equality saturation in Haskell
Safe HaskellNone
LanguageHaskell2010

Data.Equality.Utils.SizedList

Description

 
Synopsis

Documentation

data SList a Source #

A list with O(1) size access and O(1) conversion to normal list

Constructors

SList ![a] !Int 

Instances

Instances details
Foldable SList Source # 
Instance details

Defined in Data.Equality.Utils.SizedList

Methods

fold :: Monoid m => SList m -> m #

foldMap :: Monoid m => (a -> m) -> SList a -> m #

foldMap' :: Monoid m => (a -> m) -> SList a -> m #

foldr :: (a -> b -> b) -> b -> SList a -> b #

foldr' :: (a -> b -> b) -> b -> SList a -> b #

foldl :: (b -> a -> b) -> b -> SList a -> b #

foldl' :: (b -> a -> b) -> b -> SList a -> b #

foldr1 :: (a -> a -> a) -> SList a -> a #

foldl1 :: (a -> a -> a) -> SList a -> a #

toList :: SList a -> [a] #

null :: SList a -> Bool #

length :: SList a -> Int #

elem :: Eq a => a -> SList a -> Bool #

maximum :: Ord a => SList a -> a #

minimum :: Ord a => SList a -> a #

sum :: Num a => SList a -> a #

product :: Num a => SList a -> a #

Traversable SList Source # 
Instance details

Defined in Data.Equality.Utils.SizedList

Methods

traverse :: Applicative f => (a -> f b) -> SList a -> f (SList b) #

sequenceA :: Applicative f => SList (f a) -> f (SList a) #

mapM :: Monad m => (a -> m b) -> SList a -> m (SList b) #

sequence :: Monad m => SList (m a) -> m (SList a) #

Functor SList Source # 
Instance details

Defined in Data.Equality.Utils.SizedList

Methods

fmap :: (a -> b) -> SList a -> SList b #

(<$) :: a -> SList b -> SList a #

Monoid (SList a) Source # 
Instance details

Defined in Data.Equality.Utils.SizedList

Methods

mempty :: SList a #

mappend :: SList a -> SList a -> SList a #

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

Semigroup (SList a) Source # 
Instance details

Defined in Data.Equality.Utils.SizedList

Methods

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

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

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

IsList (SList a) Source # 
Instance details

Defined in Data.Equality.Utils.SizedList

Associated Types

type Item (SList a) 
Instance details

Defined in Data.Equality.Utils.SizedList

type Item (SList a) = a

Methods

fromList :: [Item (SList a)] -> SList a #

fromListN :: Int -> [Item (SList a)] -> SList a #

toList :: SList a -> [Item (SList a)] #

type Item (SList a) Source # 
Instance details

Defined in Data.Equality.Utils.SizedList

type Item (SList a) = a

(|:) :: a -> SList a -> SList a Source #

Prepend an item to the list in O(1)

toListSL :: SList a -> [a] Source #

Make a normal list from the sized list in O(1)

sizeSL :: SList a -> Int Source #

Get the size of the list in O(1)