strict-data-0.2.0.2: A collection of commonly used strict data structures

Safe HaskellNone
LanguageHaskell2010

Data.StrictList

Synopsis

Documentation

data StrictList a Source #

Constructors

Nil 
!a :! !(StrictList a) infixr 5 

Instances

Monad StrictList Source # 

Methods

(>>=) :: StrictList a -> (a -> StrictList b) -> StrictList b #

(>>) :: StrictList a -> StrictList b -> StrictList b #

return :: a -> StrictList a #

fail :: String -> StrictList a #

Functor StrictList Source # 

Methods

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

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

MonadFail StrictList Source # 

Methods

fail :: String -> StrictList a #

Applicative StrictList Source # 

Methods

pure :: a -> StrictList a #

(<*>) :: StrictList (a -> b) -> StrictList a -> StrictList b #

(*>) :: StrictList a -> StrictList b -> StrictList b #

(<*) :: StrictList a -> StrictList b -> StrictList a #

Foldable StrictList Source # 

Methods

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

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

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

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

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

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

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

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

toList :: StrictList a -> [a] #

null :: StrictList a -> Bool #

length :: StrictList a -> Int #

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

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

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

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

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

Traversable StrictList Source # 

Methods

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

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

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

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

Alternative StrictList Source # 
IsList (StrictList a) Source # 

Associated Types

type Item (StrictList a) :: * #

Eq a => Eq (StrictList a) Source # 

Methods

(==) :: StrictList a -> StrictList a -> Bool #

(/=) :: StrictList a -> StrictList a -> Bool #

Data a => Data (StrictList a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StrictList a -> c (StrictList a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StrictList a) #

toConstr :: StrictList a -> Constr #

dataTypeOf :: StrictList a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (StrictList a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StrictList a)) #

gmapT :: (forall b. Data b => b -> b) -> StrictList a -> StrictList a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StrictList a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StrictList a -> r #

gmapQ :: (forall d. Data d => d -> u) -> StrictList a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StrictList a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StrictList a -> m (StrictList a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StrictList a -> m (StrictList a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StrictList a -> m (StrictList a) #

Ord a => Ord (StrictList a) Source # 
Read a => Read (StrictList a) Source # 
Show a => Show (StrictList a) Source # 
Generic (StrictList a) Source # 

Associated Types

type Rep (StrictList a) :: * -> * #

Methods

from :: StrictList a -> Rep (StrictList a) x #

to :: Rep (StrictList a) x -> StrictList a #

Monoid (StrictList a) Source # 
Arbitrary a => Arbitrary (StrictList a) Source # 
Hashable a => Hashable (StrictList a) Source # 

Methods

hashWithSalt :: Int -> StrictList a -> Int #

hash :: StrictList a -> Int #

ToJSON a => ToJSON (StrictList a) Source # 
FromJSON a => FromJSON (StrictList a) Source # 
NFData a => NFData (StrictList a) Source # 

Methods

rnf :: StrictList a -> () #

type Rep (StrictList a) Source # 
type Rep (StrictList a) = D1 (MetaData "StrictList" "Data.StrictList.Types" "strict-data-0.2.0.2-FGPF9cVJpblGQAsBKh3DLB" False) ((:+:) (C1 (MetaCons "Nil" PrefixI False) U1) (C1 (MetaCons ":!" (InfixI RightAssociative 5) False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (StrictList a))))))
type Item (StrictList a) Source # 
type Item (StrictList a) = a

(+!+) :: StrictList a -> StrictList a -> StrictList a infixr 5 Source #

(\!\) :: Eq a => SL a -> SL a -> SL a Source #

all :: (a -> Bool) -> StrictList a -> Bool Source #

any :: (a -> Bool) -> StrictList a -> Bool Source #

break :: (a -> Bool) -> StrictList a -> (StrictList a, StrictList a) Source #

catOptions :: StrictList (Option a) -> StrictList a Source #

Equivalent to catMaybes with Option and StrictList.

>>> catOptions (sl [Some 1, None, Some 2, None, None, Some 3, Some 4])
[1,2,3,4]

catOptionsL :: [Option a] -> StrictList a Source #

>>> catOptionsL [Some 1, None, Some 2, None, None, Some 3, Some 4]
[1,2,3,4]

concatSL :: SL (SL a) -> SL a Source #

concatMap :: Foldable t => (a -> StrictList b) -> t a -> StrictList b Source #

concatMapSL :: (a -> StrictList b) -> SL a -> StrictList b Source #

concatMapM :: Monad m => (a -> m (SL b)) -> SL a -> m (SL b) Source #

delete :: Eq a => a -> SL a -> SL a Source #

delete x removes the first occurrence of x from its list argument. NOTE: Implementation copied from Data.List.

deleteBy :: (a -> a -> Bool) -> a -> SL a -> SL a Source #

The deleteBy function behaves like delete, but takes a user-supplied equality predicate. NOTE: Implementation copied from Data.List.

deleteIdx :: Int -> StrictList a -> StrictList a Source #

deleteIdx idx removes the element at index idx.

not (null xs) ==> Some (deleteIdx 0 xs) == tailOpt xs

