symantic-lib-0.0.4.20180831: Symantics for common types.

Safe HaskellNone
LanguageHaskell2010

Language.Symantic.Lib.Foldable

Contents

Description

Symantic for Foldable.

Synopsis

Class Sym_Foldable

class Sym_Foldable term where Source #

Methods

foldMap :: Foldable f => Monoid m => term (a -> m) -> term (f a) -> term m Source #

foldr :: Foldable f => term (a -> b -> b) -> term b -> term (f a) -> term b Source #

foldr' :: Foldable f => term (a -> b -> b) -> term b -> term (f a) -> term b Source #

foldl :: Foldable f => term (b -> a -> b) -> term b -> term (f a) -> term b Source #

foldl' :: Foldable f => term (b -> a -> b) -> term b -> term (f a) -> term b Source #

length :: Foldable f => term (f a) -> term Int Source #

null :: Foldable f => term (f a) -> term Bool Source #

minimum :: Foldable f => Ord a => term (f a) -> term a Source #

maximum :: Foldable f => Ord a => term (f a) -> term a Source #

elem :: Foldable f => Eq a => term a -> term (f a) -> term Bool infix 4 Source #

sum :: Foldable f => Num a => term (f a) -> term a Source #

product :: Foldable f => Num a => term (f a) -> term a Source #

toList :: Foldable f => term (f a) -> term [a] Source #

all :: Foldable f => term (a -> Bool) -> term (f a) -> term Bool Source #

and :: Foldable f => term (f Bool) -> term Bool Source #

any :: Foldable f => term (a -> Bool) -> term (f a) -> term Bool Source #

concat :: Foldable f => term (f [a]) -> term [a] Source #

concatMap :: Foldable f => term (a -> [b]) -> term (f a) -> term [b] Source #

find :: Foldable f => term (a -> Bool) -> term (f a) -> term (Maybe a) Source #

foldlM :: Foldable f => Monad m => term (b -> a -> m b) -> term b -> term (f a) -> term (m b) Source #

foldrM :: Foldable f => Monad m => term (a -> b -> m b) -> term b -> term (f a) -> term (m b) Source #

forM_ :: Foldable f => Monad m => term (f a) -> term (a -> m b) -> term (m ()) Source #

for_ :: Foldable f => Applicative p => term (f a) -> term (a -> p b) -> term (p ()) Source #

mapM_ :: Foldable f => Monad m => term (a -> m b) -> term (f a) -> term (m ()) Source #

maximumBy :: Foldable f => term (a -> a -> Ordering) -> term (f a) -> term a Source #

minimumBy :: Foldable f => term (a -> a -> Ordering) -> term (f a) -> term a Source #

notElem :: Foldable f => Eq a => term a -> term (f a) -> term Bool Source #

or :: Foldable f => term (f Bool) -> term Bool Source #

sequenceA_ :: Foldable f => Applicative p => term (f (p a)) -> term (p ()) Source #

sequence_ :: Foldable f => Monad m => term (f (m a)) -> term (m ()) Source #

traverse_ :: Foldable f => Applicative p => term (a -> p b) -> term (f a) -> term (p ()) Source #

asum :: Foldable f => Alternative p => term (f (p a)) -> term (p a) Source #

msum :: Foldable f => MonadPlus p => term (f (p a)) -> term (p a) Source #

foldMap :: Sym_Foldable (UnT term) => Trans term => Foldable f => Monoid m => term (a -> m) -> term (f a) -> term m Source #

foldr :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (a -> b -> b) -> term b -> term (f a) -> term b Source #

foldr' :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (a -> b -> b) -> term b -> term (f a) -> term b Source #

foldl :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (b -> a -> b) -> term b -> term (f a) -> term b Source #

foldl' :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (b -> a -> b) -> term b -> term (f a) -> term b Source #

length :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (f a) -> term Int Source #

null :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (f a) -> term Bool Source #

minimum :: Sym_Foldable (UnT term) => Trans term => Foldable f => Ord a => term (f a) -> term a Source #

maximum :: Sym_Foldable (UnT term) => Trans term => Foldable f => Ord a => term (f a) -> term a Source #

elem :: Sym_Foldable (UnT term) => Trans term => Foldable f => Eq a => term a -> term (f a) -> term Bool infix 4 Source #

sum :: Sym_Foldable (UnT term) => Trans term => Foldable f => Num a => term (f a) -> term a Source #

