| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Yaya.Pattern
Contents
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
- data Either a b
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- lefts :: [Either a b] -> [a]
- rights :: [Either a b] -> [b]
- partitionEithers :: [Either a b] -> ([a], [b])
- isLeft :: Either a b -> Bool
- isRight :: Either a b -> Bool
- fromLeft :: Either a b -> a
- fromRight :: Either a b -> b
- data Maybe a
- maybe :: b -> (a -> b) -> Maybe a -> b
- isJust :: Maybe a -> Bool
- isNothing :: Maybe a -> Bool
- fromJust :: Maybe a -> a
- fromMaybe :: a -> Maybe a -> a
- maybeToList :: Maybe a -> [a]
- listToMaybe :: [a] -> Maybe a
- catMaybes :: [Maybe a] -> [a]
- mapMaybe :: (a -> Maybe b) -> [a] -> [b]
- data Pair a b = !a :!: !b
- type (:!:) = Pair
- fst :: Pair a b -> a
- snd :: Pair a b -> b
- swap :: Pair a b -> Pair b a
- uncurry :: (a -> b -> c) -> Pair a b -> c
- zip :: [a] -> [b] -> [Pair a b]
- unzip :: [Pair a b] -> ([a], [b])
- curry :: (Pair a b -> c) -> a -> b -> c
- data AndMaybe a b
- data XNor a b
- andMaybe :: (a -> c) -> (a -> b -> c) -> AndMaybe a b -> c
- xnor :: c -> (a -> b -> c) -> XNor a b -> c
Documentation
The strict choice type.
Instances
| Assoc Either | |
| Swap Either | |
Defined in Data.Strict.Either | |
| Bifoldable Either | |
| Bifunctor Either | |
| Bitraversable Either | |
Defined in Data.Strict.Either Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Either a b -> f (Either c d) # | |
| Eq2 Either | |
| Ord2 Either | |
Defined in Data.Strict.Either | |
| Read2 Either | |
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 | |
| NFData2 Either | |
Defined in Data.Strict.Either | |
| Hashable2 Either | |
Defined in Data.Strict.Either | |
| Corecursive (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # | |
| Projectable (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # | |
| Recursive (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # | |
| Generic1 (Either a :: Type -> Type) | |
| Steppable (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # | |
| Foldable (Either e) | |
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 # elem :: Eq a => a -> Either e a -> Bool # maximum :: Ord a => Either e a -> a # minimum :: Ord a => Either e a -> a # | |
| Eq a => Eq1 (Either a) | |
| Ord a => Ord1 (Either a) | |
Defined in Data.Strict.Either | |
| Read a => Read1 (Either a) | |
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) | |
| Traversable (Either e) | |
| Applicative (Either a) Source # | |
| Functor (Either a) | |
| Monad (Either a) Source # | |
| NFData a => NFData1 (Either a) | |
Defined in Data.Strict.Either | |
| Hashable a => Hashable1 (Either a) | |
Defined in Data.Strict.Either | |
| (Data a, Data b) => Data (Either a b) | |
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) | |
| Generic (Either a b) | |
| (Read a, Read b) => Read (Either a b) | |
| (Show a, Show b) => Show (Either a b) | |
| (Binary a, Binary b) => Binary (Either a b) | |
| (NFData a, NFData b) => NFData (Either a b) | |
Defined in Data.Strict.Either | |
| (Eq a, Eq b) => Eq (Either a b) | |
| (Ord a, Ord b) => Ord (Either a b) | |
| (Hashable a, Hashable b) => Hashable (Either a b) | |
Defined in Data.Strict.Either | |
| Strict (Either a b) (Either a b) | |
| type Rep1 (Either a :: Type -> Type) | |
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) | |
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))) | |
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.
The type of strict optional values.
Instances
| Foldable Maybe | |
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 # elem :: Eq a => a -> Maybe a -> Bool # maximum :: Ord a => Maybe a -> a # minimum :: Ord a => Maybe a -> a # | |
| Eq1 Maybe | |
| Ord1 Maybe | |
Defined in Data.Strict.Maybe | |
| Read1 Maybe | |
Defined in Data.Strict.Maybe | |
| Show1 Maybe | |
| Traversable Maybe | |
| Applicative Maybe Source # | |
| Functor Maybe | |
| Monad Maybe Source # | |
| NFData1 Maybe | |
Defined in Data.Strict.Maybe | |
| Hashable1 Maybe | |
Defined in Data.Strict.Maybe | |
| Generic1 Maybe | |
| Projectable (->) Natural Maybe Source # | |
| Recursive (->) Natural Maybe Source # | |
| Corecursive (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # | |
| Projectable (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # | |
| Recursive (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # | |
| Steppable (->) Natural Maybe Source # | |
| Steppable (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # | |
| Data a => Data (Maybe a) | |
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) | |
| Semigroup a => Semigroup (Maybe a) | |
| Generic (Maybe a) | |
| Read a => Read (Maybe a) | |
| Show a => Show (Maybe a) | |
| Binary a => Binary (Maybe a) | |
| NFData a => NFData (Maybe a) | |
Defined in Data.Strict.Maybe | |
| Eq a => Eq (Maybe a) | |
| Ord a => Ord (Maybe a) | |
| Hashable a => Hashable (Maybe a) | |
Defined in Data.Strict.Maybe | |
| Strict (Maybe a) (Maybe a) | |
| type Rep1 Maybe | |
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) | |
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))) | |
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.
The type of strict pairs.
Constructors
| !a :!: !b infix 2 |
Instances
| Assoc Pair | |
| Swap Pair | |
Defined in Data.Strict.Tuple | |
| Bifoldable Pair | |
| Bifunctor Pair | |
| Bitraversable Pair | |
Defined in Data.Strict.Tuple Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Pair a b -> f (Pair c d) # | |
| Eq2 Pair | |
| Ord2 Pair | |
Defined in Data.Strict.Tuple | |
| Read2 Pair |
|
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 | |
| NFData2 Pair | |
Defined in Data.Strict.Tuple | |
| Hashable2 Pair | |
Defined in Data.Strict.Tuple | |
| Generic1 (Pair a :: Type -> Type) | |
| Foldable (Pair e) | |
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 # elem :: Eq a => a -> Pair e a -> Bool # maximum :: Ord a => Pair e a -> a # minimum :: Ord a => Pair e a -> a # | |
| Eq a => Eq1 (Pair a) | |
| Ord a => Ord1 (Pair a) | |
Defined in Data.Strict.Tuple | |
| Read a => Read1 (Pair a) | |
Defined in Data.Strict.Tuple | |
| Show a => Show1 (Pair a) | |
| Traversable (Pair e) | |
| Functor (Pair e) | |
| Comonad (Pair a) Source # | |
| NFData a => NFData1 (Pair a) | |
Defined in Data.Strict.Tuple | |
| Hashable a => Hashable1 (Pair a) | |
Defined in Data.Strict.Tuple | |
| (Data a, Data b) => Data (Pair a b) | |
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) | |
| (Semigroup a, Semigroup b) => Semigroup (Pair a b) | |
| (Bounded a, Bounded b) => Bounded (Pair a b) | |
| Generic (Pair a b) | |
| (Ix a, Ix b) => Ix (Pair a b) | |
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) | |
| (Show a, Show b) => Show (Pair a b) | |
| (Binary a, Binary b) => Binary (Pair a b) | |
| (NFData a, NFData b) => NFData (Pair a b) | |
Defined in Data.Strict.Tuple | |
| (Eq a, Eq b) => Eq (Pair a b) | |
| (Ord a, Ord b) => Ord (Pair a b) | |
Defined in Data.Strict.Tuple | |
| (Hashable a, Hashable b) => Hashable (Pair a b) | |
Defined in Data.Strict.Tuple | |
| Strict (a, b) (Pair a b) | |
| Field1 (Pair a b) (Pair a' b) a a' | Since: lens-4.20 |
| Field2 (Pair a b) (Pair a b') b b' | Since: lens-4.20 |
| type Rep1 (Pair a :: Type -> Type) | |
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) | |
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))) | |
uncurry :: (a -> b -> c) -> Pair a b -> c #
Convert a curried function to a function on strict pairs.
Isomorphic to (a, , it’s also the pattern functor for non-empty
lists.Maybe b)
Instances
Isomorphic to , it’s also the pattern functor for lists.Maybe (a, b)
Instances
| Bifunctor XNor Source # | |
| Eq2 XNor Source # | |
| Ord2 XNor Source # | |
Defined in Yaya.Pattern | |
| Read2 XNor Source # | Since: 0.6.1.0 |
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 # | |
| Corecursive (->) ([a] :: Type) (XNor a :: Type -> Type) Source # | |
| Projectable (->) ([a] :: Type) (XNor a :: Type -> Type) Source # | |
| Generic1 (XNor a :: Type -> Type) Source # | |
| Steppable (->) ([a] :: Type) (XNor a :: Type -> Type) Source # | |
| Foldable (XNor a) Source # | |
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 # elem :: Eq a0 => a0 -> XNor a a0 -> Bool # maximum :: Ord a0 => XNor a a0 -> a0 # minimum :: Ord a0 => XNor a a0 -> a0 # | |
| Eq a => Eq1 (XNor a) Source # | |
| Ord a => Ord1 (XNor a) Source # | |
Defined in Yaya.Pattern | |
| Read a => Read1 (XNor a) Source # | Since: 0.6.1.0 |
Defined in Yaya.Pattern | |
| Show a => Show1 (XNor a) Source # | |
| Traversable (XNor a) Source # | |
| Functor (XNor a) Source # | |
| Monoid (Mu (XNor a)) Source # | |
| Monoid (Fix (XNor a)) Source # | |
| Semigroup (Mu (XNor a)) Source # | |
| Semigroup (Fix (XNor a)) Source # | |
| IsList (Nu (XNor a)) Source # | This instance is safe, since both structures are lazy. |
| Generic (XNor a b) Source # | |
| (Read a, Read b) => Read (XNor a b) Source # | Since: 0.6.1.0 |
| (Show a, Show b) => Show (XNor a b) Source # | |
| (Eq a, Eq b) => Eq (XNor a b) Source # | |
| (Ord a, Ord b) => Ord (XNor a b) Source # | |
Defined in Yaya.Pattern | |
| type Rep1 (XNor a :: Type -> Type) Source # | |
Defined in Yaya.Pattern type Rep1 (XNor a :: Type -> Type) = D1 ('MetaData "XNor" "Yaya.Pattern" "yaya-0.6.1.0-LG58VglF8GNKDueZFlppV0" '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 # | |
Defined in Yaya.Applied | |
| type Rep (XNor a b) Source # | |
Defined in Yaya.Pattern type Rep (XNor a b) = D1 ('MetaData "XNor" "Yaya.Pattern" "yaya-0.6.1.0-LG58VglF8GNKDueZFlppV0" '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))) | |