yaya-0.6.2.0: Total recursion schemes.
Safe HaskellSafe
LanguageHaskell2010

Yaya.Pattern

Description

Common pattern functors (and instances for them).

This re-exports the functors from the strict library because it also adds some orphan instances for them.

Synopsis

Documentation

data Either a b #

The strict choice type.

Constructors

Left !a 
Right !b 

Instances

Instances details
Assoc Either 
Instance details

Defined in Data.Strict.Either

Methods

assoc :: Either (Either a b) c -> Either a (Either b c) #

unassoc :: Either a (Either b c) -> Either (Either a b) c #

Swap Either 
Instance details

Defined in Data.Strict.Either

Methods

swap :: Either a b -> Either b a #

Bifoldable Either 
Instance details

Defined in Data.Strict.Either

Methods

bifold :: Monoid m => Either m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Either a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Either a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Either a b -> c #

Bifunctor Either 
Instance details

Defined in Data.Strict.Either

Methods

bimap :: (a -> b) -> (c -> d) -> Either a c -> Either b d #

first :: (a -> b) -> Either a c -> Either b c #

second :: (b -> c) -> Either a b -> Either a c #

Bitraversable Either 
Instance details

Defined in Data.Strict.Either

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Either a b -> f (Either c d) #

Eq2 Either 
Instance details

Defined in Data.Strict.Either

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Either a c -> Either b d -> Bool #

Ord2 Either 
Instance details

Defined in Data.Strict.Either

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Either a c -> Either b d -> Ordering #

Read2 Either 
Instance details

Defined in Data.Strict.Either

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Either a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Either a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Either a b] #

Show2 Either 
Instance details

Defined in Data.Strict.Either

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Either a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Either a b] -> ShowS #

NFData2 Either 
Instance details

Defined in Data.Strict.Either

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> Either a b -> () #

Hashable2 Either 
Instance details

Defined in Data.Strict.Either

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> Either a b -> Int #

