strict-base-0.4.0.0: Strict versions of base data types.

Copyright(c) 2017 Daniel Mendler
LicenseBSD-style (see the file LICENSE)
MaintainerDaniel Mendler <mail@daniel-mendler.de>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Strict.List

Contents

Description

Strict List.

Same as the standard Haskell List, but strict.

Synopsis

Documentation

data List a Source #

The strict list type.

Constructors

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

Instances

Functor List Source # 

Methods

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

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

Foldable List Source # 

Methods

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

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

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

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

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

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

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

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

toList :: List a -> [a] #

null :: List a -> Bool #

length :: List a -> Int #

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

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

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

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

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

Traversable List Source # 

Methods

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

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

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

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

Generic1 List Source # 

Associated Types

type Rep1 (List :: * -> *) :: * -> * #

Methods

from1 :: List a -> Rep1 List a #

to1 :: Rep1 List a -> List a #

IsList (List a) Source # 

Associated Types

type Item (List a) :: * #

Methods

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

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

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

Eq a => Eq (List a) Source # 

Methods

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

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

Data a => Data (List a) Source # 

Methods

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

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

toConstr :: List a -> Constr #

dataTypeOf :: List a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (List a) Source # 

Methods

compare :: List a -> List a -> Ordering #

(<) :: List a -> List a -> Bool #

(<=) :: List a -> List a -> Bool #

(>) :: List a -> List a -> Bool #

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

max :: List a -> List a -> List a #

min :: List a -> List a -> List a #

Read a => Read (List a) Source # 
Show a => Show (List a) Source # 

Methods

showsPrec :: Int -> List a -> ShowS #

show :: List a -> String #

showList :: [List a] -> ShowS #

Generic (List a) Source # 

Associated Types

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

Methods

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

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

type Rep1 List Source # 
type Rep (List a) Source # 
type Rep (List a) = D1 (MetaData "List" "Data.Strict.List" "strict-base-0.4.0.0-1k3wDu59CS22iu6yIZo2Dn" 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 (List a))))))
type Item (List a) Source # 
type Item (List a) = a

Orphan instances

IsStrict [a] (List a) Source # 

Methods

fromStrict :: List a -> [a] Source #

toStrict :: [a] -> List a Source #