product :: Sym_Foldable (UnT term) => Trans term => Foldable f => Num a => term (f a) -> term a Source #

toList :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (f a) -> term [a] Source #

all :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (a -> Bool) -> term (f a) -> term Bool Source #

and :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (f Bool) -> term Bool Source #

any :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (a -> Bool) -> term (f a) -> term Bool Source #

concat :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (f [a]) -> term [a] Source #

concatMap :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (a -> [b]) -> term (f a) -> term [b] Source #

find :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (a -> Bool) -> term (f a) -> term (Maybe a) Source #

foldlM :: Sym_Foldable (UnT term) => Trans term => Foldable f => Monad m => term (b -> a -> m b) -> term b -> term (f a) -> term (m b) Source #

foldrM :: Sym_Foldable (UnT term) => Trans term => Foldable f => Monad m => term (a -> b -> m b) -> term b -> term (f a) -> term (m b) Source #

forM_ :: Sym_Foldable (UnT term) => Trans term => Foldable f => Monad m => term (f a) -> term (a -> m b) -> term (m ()) Source #

for_ :: Sym_Foldable (UnT term) => Trans term => Foldable f => Applicative p => term (f a) -> term (a -> p b) -> term (p ()) Source #

mapM_ :: Sym_Foldable (UnT term) => Trans term => Foldable f => Monad m => term (a -> m b) -> term (f a) -> term (m ()) Source #

maximumBy :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (a -> a -> Ordering) -> term (f a) -> term a Source #

minimumBy :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (a -> a -> Ordering) -> term (f a) -> term a Source #

notElem :: Sym_Foldable (UnT term) => Trans term => Foldable f => Eq a => term a -> term (f a) -> term Bool Source #

or :: Sym_Foldable (UnT term) => Trans term => Foldable f => term (f Bool) -> term Bool Source #

sequenceA_ :: Sym_Foldable (UnT term) => Trans term => Foldable f => Applicative p => term (f (p a)) -> term (p ()) Source #

sequence_ :: Sym_Foldable (UnT term) => Trans term => Foldable f => Monad m => term (f (m a)) -> term (m ()) Source #

traverse_ :: Sym_Foldable (UnT term) => Trans term => Foldable f => Applicative p => term (a -> p b) -> term (f a) -> term (p ()) Source #

asum :: Sym_Foldable (UnT term) => Trans term => Foldable f => Alternative m => term (f (m a)) -> term (m a) Source #

msum :: Sym_Foldable (UnT term) => Trans term => Foldable f => MonadPlus m => term (f (m a)) -> term (m a) Source #

Instances
Sym_Foldable View Source # 
Instance details

Defined in Language.Symantic.Lib.Foldable

Methods

foldMap :: (Foldable f, Monoid m) => View (a -> m) -> View (f a) -> View m Source #

foldr :: Foldable f => View (a -> b -> b) -> View b -> View (f a) -> View b Source #

foldr' :: Foldable f => View (a -> b -> b) -> View b -> View (f a) -> View b Source #

foldl :: Foldable f => View (b -> a -> b) -> View b -> View (f a) -> View b Source #

foldl' :: Foldable f => View (b -> a -> b) -> View b -> View (f a) -> View b Source #

length :: Foldable f => View (f a) -> View Int Source #

null :: Foldable f => View (f a) -> View Bool Source #

minimum :: (Foldable f, Ord a) => View (f a) -> View a Source #

maximum :: (Foldable f, Ord a) => View (f a) -> View a Source #

elem :: (Foldable f, Eq a) => View a -> View (f a) -> View Bool Source #

sum :: (Foldable f, Num a) => View (f a) -> View a Source #

product :: (Foldable f, Num a) => View (f a) -> View a Source #

toList :: Foldable f => View (f a) -> View [a] Source #

all :: Foldable f => View (a -> Bool) -> View (f a) -> View Bool Source #

and :: Foldable f => View (f Bool) -> View Bool Source #

any :: Foldable f => View (a -> Bool) -> View (f a) -> View Bool Source #

concat :: Foldable f => View (f [a]) -> View [a] Source #

concatMap :: Foldable f => View (a -> [b]) -> View (f a) -> View [b] Source #

find :: Foldable f => View (a -> Bool) -> View (f a) -> View (Maybe a) Source #

