ghc-8.0.0.20160204: The GHC API

Safe HaskellNone
LanguageHaskell2010

Bag

Documentation

data Bag a Source

Instances

Foldable Bag 

Methods

fold :: Monoid m => Bag m -> m Source

foldMap :: Monoid m => (a -> m) -> Bag a -> m Source

foldr :: (a -> b -> b) -> b -> Bag a -> b Source

foldr' :: (a -> b -> b) -> b -> Bag a -> b Source

foldl :: (b -> a -> b) -> b -> Bag a -> b Source

foldl' :: (b -> a -> b) -> b -> Bag a -> b Source

foldr1 :: (a -> a -> a) -> Bag a -> a Source

foldl1 :: (a -> a -> a) -> Bag a -> a Source

toList :: Bag a -> [a] Source

null :: Bag a -> Bool Source

length :: Bag a -> Int Source

elem :: Eq a => a -> Bag a -> Bool Source

maximum :: Ord a => Bag a -> a Source

minimum :: Ord a => Bag a -> a Source

sum :: Num a => Bag a -> a Source

product :: Num a => Bag a -> a Source

Data a => Data (Bag a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bag a -> c (Bag a) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Bag a) Source

toConstr :: Bag a -> Constr Source

dataTypeOf :: Bag a -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (Bag a)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Bag a)) Source

gmapT :: (forall b. Data b => b -> b) -> Bag a -> Bag a Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bag a -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bag a -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Bag a -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bag a -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bag a -> m (Bag a) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bag a -> m (Bag a) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bag a -> m (Bag a) Source

Outputable a => Outputable (Bag a) 

Methods

ppr :: Bag a -> SDoc Source

pprPrec :: Rational -> Bag a -> SDoc Source

unitBag :: a -> Bag a Source

unionBags :: Bag a -> Bag a -> Bag a Source

mapBag :: (a -> b) -> Bag a -> Bag b Source

elemBag :: Eq a => a -> Bag a -> Bool Source

filterBag :: (a -> Bool) -> Bag a -> Bag a Source

partitionBag :: (a -> Bool) -> Bag a -> (Bag a, Bag a) Source

partitionBagWith :: (a -> Either b c) -> Bag a -> (Bag b, Bag c) Source

concatBag :: Bag (Bag a) -> Bag a Source

foldBag :: (r -> r -> r) -> (a -> r) -> r -> Bag a -> r Source

foldrBag :: (a -> r -> r) -> r -> Bag a -> r Source

foldlBag :: (r -> a -> r) -> r -> Bag a -> r Source

consBag :: a -> Bag a -> Bag a infixr 3 Source

snocBag :: Bag a -> a -> Bag a infixl 3 Source

anyBag :: (a -> Bool) -> Bag a -> Bool Source

listToBag :: [a] -> Bag a Source

bagToList :: Bag a -> [a] Source

mapAccumBagL Source

Arguments

:: (acc -> x -> (acc, y))

combining funcction

-> acc

initial state

-> Bag x

inputs

-> (acc, Bag y)

final state, outputs

foldrBagM :: Monad m => (a -> b -> m b) -> b -> Bag a -> m b Source

foldlBagM :: Monad m => (b -> a -> m b) -> b -> Bag a -> m b Source

mapBagM :: Monad m => (a -> m b) -> Bag a -> m (Bag b) Source

mapBagM_ :: Monad m => (a -> m b) -> Bag a -> m () Source

flatMapBagM :: Monad m => (a -> m (Bag b)) -> Bag a -> m (Bag b) Source

flatMapBagPairM :: Monad m => (a -> m (Bag b, Bag c)) -> Bag a -> m (Bag b, Bag c) Source

mapAndUnzipBagM :: Monad m => (a -> m (b, c)) -> Bag a -> m (Bag b, Bag c) Source

mapAccumBagLM Source

Arguments

:: Monad m 
=> (acc -> x -> m (acc, y))

combining funcction

-> acc

initial state

-> Bag x

inputs

-> m (acc, Bag y)

final state, outputs

anyBagM :: Monad m => (a -> m Bool) -> Bag a -> m Bool Source

filterBagM :: Monad m => (a -> m Bool) -> Bag a -> m (Bag a) Source