Corecursive (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

ana :: forall (a0 :: k). Coalgebra (->) (Const (Either a b)) a0 -> a0 -> Either a b Source #

Projectable (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (Const (Either a b)) (Either a b) Source #

Recursive (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: forall (a0 :: k1). Algebra (->) (Const (Either a b)) a0 -> Either a b -> a0 Source #

Generic1 (Either a :: Type -> Type) 
Instance details

Defined in Data.Strict.Either

Associated Types

type Rep1 (Either a) :: k -> Type #

Methods

from1 :: forall (a0 :: k). Either a a0 -> Rep1 (Either a) a0 #

to1 :: forall (a0 :: k). Rep1 (Either a) a0 -> Either a a0 #

Steppable (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (Const (Either a b)) (Either a b) Source #

Foldable (Either e) 
Instance details

Defined in Data.Strict.Either

Methods

fold :: Monoid m => Either e m -> m #

foldMap :: Monoid m => (a -> m) -> Either e a -> m #

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

foldr :: (a -> b -> b) -> b -> Either e a -> b #

foldr' :: (a -> b -> b) -> b -> Either e a -> b #

foldl :: (b -> a -> b) -> b -> Either e a -> b #

foldl' :: (b -> a -> b) -> b -> Either e a -> b #

foldr1 :: (a -> a -> a) -> Either e a -> a #

foldl1 :: (a -> a -> a) -> Either e a -> a #

toList :: Either e a -> [a] #

null :: Either e a -> Bool #

length :: Either e a -> Int #

elem :: Eq a => a -> Either e a -> Bool #

maximum :: Ord a => Either e a -> a #

minimum :: Ord a => Either e a -> a #

sum :: Num a => Either e a -> a #

product :: Num a => Either e a -> a #

Eq a => Eq1 (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

liftEq :: (a0 -> b -> Bool) -> Either a a0 -> Either a b -> Bool #

Ord a => Ord1 (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

liftCompare :: (a0 -> b -> Ordering) -> Either a a0 -> Either a b -> Ordering #

Read a => Read1 (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Either a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Either a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Either a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Either a a0] #

Show a => Show1 (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Either a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Either a a0] -> ShowS #

Traversable (Either e) 
Instance details

Defined in Data.Strict.Either

Methods

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

sequenceA :: Applicative f => Either e (f a) -> f (Either e a) #

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

sequence :: Monad m => Either e (m a) -> m (Either e a) #

Applicative (Either a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

pure :: a0 -> Either a a0 #

(<*>) :: Either a (a0 -> b) -> Either a a0 -> Either a b #

liftA2 :: (a0 -> b -> c) -> Either a a0 -> Either a b -> Either a c #

(*>) :: Either a a0 -> Either a b -> Either a b #

(<*) :: Either a a0 -> Either a b -> Either a a0 #

Functor (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

fmap :: (a0 -> b) -> Either a a0 -> Either a b #

(<$) :: a0 -> Either a b -> Either a a0 #

Monad (Either a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

(>>=) :: Either a a0 -> (a0 -> Either a b) -> Either a b #

(>>) :: Either a a0 -> Either a b -> Either a b #

return :: a0 -> Either a a0 #

NFData a => NFData1 (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

liftRnf :: (a0 -> ()) -> Either a a0 -> () #

Hashable a => Hashable1 (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

liftHashWithSalt :: (Int -> a0 -> Int) -> Int -> Either a a0 -> Int #

(Data a, Data b) => Data (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

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

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

toConstr :: Either a b -> Constr #

dataTypeOf :: Either a b -> DataType #

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

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

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

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

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

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

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

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

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

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

Semigroup (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

(<>) :: Either a b -> Either a b -> Either a b #

sconcat :: NonEmpty (Either a b) -> Either a b #

stimes :: Integral b0 => b0 -> Either a b -> Either a b #

Generic (Either a b) 
Instance details

Defined in Data.Strict.Either

Associated Types

type Rep (Either a b) :: Type -> Type #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

(Read a, Read b) => Read (Either a b) 
Instance details

Defined in Data.Strict.Either

(Show a, Show b) => Show (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

showsPrec :: Int -> Either a b -> ShowS #

show :: Either a b -> String #

showList :: [Either a b] -> ShowS #

(Binary a, Binary b) => Binary (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

put :: Either a b -> Put #

get :: Get (Either a b) #

putList :: [Either a b] -> Put #

(NFData a, NFData b) => NFData (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

rnf :: Either a b -> () #

(Eq a, Eq b) => Eq (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

(==) :: Either a b -> Either a b -> Bool #

(/=) :: Either a b -> Either a b -> Bool #

(Ord a, Ord b) => Ord (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

compare :: Either a b -> Either a b -> Ordering #

(<) :: Either a b -> Either a b -> Bool #

(<=) :: Either a b -> Either a b -> Bool #

(>) :: Either a b -> Either a b -> Bool #

(>=) :: Either a b -> Either a b -> Bool #

max :: Either a b -> Either a b -> Either a b #

min :: Either a b -> Either a b -> Either a b #

(Hashable a, Hashable b) => Hashable (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

hashWithSalt :: Int -> Either a b -> Int #

hash :: Either a b -> Int #

Strict (Either a b) (Either a b) 
Instance details

Defined in Data.Strict.Classes

Methods

toStrict :: Either0 a b -> Either a b #

toLazy :: Either a b -> Either0 a b #

type Rep1 (Either a :: Type -> Type) 
Instance details

Defined in Data.Strict.Either

type Rep1 (Either a :: Type -> Type) = D1 ('MetaData "Either" "Data.Strict.Either" "strict-0.5-BWxnEivHTJ1GZRp1YcohzE" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1))
type Rep (Either a b) 
Instance details

Defined in Data.Strict.Either

type Rep (Either a b) = D1 ('MetaData "Either" "Data.Strict.Either" "strict-0.5-BWxnEivHTJ1GZRp1YcohzE" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)))

either :: (a -> c) -> (b -> c) -> Either a b -> c #

Case analysis: if the value is Left a, apply the first function to a; if it is Right b, apply the second function to b.

lefts :: [Either a b] -> [a] #

Analogous to lefts in Data.Either.

rights :: [Either a b] -> [b] #

Analogous to rights in Data.Either.

partitionEithers :: [Either a b] -> ([a], [b]) #

Analogous to partitionEithers in Data.Either.

isLeft :: Either a b -> Bool #

Yields True iff the argument is of the form Left _.

isRight :: Either a b -> Bool #

Yields True iff the argument is of the form Right _.

fromLeft :: Either a b -> a #

Extracts the element out of a Left and throws an error if the argument is a Right.

fromRight :: Either a b -> b #

Extracts the element out of a Right and throws an error if the argument is a Left.

data Maybe a #

The type of strict optional values.

Constructors

Nothing 
Just !a 

Instances

Instances details
Foldable Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

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

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

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

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

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

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

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

toList :: Maybe a -> [a] #

null :: Maybe a -> Bool #

length :: Maybe a -> Int #

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

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

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

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

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

Eq1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

liftEq :: (a -> b -> Bool) -> Maybe a -> Maybe b -> Bool #

Ord1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

liftCompare :: (a -> b -> Ordering) -> Maybe a -> Maybe b -> Ordering #

Read1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Maybe a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Maybe a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Maybe a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Maybe a] #

Show1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Maybe a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Maybe a] -> ShowS #

Traversable Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

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

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

Applicative Maybe Source # 
Instance details

Defined in Yaya.Pattern

Methods

pure :: a -> Maybe a #

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

liftA2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c #

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

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

Functor Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

Monad Maybe Source # 
Instance details

Defined in Yaya.Pattern

Methods

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

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

return :: a -> Maybe a #

NFData1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

liftRnf :: (a -> ()) -> Maybe a -> () #

Hashable1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Maybe a -> Int #

Generic1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Associated Types

type Rep1 Maybe :: k -> Type #

Methods

from1 :: forall (a :: k). Maybe a -> Rep1 Maybe a #

to1 :: forall (a :: k). Rep1 Maybe a -> Maybe a #

Projectable (->) Natural Maybe Source # 
Instance details

Defined in Yaya.Fold

Recursive (->) Natural Maybe Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

cata :: forall (a :: k1). Algebra (->) Maybe a -> Natural -> a Source #

Corecursive (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

ana :: forall (a0 :: k). Coalgebra (->) (Const (Maybe a)) a0 -> a0 -> Maybe a Source #

Projectable (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (Const (Maybe a)) (Maybe a) Source #

Recursive (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: forall (a0 :: k1). Algebra (->) (Const (Maybe a)) a0 -> Maybe a -> a0 Source #

Steppable (->) Natural Maybe Source # 
Instance details

Defined in Yaya.Fold

Steppable (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (Const (Maybe a)) (Maybe a) Source #

Data a => Data (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

toConstr :: Maybe a -> Constr #

dataTypeOf :: Maybe a -> DataType #

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

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

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

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

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

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

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

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

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

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

Semigroup a => Monoid (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

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

Semigroup a => Semigroup (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

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

Generic (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Associated Types

type Rep (Maybe a) :: Type -> Type #

Methods

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

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

Read a => Read (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Show a => Show (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

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

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Binary a => Binary (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

put :: Maybe a -> Put #

get :: Get (Maybe a) #

putList :: [Maybe a] -> Put #

NFData a => NFData (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

rnf :: Maybe a -> () #

Eq a => Eq (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

Ord a => Ord (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

compare :: Maybe a -> Maybe a -> Ordering #

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

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

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

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

max :: Maybe a -> Maybe a -> Maybe a #

min :: Maybe a -> Maybe a -> Maybe a #

Hashable a => Hashable (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

hashWithSalt :: Int -> Maybe a -> Int #

hash :: Maybe a -> Int #

Strict (Maybe a) (Maybe a) 
Instance details

Defined in Data.Strict.Classes

Methods

toStrict :: Maybe0 a -> Maybe a #

toLazy :: Maybe a -> Maybe0 a #

type Rep1 Maybe 
Instance details

Defined in Data.Strict.Maybe

type Rep1 Maybe = D1 ('MetaData "Maybe" "Data.Strict.Maybe" "strict-0.5-BWxnEivHTJ1GZRp1YcohzE" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1))
type Rep (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

type Rep (Maybe a) = D1 ('MetaData "Maybe" "Data.Strict.Maybe" "strict-0.5-BWxnEivHTJ1GZRp1YcohzE" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))

maybe :: b -> (a -> b) -> Maybe a -> b #

Given a default value, a function and a Maybe value, yields the default value if the Maybe value is Nothing and applies the function to the value stored in the Just otherwise.

isJust :: Maybe a -> Bool #

Yields True iff the argument is of the form Just _.

isNothing :: Maybe a -> Bool #

Yields True iff the argument is Nothing.

fromJust :: Maybe a -> a #

Extracts the element out of a Just and throws an error if the argument is Nothing.

fromMaybe :: a -> Maybe a -> a #

Given a default value and a Maybe, yield the default value if the Maybe argument is Nothing and extract the value out of the Just otherwise.

maybeToList :: Maybe a -> [a] #

Analogous to maybeToList in Data.Maybe.

listToMaybe :: [a] -> Maybe a #

Analogous to listToMaybe in Data.Maybe.

catMaybes :: [Maybe a] -> [a] #

Analogous to catMaybes in Data.Maybe.

mapMaybe :: (a -> Maybe b) -> [a] -> [b] #

Analogous to mapMaybe in Data.Maybe.

data Pair a b #

The type of strict pairs.

Constructors

!a :!: !b infix 2 

Instances

Instances details
Assoc Pair 
Instance details

Defined in Data.Strict.Tuple

Methods

assoc :: Pair (Pair a b) c -> Pair a (Pair b c) #

unassoc :: Pair a (Pair b c) -> Pair (Pair a b) c #

Swap Pair 
Instance details

Defined in Data.Strict.Tuple

Methods

swap :: Pair a b -> Pair b a #

Bifoldable Pair 
Instance details

Defined in Data.Strict.Tuple

Methods

bifold :: Monoid m => Pair m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Pair a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Pair a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Pair a b -> c #

Bifunctor Pair 
Instance details

Defined in Data.Strict.Tuple

Methods

bimap :: (a -> b) -> (c -> d) -> Pair a c -> Pair b d #

first :: (a -> b) -> Pair a c -> Pair b c #

second :: (b -> c) -> Pair a b -> Pair a c #

Bitraversable Pair 
Instance details

Defined in Data.Strict.Tuple

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Pair a b -> f (Pair c d) #

Eq2 Pair 
Instance details

Defined in Data.Strict.Tuple

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Pair a c -> Pair b d -> Bool #

Ord2 Pair 
Instance details

Defined in Data.Strict.Tuple

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Pair a c -> Pair b d -> Ordering #

Read2 Pair
>>> readsPrec2 0 "'a' :!: ('b' :!: 'c')" :: [(Pair Char (Pair Char Char), String)]
[('a' :!: ('b' :!: 'c'),"")]
>>> readsPrec2 0 "('a' :!: 'b') :!: 'c'" :: [(Pair (Pair Char Char) Char, String)]
[(('a' :!: 'b') :!: 'c',"")]
Instance details

Defined in Data.Strict.Tuple

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Pair a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Pair a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Pair a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Pair a b] #

Show2 Pair 
Instance details

Defined in Data.Strict.Tuple

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Pair a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Pair a b] -> ShowS #

NFData2 Pair 
Instance details

Defined in Data.Strict.Tuple

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> Pair a b -> () #

Hashable2 Pair 
Instance details

Defined in Data.Strict.Tuple

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> Pair a b -> Int #

Generic1 (Pair a :: Type -> Type) 
Instance details

Defined in Data.Strict.Tuple

Associated Types

type Rep1 (Pair a) :: k -> Type #

Methods

from1 :: forall (a0 :: k). Pair a a0 -> Rep1 (Pair a) a0 #

to1 :: forall (a0 :: k). Rep1 (Pair a) a0 -> Pair a a0 #

Foldable (Pair e) 
Instance details

Defined in Data.Strict.Tuple

Methods

fold :: Monoid m => Pair e m -> m #

foldMap :: Monoid m => (a -> m) -> Pair e a -> m #

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

foldr :: (a -> b -> b) -> b -> Pair e a -> b #

foldr' :: (a -> b -> b) -> b -> Pair e a -> b #

foldl :: (b -> a -> b) -> b -> Pair e a -> b #

foldl' :: (b -> a -> b) -> b -> Pair e a -> b #

foldr1 :: (a -> a -> a) -> Pair e a -> a #

foldl1 :: (a -> a -> a) -> Pair e a -> a #

toList :: Pair e a -> [a] #

null :: Pair e a -> Bool #

length :: Pair e a -> Int #

elem :: Eq a => a -> Pair e a -> Bool #

maximum :: Ord a => Pair e a -> a #

minimum :: Ord a => Pair e a -> a #

sum :: Num a => Pair e a -> a #

product :: Num a => Pair e a -> a #

Eq a => Eq1 (Pair a) 
Instance details

Defined in Data.Strict.Tuple

Methods

liftEq :: (a0 -> b -> Bool) -> Pair a a0 -> Pair a b -> Bool #

Ord a => Ord1 (Pair a) 
Instance details

Defined in Data.Strict.Tuple

Methods

liftCompare :: (a0 -> b -> Ordering) -> Pair a a0 -> Pair a b -> Ordering #

Read a => Read1 (Pair a) 
Instance details

Defined in Data.Strict.Tuple

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Pair a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Pair a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Pair a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Pair a a0] #

Show a => Show1 (Pair a) 
Instance details

Defined in Data.Strict.Tuple

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Pair a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Pair a a0] -> ShowS #

Traversable (Pair e) 
Instance details

Defined in Data.Strict.Tuple

Methods

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

sequenceA :: Applicative f => Pair e (f a) -> f (Pair e a) #

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

sequence :: Monad m => Pair e (m a) -> m (Pair e a) #

Functor (Pair e) 
Instance details

Defined in Data.Strict.Tuple

Methods

fmap :: (a -> b) -> Pair e a -> Pair e b #

(<$) :: a -> Pair e b -> Pair e a #

Comonad (Pair a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

extract :: Pair a a0 -> a0 #

duplicate :: Pair a a0 -> Pair a (Pair a a0) #

extend :: (Pair a a0 -> b) -> Pair a a0 -> Pair a b #

NFData a => NFData1 (Pair a) 
Instance details

Defined in Data.Strict.Tuple

Methods

liftRnf :: (a0 -> ()) -> Pair a a0 -> () #

Hashable a => Hashable1 (Pair a) 
Instance details

Defined in Data.Strict.Tuple

Methods

liftHashWithSalt :: (Int -> a0 -> Int) -> Int -> Pair a a0 -> Int #

(Data a, Data b) => Data (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

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

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

toConstr :: Pair a b -> Constr #

dataTypeOf :: Pair a b -> DataType #

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

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

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

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

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

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

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

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

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

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

(Monoid a, Monoid b) => Monoid (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

mempty :: Pair a b #

mappend :: Pair a b -> Pair a b -> Pair a b #

mconcat :: [Pair a b] -> Pair a b #

(Semigroup a, Semigroup b) => Semigroup (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

(<>) :: Pair a b -> Pair a b -> Pair a b #

sconcat :: NonEmpty (Pair a b) -> Pair a b #

stimes :: Integral b0 => b0 -> Pair a b -> Pair a b #

(Bounded a, Bounded b) => Bounded (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

minBound :: Pair a b #

maxBound :: Pair a b #

Generic (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Associated Types

type Rep (Pair a b) :: Type -> Type #

Methods

from :: Pair a b -> Rep (Pair a b) x #

to :: Rep (Pair a b) x -> Pair a b #

(Ix a, Ix b) => Ix (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

range :: (Pair a b, Pair a b) -> [Pair a b] #

index :: (Pair a b, Pair a b) -> Pair a b -> Int #

unsafeIndex :: (Pair a b, Pair a b) -> Pair a b -> Int #

inRange :: (Pair a b, Pair a b) -> Pair a b -> Bool #

rangeSize :: (Pair a b, Pair a b) -> Int #

unsafeRangeSize :: (Pair a b, Pair a b) -> Int #

(Read a, Read b) => Read (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

readsPrec :: Int -> ReadS (Pair a b) #

readList :: ReadS [Pair a b] #

readPrec :: ReadPrec (Pair a b) #

readListPrec :: ReadPrec [Pair a b] #

(Show a, Show b) => Show (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

showsPrec :: Int -> Pair a b -> ShowS #

show :: Pair a b -> String #

showList :: [Pair a b] -> ShowS #

(Binary a, Binary b) => Binary (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

put :: Pair a b -> Put #

get :: Get (Pair a b) #

putList :: [Pair a b] -> Put #

(NFData a, NFData b) => NFData (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

rnf :: Pair a b -> () #

(Eq a, Eq b) => Eq (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

(==) :: Pair a b -> Pair a b -> Bool #

(/=) :: Pair a b -> Pair a b -> Bool #

(Ord a, Ord b) => Ord (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

compare :: Pair a b -> Pair a b -> Ordering #

(<) :: Pair a b -> Pair a b -> Bool #

(<=) :: Pair a b -> Pair a b -> Bool #

(>) :: Pair a b -> Pair a b -> Bool #

(>=) :: Pair a b -> Pair a b -> Bool #

max :: Pair a b -> Pair a b -> Pair a b #

min :: Pair a b -> Pair a b -> Pair a b #

(Hashable a, Hashable b) => Hashable (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

hashWithSalt :: Int -> Pair a b -> Int #

hash :: Pair a b -> Int #

Strict (a, b) (Pair a b) 
Instance details

Defined in Data.Strict.Classes

Methods

toStrict :: (a, b) -> Pair a b #

toLazy :: Pair a b -> (a, b) #

Field1 (Pair a b) (Pair a' b) a a'

Since: lens-4.20

Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (Pair a b) (Pair a' b) a a' #

Field2 (Pair a b) (Pair a b') b b'

Since: lens-4.20

Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (Pair a b) (Pair a b') b b' #

type Rep1 (Pair a :: Type -> Type) 
Instance details

Defined in Data.Strict.Tuple

type Rep1 (Pair a :: Type -> Type) = D1 ('MetaData "Pair" "Data.Strict.Tuple" "strict-0.5-BWxnEivHTJ1GZRp1YcohzE" 'False) (C1 ('MetaCons ":!:" ('InfixI 'NotAssociative 2) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1))
type Rep (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

type Rep (Pair a b) = D1 ('MetaData "Pair" "Data.Strict.Tuple" "strict-0.5-BWxnEivHTJ1GZRp1YcohzE" 'False) (C1 ('MetaCons ":!:" ('InfixI 'NotAssociative 2) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)))

type (:!:) = Pair infix 2 #

fst :: Pair a b -> a #

Extract the first component of a strict pair.

snd :: Pair a b -> b #

Extract the second component of a strict pair.

swap :: Pair a b -> Pair b a #

Analogous to swap from Data.Tuple

uncurry :: (a -> b -> c) -> Pair a b -> c #

Convert a curried function to a function on strict pairs.

zip :: [a] -> [b] -> [Pair a b] #

Zip for strict pairs (defined with zipWith).

unzip :: [Pair a b] -> ([a], [b]) #

Unzip for stict pairs into a (lazy) pair of lists.

curry :: (Pair a b -> c) -> a -> b -> c #

Curry a function on strict pairs.

data AndMaybe a b Source #

Isomorphic to (a, Maybe b), it’s also the pattern functor for non-empty lists.

Constructors

Only ~a 
Indeed ~a b 

Instances

Instances details
Bifunctor AndMaybe Source # 
Instance details

Defined in Yaya.Pattern

Methods

bimap :: (a -> b) -> (c -> d) -> AndMaybe a c -> AndMaybe b d #

first :: (a -> b) -> AndMaybe a c -> AndMaybe b c #

second :: (b -> c) -> AndMaybe a b -> AndMaybe a c #

Eq2 AndMaybe Source # 
Instance details

Defined in Yaya.Pattern

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> AndMaybe a c -> AndMaybe b d -> Bool #

Ord2 AndMaybe Source # 
Instance details

Defined in Yaya.Pattern

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> AndMaybe a c -> AndMaybe b d -> Ordering #

Read2 AndMaybe Source #

Since: 0.6.1.0

Instance details

Defined in Yaya.Pattern

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (AndMaybe a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [AndMaybe a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (AndMaybe a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [AndMaybe a b] #

Show2 AndMaybe Source # 
Instance details

Defined in Yaya.Pattern

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> AndMaybe a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [AndMaybe a b] -> ShowS #

Corecursive (->) (NonEmpty a :: Type) (AndMaybe a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: forall (a0 :: k). Coalgebra (->) (AndMaybe a) a0 -> a0 -> NonEmpty a Source #

Projectable (->) (NonEmpty a :: Type) (AndMaybe a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (AndMaybe a) (NonEmpty a) Source #

Generic1 (AndMaybe a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Pattern

Associated Types

type Rep1 (AndMaybe a) :: k -> Type #

Methods

from1 :: forall (a0 :: k). AndMaybe a a0 -> Rep1 (AndMaybe a) a0 #

to1 :: forall (a0 :: k). Rep1 (AndMaybe a) a0 -> AndMaybe a a0 #

Steppable (->) (NonEmpty a :: Type) (AndMaybe a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (AndMaybe a) (NonEmpty a) Source #

Foldable (AndMaybe a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

fold :: Monoid m => AndMaybe a m -> m #

foldMap :: Monoid m => (a0 -> m) -> AndMaybe a a0 -> m #

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

foldr :: (a0 -> b -> b) -> b -> AndMaybe a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> AndMaybe a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> AndMaybe a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> AndMaybe a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> AndMaybe a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> AndMaybe a a0 -> a0 #

toList :: AndMaybe a a0 -> [a0] #

null :: AndMaybe a a0 -> Bool #

length :: AndMaybe a a0 -> Int #

elem :: Eq a0 => a0 -> AndMaybe a a0 -> Bool #

maximum :: Ord a0 => AndMaybe a a0 -> a0 #

minimum :: Ord a0 => AndMaybe a a0 -> a0 #

sum :: Num a0 => AndMaybe a a0 -> a0 #

product :: Num a0 => AndMaybe a a0 -> a0 #

Eq a => Eq1 (AndMaybe a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

liftEq :: (a0 -> b -> Bool) -> AndMaybe a a0 -> AndMaybe a b -> Bool #

Ord a => Ord1 (AndMaybe a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

liftCompare :: (a0 -> b -> Ordering) -> AndMaybe a a0 -> AndMaybe a b -> Ordering #

Read a => Read1 (AndMaybe a) Source #

Since: 0.6.1.0

Instance details

Defined in Yaya.Pattern

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (AndMaybe a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [AndMaybe a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (AndMaybe a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [AndMaybe a a0] #

Show a => Show1 (AndMaybe a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> AndMaybe a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [AndMaybe a a0] -> ShowS #

Traversable (AndMaybe a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

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

sequenceA :: Applicative f => AndMaybe a (f a0) -> f (AndMaybe a a0) #

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

sequence :: Monad m => AndMaybe a (m a0) -> m (AndMaybe a a0) #

Functor (AndMaybe a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

fmap :: (a0 -> b) -> AndMaybe a a0 -> AndMaybe a b #

(<$) :: a0 -> AndMaybe a b -> AndMaybe a a0 #

Generic (AndMaybe a b) Source # 
Instance details

Defined in Yaya.Pattern

Associated Types

type Rep (AndMaybe a b) :: Type -> Type #

Methods

from :: AndMaybe a b -> Rep (AndMaybe a b) x #

to :: Rep (AndMaybe a b) x -> AndMaybe a b #

(Read a, Read b) => Read (AndMaybe a b) Source #

Since: 0.6.1.0

Instance details

Defined in Yaya.Pattern

(Show a, Show b) => Show (AndMaybe a b) Source # 
Instance details

Defined in Yaya.Pattern

Methods

showsPrec :: Int -> AndMaybe a b -> ShowS #

show :: AndMaybe a b -> String #

showList :: [AndMaybe a b] -> ShowS #

(Eq a, Eq b) => Eq (AndMaybe a b) Source # 
Instance details

Defined in Yaya.Pattern

Methods

(==) :: AndMaybe a b -> AndMaybe a b -> Bool #

(/=) :: AndMaybe a b -> AndMaybe a b -> Bool #

(Ord a, Ord b) => Ord (AndMaybe a b) Source #

This definition is different from the one that is derivable. For example, the derived instance would always have compare (Only x) (Indeed x' y) == LT, but this instance will return GT if compare x x' == GT.

Instance details

Defined in Yaya.Pattern

Methods

compare :: AndMaybe a b -> AndMaybe a b -> Ordering #

(<) :: AndMaybe a b -> AndMaybe a b -> Bool #

(<=) :: AndMaybe a b -> AndMaybe a b -> Bool #

(>) :: AndMaybe a b -> AndMaybe a b -> Bool #

(>=) :: AndMaybe a b -> AndMaybe a b -> Bool #

max :: AndMaybe a b -> AndMaybe a b -> AndMaybe a b #

min :: AndMaybe a b -> AndMaybe a b -> AndMaybe a b #

type Rep1 (AndMaybe a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Pattern

type Rep (AndMaybe a b) Source # 
Instance details

Defined in Yaya.Pattern

type Rep (AndMaybe a b) = D1 ('MetaData "AndMaybe" "Yaya.Pattern" "yaya-0.6.2.0-EgozjXGIZKx9HLMrnz1gAG" 'False) (C1 ('MetaCons "Only" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceLazy 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Indeed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceLazy 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 b)))

data XNor a b Source #

Isomorphic to Maybe (a, b), it’s also the pattern functor for lists.

Constructors

Neither 
Both ~a b 

Instances

Instances details
Bifunctor XNor Source # 
Instance details

Defined in Yaya.Pattern

Methods

bimap :: (a -> b) -> (c -> d) -> XNor a c -> XNor b d #

first :: (a -> b) -> XNor a c -> XNor b c #

second :: (b -> c) -> XNor a b -> XNor a c #

Eq2 XNor Source # 
Instance details

Defined in Yaya.Pattern

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> XNor a c -> XNor b d -> Bool #

Ord2 XNor Source # 
Instance details

Defined in Yaya.Pattern

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> XNor a c -> XNor b d -> Ordering #

Read2 XNor Source #

Since: 0.6.1.0

Instance details

Defined in Yaya.Pattern

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (XNor a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [XNor a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (XNor a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [XNor a b] #

Show2 XNor Source # 
Instance details

Defined in Yaya.Pattern

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> XNor a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [XNor a b] -> ShowS #

Corecursive (->) ([a] :: Type) (XNor a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: forall (a0 :: k). Coalgebra (->) (XNor a) a0 -> a0 -> [a] Source #

Projectable (->) ([a] :: Type) (XNor a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (XNor a) [a] Source #

Generic1 (XNor a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Pattern

Associated Types

type Rep1 (XNor a) :: k -> Type #

Methods

from1 :: forall (a0 :: k). XNor a a0 -> Rep1 (XNor a) a0 #

to1 :: forall (a0 :: k). Rep1 (XNor a) a0 -> XNor a a0 #

Steppable (->) ([a] :: Type) (XNor a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (XNor a) [a] Source #

Foldable (XNor a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

fold :: Monoid m => XNor a m -> m #

foldMap :: Monoid m => (a0 -> m) -> XNor a a0 -> m #

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

foldr :: (a0 -> b -> b) -> b -> XNor a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> XNor a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> XNor a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> XNor a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> XNor a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> XNor a a0 -> a0 #

toList :: XNor a a0 -> [a0] #

null :: XNor a a0 -> Bool #

length :: XNor a a0 -> Int #

elem :: Eq a0 => a0 -> XNor a a0 -> Bool #

maximum :: Ord a0 => XNor a a0 -> a0 #

minimum :: Ord a0 => XNor a a0 -> a0 #

sum :: Num a0 => XNor a a0 -> a0 #

product :: Num a0 => XNor a a0 -> a0 #

Eq a => Eq1 (XNor a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

liftEq :: (a0 -> b -> Bool) -> XNor a a0 -> XNor a b -> Bool #

Ord a => Ord1 (XNor a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

liftCompare :: (a0 -> b -> Ordering) -> XNor a a0 -> XNor a b -> Ordering #

Read a => Read1 (XNor a) Source #

Since: 0.6.1.0

Instance details

Defined in Yaya.Pattern

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (XNor a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [XNor a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (XNor a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [XNor a a0] #

Show a => Show1 (XNor a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> XNor a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [XNor a a0] -> ShowS #

Traversable (XNor a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

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

sequenceA :: Applicative f => XNor a (f a0) -> f (XNor a a0) #

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

sequence :: Monad m => XNor a (m a0) -> m (XNor a a0) #

Functor (XNor a) Source # 
Instance details

Defined in Yaya.Pattern

Methods

fmap :: (a0 -> b) -> XNor a a0 -> XNor a b #

(<$) :: a0 -> XNor a b -> XNor a a0 #

Monoid (Mu (XNor a)) Source # 
Instance details

Defined in Yaya.Applied

Methods

mempty :: Mu (XNor a) #

mappend :: Mu (XNor a) -> Mu (XNor a) -> Mu (XNor a) #

mconcat :: [Mu (XNor a)] -> Mu (XNor a) #

Monoid (Fix (XNor a)) Source # 
Instance details

Defined in Yaya.Applied

Methods

mempty :: Fix (XNor a) #

mappend :: Fix (XNor a) -> Fix (XNor a) -> Fix (XNor a) #

mconcat :: [Fix (XNor a)] -> Fix (XNor a) #

Semigroup (Mu (XNor a)) Source # 
Instance details

Defined in Yaya.Applied

Methods

(<>) :: Mu (XNor a) -> Mu (XNor a) -> Mu (XNor a) #

sconcat :: NonEmpty (Mu (XNor a)) -> Mu (XNor a) #

stimes :: Integral b => b -> Mu (XNor a) -> Mu (XNor a) #

Semigroup (Fix (XNor a)) Source # 
Instance details

Defined in Yaya.Applied

Methods

(<>) :: Fix (XNor a) -> Fix (XNor a) -> Fix (XNor a) #

sconcat :: NonEmpty (Fix (XNor a)) -> Fix (XNor a) #

stimes :: Integral b => b -> Fix (XNor a) -> Fix (XNor a) #

IsList (Nu (XNor a)) Source #

This instance is safe, since both structures are lazy.

Instance details

Defined in Yaya.Applied

Associated Types

type Item (Nu (XNor a)) #

Methods

fromList :: [Item (Nu (XNor a))] -> Nu (XNor a) #

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

toList :: Nu (XNor a) -> [Item (Nu (XNor a))] #

Generic (XNor a b) Source # 
Instance details

Defined in Yaya.Pattern

Associated Types

type Rep (XNor a b) :: Type -> Type #

Methods

from :: XNor a b -> Rep (XNor a b) x #

to :: Rep (XNor a b) x -> XNor a b #

(Read a, Read b) => Read (XNor a b) Source #

Since: 0.6.1.0

Instance details

Defined in Yaya.Pattern

Methods

readsPrec :: Int -> ReadS (XNor a b) #

readList :: ReadS [XNor a b] #

readPrec :: ReadPrec (XNor a b) #

readListPrec :: ReadPrec [XNor a b] #

(Show a, Show b) => Show (XNor a b) Source # 
Instance details

Defined in Yaya.Pattern

Methods

showsPrec :: Int -> XNor a b -> ShowS #

show :: XNor a b -> String #

showList :: [XNor a b] -> ShowS #

(Eq a, Eq b) => Eq (XNor a b) Source # 
Instance details

Defined in Yaya.Pattern

Methods

(==) :: XNor a b -> XNor a b -> Bool #

(/=) :: XNor a b -> XNor a b -> Bool #

(Ord a, Ord b) => Ord (XNor a b) Source # 
Instance details

Defined in Yaya.Pattern

Methods

compare :: XNor a b -> XNor a b -> Ordering #

(<) :: XNor a b -> XNor a b -> Bool #

(<=) :: XNor a b -> XNor a b -> Bool #

(>) :: XNor a b -> XNor a b -> Bool #

(>=) :: XNor a b -> XNor a b -> Bool #

max :: XNor a b -> XNor a b -> XNor a b #

min :: XNor a b -> XNor a b -> XNor a b #

type Rep1 (XNor a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Pattern

type Rep1 (XNor a :: Type -> Type) = D1 ('MetaData "XNor" "Yaya.Pattern" "yaya-0.6.2.0-EgozjXGIZKx9HLMrnz1gAG" 'False) (C1 ('MetaCons "Neither" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Both" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceLazy 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1))
type Item (Nu (XNor a)) Source # 
Instance details

Defined in Yaya.Applied

type Item (Nu (XNor a)) = a
type Rep (XNor a b) Source # 
Instance details

Defined in Yaya.Pattern

type Rep (XNor a b) = D1 ('MetaData "XNor" "Yaya.Pattern" "yaya-0.6.2.0-EgozjXGIZKx9HLMrnz1gAG" 'False) (C1 ('MetaCons "Neither" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Both" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceLazy 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 b)))

andMaybe :: (a -> c) -> (a -> b -> c) -> AndMaybe a b -> c Source #

Eliminator for AndMaybe, akin to either or maybe.

Since: 0.6.1.0

xnor :: c -> (a -> b -> c) -> XNor a b -> c Source #

Eliminator for XNor, akin to either or maybe.

Since: 0.6.1.0

Orphan instances

Applicative Maybe Source # 
Instance details

Methods

pure :: a -> Maybe a #

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

liftA2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c #

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

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

Monad Maybe Source # 
Instance details

Methods

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

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

return :: a -> Maybe a #

Applicative (Either a) Source # 
Instance details

Methods

pure :: a0 -> Either a a0 #

(<*>) :: Either a (a0 -> b) -> Either a a0 -> Either a b #

liftA2 :: (a0 -> b -> c) -> Either a a0 -> Either a b -> Either a c #

(*>) :: Either a a0 -> Either a b -> Either a b #

(<*) :: Either a a0 -> Either a b -> Either a a0 #

Monad (Either a) Source # 
Instance details

Methods

(>>=) :: Either a a0 -> (a0 -> Either a b) -> Either a b #

(>>) :: Either a a0 -> Either a b -> Either a b #

return :: a0 -> Either a a0 #

Comonad (Pair a) Source # 
Instance details

Methods

extract :: Pair a a0 -> a0 #

duplicate :: Pair a a0 -> Pair a (Pair a a0) #

extend :: (Pair a a0 -> b) -> Pair a a0 -> Pair a b #