foldlM :: (Foldable f, Monad m) => View (b -> a -> m b) -> View b -> View (f a) -> View (m b) Source #

foldrM :: (Foldable f, Monad m) => View (a -> b -> m b) -> View b -> View (f a) -> View (m b) Source #

forM_ :: (Foldable f, Monad m) => View (f a) -> View (a -> m b) -> View (m ()) Source #

for_ :: (Foldable f, Applicative p) => View (f a) -> View (a -> p b) -> View (p ()) Source #

mapM_ :: (Foldable f, Monad m) => View (a -> m b) -> View (f a) -> View (m ()) Source #

maximumBy :: Foldable f => View (a -> a -> Ordering) -> View (f a) -> View a Source #

minimumBy :: Foldable f => View (a -> a -> Ordering) -> View (f a) -> View a Source #

notElem :: (Foldable f, Eq a) => View a -> View (f a) -> View Bool Source #

or :: Foldable f => View (f Bool) -> View Bool Source #

sequenceA_ :: (Foldable f, Applicative p) => View (f (p a)) -> View (p ()) Source #

sequence_ :: (Foldable f, Monad m) => View (f (m a)) -> View (m ()) Source #

traverse_ :: (Foldable f, Applicative p) => View (a -> p b) -> View (f a) -> View (p ()) Source #

asum :: (Foldable f, Alternative p) => View (f (p a)) -> View (p a) Source #

msum :: (Foldable f, MonadPlus p) => View (f (p a)) -> View (p a) Source #

Sym_Foldable Eval Source # 
Instance details

Defined in Language.Symantic.Lib.Foldable

Methods

foldMap :: (Foldable f, Monoid m) => Eval (a -> m) -> Eval (f a) -> Eval m Source #

foldr :: Foldable f => Eval (a -> b -> b) -> Eval b -> Eval (f a) -> Eval b Source #

foldr' :: Foldable f => Eval (a -> b -> b) -> Eval b -> Eval (f a) -> Eval b Source #

foldl :: Foldable f => Eval (b -> a -> b) -> Eval b -> Eval (f a) -> Eval b Source #

foldl' :: Foldable f => Eval (b -> a -> b) -> Eval b -> Eval (f a) -> Eval b Source #

length :: Foldable f => Eval (f a) -> Eval Int Source #

null :: Foldable f => Eval (f a) -> Eval Bool Source #

minimum :: (Foldable f, Ord a) => Eval (f a) -> Eval a Source #

maximum :: (Foldable f, Ord a) => Eval (f a) -> Eval a Source #

elem :: (Foldable f, Eq a) => Eval a -> Eval (f a) -> Eval Bool Source #

sum :: (Foldable f, Num a) => Eval (f a) -> Eval a Source #

product :: (Foldable f, Num a) => Eval (f a) -> Eval a Source #

toList :: Foldable f => Eval (f a) -> Eval [a] Source #

all :: Foldable f => Eval (a -> Bool) -> Eval (f a) -> Eval Bool Source #

and :: Foldable f => Eval (f Bool) -> Eval Bool Source #

any :: Foldable f => Eval (a -> Bool) -> Eval (f a) -> Eval Bool Source #

concat :: Foldable f => Eval (f [a]) -> Eval [a] Source #

concatMap :: Foldable f => Eval (a -> [b]) -> Eval (f a) -> Eval [b] Source #

find :: Foldable f => Eval (a -> Bool) -> Eval (f a) -> Eval (Maybe a) Source #

foldlM :: (Foldable f, Monad m) => Eval (b -> a -> m b) -> Eval b -> Eval (f a) -> Eval (m b) Source #

foldrM :: (Foldable f, Monad m) => Eval (a -> b -> m b) -> Eval b -> Eval (f a) -> Eval (m b) Source #

forM_ :: (Foldable f, Monad m) => Eval (f a) -> Eval (a -> m b) -> Eval (m ()) Source #

for_ :: (Foldable f, Applicative p) => Eval (f a) -> Eval (a -> p b) -> Eval (p ()) Source #

mapM_ :: (Foldable f, Monad m) => Eval (a -> m b) -> Eval (f a) -> Eval (m ()) Source #

maximumBy :: Foldable f => Eval (a -> a -> Ordering) -> Eval (f a) -> Eval a Source #

minimumBy :: Foldable f => Eval (a -> a -> Ordering) -> Eval (f a) -> Eval a Source #