drop :: Int -> StrictList a -> StrictList a Source #

>>> drop 3 (sl [1, 2, 3, 4, 5])
[4,5]

dropWhileEnd :: (a -> Bool) -> SL a -> SL a Source #

elem :: Eq a => a -> StrictList a -> Bool Source #

filter :: (a -> Bool) -> StrictList a -> StrictList a Source #

Equivalent of filter with StrictList.

find :: (a -> Bool) -> StrictList a -> Maybe a Source #

groupBy :: (a -> a -> Bool) -> StrictList a -> StrictList (StrictList a) Source #

headM :: Monad m => StrictList a -> m a Source #

headOpt :: StrictList a -> Option a Source #

not (null xs) ==> isSome (headOpt xs)

insert :: Ord a => a -> SL a -> SL a Source #

insertBy :: (a -> a -> Ordering) -> a -> SL a -> SL a Source #

lastM :: Monad m => StrictList a -> m a Source #

ll :: SL a -> [a] Source #

lookup :: Eq a => a -> StrictList (a :!: b) -> Option b Source #

lookupM :: (Monad m, Show a, Eq a) => a -> StrictList (a :!: b) -> m b Source #

lookupM' :: (Monad m, Eq a) => (a -> String) -> a -> StrictList (a :!: b) -> m b Source #

lookupM'' :: (Monad m, Eq k) => (k -> String) -> (a -> Maybe k) -> k -> StrictList a -> m a Source #

lookupM'' showKey getKey getValue key list searches for key in list using getKey as the key extraction function and showKey to print all available keys when no match is found.

map :: (a -> b) -> StrictList a -> StrictList b Source #

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

mapM_ :: Monad m => (a -> m b) -> StrictList a -> m () Source #

mapMaybe :: (a -> Maybe b) -> StrictList a -> StrictList b Source #

Equivalent of mapMaybe with StrictList.

mapOption :: (a -> Option b) -> StrictList a -> StrictList b Source #

Equivalent of mapMaybe with Option and StrictList.

>>> mapOption (\x -> if even x then Some (x * 2) else None) (sl [1, 2, 3, 4, 5])
[4,8]

maximumM :: (Ord a, Monad m) => SL a -> m a Source #

maybeToStrictList :: Maybe a -> StrictList a Source #

>>> maybeToStrictList (Just "bar")
["bar"]
>>> maybeToStrictList Nothing
[]

mconcatSL :: Monoid a => SL a -> a Source #

notElem :: Eq a => a -> StrictList a -> Bool Source #

nub :: (Eq a, Hashable a) => SL a -> SL a Source #

null :: StrictList a -> Bool Source #

>>> null (sl [])
True
>>> null (sl ["foo"])
False

optionToStrictList :: Option a -> StrictList a Source #

>>> optionToStrictList (Some "foo")
["foo"]
>>> optionToStrictList None
[]

partition :: (a -> Bool) -> SL a -> (SL a, SL a) Source #

replicate :: Integral i => i -> a -> StrictList a Source #

reverse :: StrictList a -> StrictList a Source #

reverse (reverse xs) == xs

sl :: [a] -> SL a Source #

snoc :: SL a -> a -> SL a Source #

Appends an element to the end of this list. This is really inefficient because the whole list needs to be copied. Use at your own risk.

mergeBy :: (a -> a -> Ordering) -> StrictList a -> StrictList a -> StrictList a Source #

sortBy :: (a -> a -> Ordering) -> StrictList a -> StrictList a Source #

sortOn :: Ord b => (a -> b) -> StrictList a -> StrictList a Source #

>>> sortOn snd (sl [("foo", 10), ("bar", 1), ("baz", 100)])
[("bar",1),("foo",10),("baz",100)]

span :: (a -> Bool) -> StrictList a -> (StrictList a, StrictList a) Source #

stripPrefix :: Eq a => SL a -> SL a -> Maybe (SL a) Source #

stripSuffix :: Eq a => SL a -> SL a -> Maybe (SL a) Source #

tailOpt :: StrictList a -> Option (StrictList a) Source #

Safe tail function: Returns None for an empty list, Some x for a non-empty list starting with x.

take :: Int -> StrictList a -> StrictList a Source #

>>> take 3 (sl [1, 2, 3, 4, 5, 6, 7])
[1,2,3]

transpose :: SL (SL a) -> SL (SL a) Source #

unzip :: SL (a :!: b) -> SL a :!: SL b Source #

unzipL :: [a :!: b] -> SL a :!: SL b Source #

unzipLL :: [(a, b)] -> SL a :!: SL b Source #

zipLL :: [a] -> [b] -> StrictList (a :!: b) Source #

zipLS :: [a] -> StrictList b -> StrictList (a :!: b) Source #

zipSL :: StrictList a -> [b] -> StrictList (a :!: b) Source #

zipWith :: (a -> b -> c) -> SL a -> SL b -> SL c Source #

zipWithLS :: (a -> b -> c) -> [a] -> SL b -> SL c Source #

zipWithSL :: (a -> b -> c) -> SL a -> [b] -> SL c Source #