notElem :: (Foldable f, Eq a) => Eval a -> Eval (f a) -> Eval Bool Source #

or :: Foldable f => Eval (f Bool) -> Eval Bool Source #

sequenceA_ :: (Foldable f, Applicative p) => Eval (f (p a)) -> Eval (p ()) Source #

sequence_ :: (Foldable f, Monad m) => Eval (f (m a)) -> Eval (m ()) Source #

traverse_ :: (Foldable f, Applicative p) => Eval (a -> p b) -> Eval (f a) -> Eval (p ()) Source #

asum :: (Foldable f, Alternative p) => Eval (f (p a)) -> Eval (p a) Source #

msum :: (Foldable f, MonadPlus p) => Eval (f (p a)) -> Eval (p a) Source #

(Sym_Foldable term, Sym_Lambda term) => Sym_Foldable (BetaT term) Source # 
Instance details

Defined in Language.Symantic.Lib.Foldable

Methods

foldMap :: (Foldable f, Monoid m) => BetaT term (a -> m) -> BetaT term (f a) -> BetaT term m Source #

foldr :: Foldable f => BetaT term (a -> b -> b) -> BetaT term b -> BetaT term (f a) -> BetaT term b Source #

foldr' :: Foldable f => BetaT term (a -> b -> b) -> BetaT term b -> BetaT term (f a) -> BetaT term b Source #

foldl :: Foldable f => BetaT term (b -> a -> b) -> BetaT term b -> BetaT term (f a) -> BetaT term b Source #

foldl' :: Foldable f => BetaT term (b -> a -> b) -> BetaT term b -> BetaT term (f a) -> BetaT term b Source #

length :: Foldable f => BetaT term (f a) -> BetaT term Int Source #

null :: Foldable f => BetaT term (f a) -> BetaT term Bool Source #

minimum :: (Foldable f, Ord a) => BetaT term (f a) -> BetaT term a Source #

maximum :: (Foldable f, Ord a) => BetaT term (f a) -> BetaT term a Source #

elem :: (Foldable f, Eq a) => BetaT term a -> BetaT term (f a) -> BetaT term Bool Source #

sum :: (Foldable f, Num a) => BetaT term (f a) -> BetaT term a Source #

product :: (Foldable f, Num a) => BetaT term (f a) -> BetaT term a Source #

toList :: Foldable f => BetaT term (f a) -> BetaT term [a] Source #

all :: Foldable f => BetaT term (a -> Bool) -> BetaT term (f a) -> BetaT term Bool Source #

and :: Foldable f => BetaT term (f Bool) -> BetaT term Bool Source #

any :: Foldable f => BetaT term (a -> Bool) -> BetaT term (f a) -> BetaT term Bool Source #

concat :: Foldable f => BetaT term (f [a]) -> BetaT term [a] Source #

concatMap :: Foldable f => BetaT term (a -> [b]) -> BetaT term (f a) -> BetaT term [b] Source #

find :: Foldable f => BetaT term (a -> Bool) -> BetaT term (f a) -> BetaT term (Maybe a) Source #

foldlM :: (Foldable f, Monad m) => BetaT term (b -> a -> m b) -> BetaT term b -> BetaT term (f a) -> BetaT term (m b) Source #

foldrM :: (Foldable f, Monad m) => BetaT term (a -> b -> m b) -> BetaT term b -> BetaT term (f a) -> BetaT term (m b) Source #

forM_ :: (Foldable f, Monad m) => BetaT term (f a) -> BetaT term (a -> m b) -> BetaT term (m ()) Source #

for_ :: (Foldable f, Applicative p) => BetaT term (f a) -> BetaT term (a -> p b) -> BetaT term (p ()) Source #

mapM_ :: (Foldable f, Monad m) => BetaT term (a -> m b) -> BetaT term (f a) -> BetaT term (m ()) Source #

maximumBy :: Foldable f => BetaT term (a -> a -> Ordering) -> BetaT term (f a) -> BetaT term a Source #

minimumBy :: Foldable f => BetaT term (a -> a -> Ordering) -> BetaT term (f a) -> BetaT term a Source #

notElem :: (Foldable f, Eq a) => BetaT term a -> BetaT term (f a) -> BetaT term Bool Source #

or :: Foldable f => BetaT term (f Bool) -> BetaT term Bool Source #

sequenceA_ :: (Foldable f, Applicative p) => BetaT term (f (p a)) -> BetaT term (p ()) Source #

sequence_ :: (Foldable f, Monad m) => BetaT term (f (m a)) -> BetaT term (m ()) Source #

traverse_ :: (Foldable f, Applicative p) => BetaT term (a -> p b) -> BetaT term (f a) -> BetaT term (p ()) Source #

asum :: (Foldable f, Alternative p) => BetaT term (f (p a)) -> BetaT term (p a) Source #

msum :: (Foldable f, MonadPlus p) => BetaT term (f (p a)) -> BetaT term (p a) Source #

(Sym_Foldable r1, Sym_Foldable r2) => Sym_Foldable (Dup r1 r2) Source # 
Instance details

Defined in Language.Symantic.Lib.Foldable

Methods

foldMap :: (Foldable f, Monoid m) => Dup r1 r2 (a -> m) -> Dup r1 r2 (f a) -> Dup r1 r2 m Source #

foldr :: Foldable f => Dup r1 r2 (a -> b -> b) -> Dup r1 r2 b -> Dup r1 r2 (f a) -> Dup r1 r2 b Source #

foldr' :: Foldable f => Dup r1 r2 (a -> b -> b) -> Dup r1 r2 b -> Dup r1 r2 (f a) -> Dup r1 r2 b Source #

foldl :: Foldable f => Dup r1 r2 (b -> a -> b) -> Dup r1 r2 b -> Dup r1 r2 (f a) -> Dup r1 r2 b Source #

foldl' :: Foldable f => Dup r1 r2 (b -> a -> b) -> Dup r1 r2 b -> Dup r1 r2 (f a) -> Dup r1 r2 b Source #

length :: Foldable f => Dup r1 r2 (f a) -> Dup r1 r2 Int Source #

null :: Foldable f => Dup r1 r2 (f a) -> Dup r1 r2 Bool Source #

minimum :: (Foldable f, Ord a) => Dup r1 r2 (f a) -> Dup r1 r2 a Source #

maximum :: (Foldable f, Ord a) => Dup r1 r2 (f a) -> Dup r1 r2 a Source #

elem :: (Foldable f, Eq a) => Dup r1 r2 a -> Dup r1 r2 (f a) -> Dup r1 r2 Bool Source #

sum :: (Foldable f, Num a) => Dup r1 r2 (f a) -> Dup r1 r2 a Source #

product :: (Foldable f, Num a) => Dup r1 r2 (f a) -> Dup r1 r2 a Source #

toList :: Foldable f => Dup r1 r2 (f a) -> Dup r1 r2 [a] Source #

all :: Foldable f => Dup r1 r2 (a -> Bool) -> Dup r1 r2 (f a) -> Dup r1 r2 Bool Source #

and :: Foldable f => Dup r1 r2 (f Bool) -> Dup r1 r2 Bool Source #

any :: Foldable f => Dup r1 r2 (a -> Bool) -> Dup r1 r2 (f a) -> Dup r1 r2 Bool Source #

concat :: Foldable f => Dup r1 r2 (f [a]) -> Dup r1 r2 [a] Source #

concatMap :: Foldable f => Dup r1 r2 (a -> [b]) -> Dup r1 r2 (f a) -> Dup r1 r2 [b] Source #

find :: Foldable f => Dup r1 r2 (a -> Bool) -> Dup r1 r2 (f a) -> Dup r1 r2 (Maybe a) Source #

foldlM :: (Foldable f, Monad m) => Dup r1 r2 (b -> a -> m b) -> Dup r1 r2 b -> Dup r1 r2 (f a) -> Dup r1 r2 (m b) Source #

foldrM :: (Foldable f, Monad m) => Dup r1 r2 (a -> b -> m b) -> Dup r1 r2 b -> Dup r1 r2 (f a) -> Dup r1 r2 (m b) Source #

forM_ :: (Foldable f, Monad m) => Dup r1 r2 (f a) -> Dup r1 r2 (a -> m b) -> Dup r1 r2 (m ()) Source #

for_ :: (Foldable f, Applicative p) => Dup r1 r2 (f a) -> Dup r1 r2 (a -> p b) -> Dup r1 r2 (p ()) Source #

mapM_ :: (Foldable f, Monad m) => Dup r1 r2 (a -> m b) -> Dup r1 r2 (f a) -> Dup r1 r2 (m ()) Source #

maximumBy :: Foldable f => Dup r1 r2 (a -> a -> Ordering) -> Dup r1 r2 (f a) -> Dup r1 r2 a Source #

minimumBy :: Foldable f => Dup r1 r2 (a -> a -> Ordering) -> Dup r1 r2 (f a) -> Dup r1 r2 a Source #

notElem :: (Foldable f, Eq a) => Dup r1 r2 a -> Dup r1 r2 (f a) -> Dup r1 r2 Bool Source #

or :: Foldable f => Dup r1 r2 (f Bool) -> Dup r1 r2 Bool Source #

sequenceA_ :: (Foldable f, Applicative p) => Dup r1 r2 (f (p a)) -> Dup r1 r2 (p ()) Source #

sequence_ :: (Foldable f, Monad m) => Dup r1 r2 (f (m a)) -> Dup r1 r2 (m ()) Source #

traverse_ :: (Foldable f, Applicative p) => Dup r1 r2 (a -> p b) -> Dup r1 r2 (f a) -> Dup r1 r2 (p ()) Source #

asum :: (Foldable f, Alternative p) => Dup r1 r2 (f (p a)) -> Dup r1 r2 (p a) Source #

msum :: (Foldable f, MonadPlus p) => Dup r1 r2 (f (p a)) -> Dup r1 r2 (p a) Source #

Types

tyFoldable :: Source src => Type src vs a -> Type src vs (Foldable a) Source #

t0 :: Source src => LenInj vs => KindInj (K t) => Type src (Proxy t ': vs) t Source #

t1 :: Source src => LenInj vs => KindInj (K t) => Type src (a ': (Proxy t ': vs)) t Source #

t2 :: Source src => LenInj vs => KindInj (K t) => Type src (a ': (b ': (Proxy t ': vs))) t Source #

Terms

teFoldable_foldMap :: TermDef Foldable '[Proxy a, Proxy t, Proxy m] ((Foldable t # Monoid m) #> ((a -> m) -> t a -> m)) Source #

teFoldable_elem :: TermDef Foldable '[Proxy a, Proxy t] ((Foldable t # Eq a) #> (a -> t a -> Bool)) Source #

teFoldable_foldr :: TermDef Foldable '[Proxy a, Proxy b, Proxy t] (Foldable t #> ((a -> b -> b) -> b -> t a -> b)) Source #

teFoldable_foldr' :: TermDef Foldable '[Proxy a, Proxy b, Proxy t] (Foldable t #> ((a -> b -> b) -> b -> t a -> b)) Source #

teFoldable_foldl :: TermDef Foldable '[Proxy a, Proxy b, Proxy t] (Foldable t #> ((b -> a -> b) -> b -> t a -> b)) Source #

teFoldable_sum :: TermDef Foldable '[Proxy a, Proxy t] ((Foldable t # Num a) #> (t a -> a)) Source #

teFoldable_all :: TermDef Foldable '[Proxy a, Proxy t] (Foldable t #> ((a -> Bool) -> t a -> Bool)) Source #

teFoldable_any :: TermDef Foldable '[Proxy a, Proxy t] (Foldable t #> ((a -> Bool) -> t a -> Bool)) Source #

teFoldable_asum :: TermDef Foldable '[Proxy a, Proxy t, Proxy f] ((Foldable t # Alternative f) #> (t (f a) -> f a)) Source #

Orphan instances

ClassInstancesFor Foldable Source # 
Instance details

Methods

proveConstraintFor :: Source src => proxy Foldable -> Type src vs q -> Maybe (Qual q) #

TypeInstancesFor Foldable Source # 
Instance details

Methods

expandFamFor :: Source src => proxy Foldable -> Len vs -> Const src fam -> Types src vs ts -> Maybe (Type src vs (Fam fam ts)) #

NameTyOf Foldable Source # 
Instance details

Methods

nameTyOf :: proxy Foldable -> Mod NameTy #

isNameTyOp :: proxy Foldable -> Bool #

FixityOf Foldable Source # 
Instance details

Methods

fixityOf :: proxy Foldable -> Maybe Fixity #

(Source src, SymInj ss Foldable) => ModuleFor src ss Foldable Source # 
Instance details

Methods

moduleFor :: (PathMod, Module src ss) #

Gram_Term_AtomsFor src ss g Foldable Source # 
Instance details

Methods

g_term_atomsFor :: [CF g (AST_Term src ss)] #