compactable-0.2.0.0: A typeclass for structures which can be catMaybed, filtered, and partitioned.
Safe HaskellNone
LanguageHaskell2010

Control.Functor.Dichotomous

Synopsis

Documentation

class Dichotomous (f :: Type -> Type -> Type) where Source #

Dichotomous is about types that are injective to (Maybe (These a b)) In other words a + b + (a * b) + 1. Therefore ab (,) b LeftOnly b ab LeftOrBoth a RightOnly a ab RightOrBoth a b Either a b ab These 1 None 1 ab MaybeBoth 1 b MaybeRight 1 b ab MaybeRightOrBoth 1 a MaybeLeft 1 a ab MaybeLeftOrBoth 1 a b MaybeEither 1 a b ab TheseOrNot

Methods

dichotomy :: f a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (f a b) Source #

Instances

Instances details
Dichotomous Either Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: Either a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (Either a b) Source #

Dichotomous (,) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: (a, b) -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (a, b) Source #

Dichotomous These Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: These a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (These a b) Source #

Dichotomous TheseOrNot Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: TheseOrNot a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (TheseOrNot a b) Source #

Dichotomous MaybeEither Source # 
Instance details

Defined in Control.Functor.Dichotomous

Dichotomous MaybeLeftOrBoth Source # 
Instance details

Defined in Control.Functor.Dichotomous

Dichotomous MaybeLeft Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: MaybeLeft a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (MaybeLeft a b) Source #

Dichotomous MaybeRightOrBoth Source # 
Instance details

Defined in Control.Functor.Dichotomous

Dichotomous MaybeRight Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: MaybeRight a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (MaybeRight a b) Source #

Dichotomous MaybeBoth Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: MaybeBoth a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (MaybeBoth a b) Source #

Dichotomous None Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: None a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (None a b) Source #

Dichotomous RightOrBoth Source # 
Instance details

Defined in Control.Functor.Dichotomous

Dichotomous RightOnly Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: RightOnly a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (RightOnly a b) Source #

Dichotomous LeftOrBoth Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: LeftOrBoth a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (LeftOrBoth a b) Source #

Dichotomous LeftOnly Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: LeftOnly a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (LeftOnly a b) Source #

hushLeft :: Dichotomous g => g l r -> Maybe r Source #

hushRight :: Dichotomous g => g l r -> Maybe l Source #

swap :: Dichotomous g => g a b -> Maybe (g b a) Source #

newtype AltSum f a Source #

Constructors

AltSum 

Fields

Instances

Instances details
Functor f => Functor (AltSum f) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

fmap :: (a -> b) -> AltSum f a -> AltSum f b #

(<$) :: a -> AltSum f b -> AltSum f a #

Applicative f => Applicative (AltSum f) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

pure :: a -> AltSum f a #

(<*>) :: AltSum f (a -> b) -> AltSum f a -> AltSum f b #

liftA2 :: (a -> b -> c) -> AltSum f a -> AltSum f b -> AltSum f c #

(*>) :: AltSum f a -> AltSum f b -> AltSum f b #

(<*) :: AltSum f a -> AltSum f b -> AltSum f a #

Alternative f => Alternative (AltSum f) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

empty :: AltSum f a #

(<|>) :: AltSum f a -> AltSum f a -> AltSum f a #

some :: AltSum f a -> AltSum f [a] #

many :: AltSum f a -> AltSum f [a] #

Alternative f => Semigroup (AltSum f a) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

(<>) :: AltSum f a -> AltSum f a -> AltSum f a #

sconcat :: NonEmpty (AltSum f a) -> AltSum f a #

stimes :: Integral b => b -> AltSum f a -> AltSum f a #

Alternative f => Monoid (AltSum f a) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

mempty :: AltSum f a #

mappend :: AltSum f a -> AltSum f a -> AltSum f a #

mconcat :: [AltSum f a] -> AltSum f a #

mfold' :: (Foldable f, Alternative m) => f a -> m a Source #

mlefts :: (Bifoldable f, Alternative m) => f a b -> m a Source #

mrights :: (Bifoldable f, Alternative m) => f a b -> m b Source #

flipThese :: These a b -> These b a Source #

newtype LeftOnly a b Source #

Constructors

LeftOnly 

Fields

Instances

Instances details
Dichotomous LeftOnly Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: LeftOnly a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (LeftOnly a b) Source #

Eq a => Eq (LeftOnly a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

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

Ord a => Ord (LeftOnly a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

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

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

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

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

max :: LeftOnly a b -> LeftOnly a b -> LeftOnly a b #

min :: LeftOnly a b -> LeftOnly a b -> LeftOnly a b #

Read a => Read (LeftOnly a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Show a => Show (LeftOnly a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

show :: LeftOnly a b -> String #

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

Generic (LeftOnly a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Associated Types

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

Methods

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

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

type Rep (LeftOnly a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

type Rep (LeftOnly a b) = D1 ('MetaData "LeftOnly" "Control.Functor.Dichotomous" "compactable-0.2.0.0-5KI6UAYCQgl1RWEyoYfh9X" 'True) (C1 ('MetaCons "LeftOnly" 'PrefixI 'True) (S1 ('MetaSel ('Just "unLeftOnly") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data LeftOrBoth a b Source #

Constructors

Left' a 
LBoth a b 

Instances

Instances details
Dichotomous LeftOrBoth Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: LeftOrBoth a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (LeftOrBoth a b) Source #

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

Defined in Control.Functor.Dichotomous

Methods

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

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

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

Defined in Control.Functor.Dichotomous

Methods

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

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

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

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

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

max :: LeftOrBoth a b -> LeftOrBoth a b -> LeftOrBoth a b #

min :: LeftOrBoth a b -> LeftOrBoth a b -> LeftOrBoth a b #

(Read a, Read b) => Read (LeftOrBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

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

Defined in Control.Functor.Dichotomous

Methods

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

show :: LeftOrBoth a b -> String #

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

Generic (LeftOrBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Associated Types

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

Methods

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

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

type Rep (LeftOrBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

type Rep (LeftOrBoth a b) = D1 ('MetaData "LeftOrBoth" "Control.Functor.Dichotomous" "compactable-0.2.0.0-5KI6UAYCQgl1RWEyoYfh9X" 'False) (C1 ('MetaCons "Left'" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "LBoth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)))

newtype RightOnly a b Source #

Constructors

RightOnly 

Fields

Instances

Instances details
Dichotomous RightOnly Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: RightOnly a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (RightOnly a b) Source #

Eq b => Eq (RightOnly a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

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

Ord b => Ord (RightOnly a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

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

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

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

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

max :: RightOnly a b -> RightOnly a b -> RightOnly a b #

min :: RightOnly a b -> RightOnly a b -> RightOnly a b #

Read b => Read (RightOnly a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Show b => Show (RightOnly a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

show :: RightOnly a b -> String #

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

Generic (RightOnly a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Associated Types

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

Methods

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

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

type Rep (RightOnly a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

type Rep (RightOnly a b) = D1 ('MetaData "RightOnly" "Control.Functor.Dichotomous" "compactable-0.2.0.0-5KI6UAYCQgl1RWEyoYfh9X" 'True) (C1 ('MetaCons "RightOnly" 'PrefixI 'True) (S1 ('MetaSel ('Just "unRightOnly") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)))

data RightOrBoth a b Source #

Constructors

Right' b 
RBoth a b 

Instances

Instances details
Dichotomous RightOrBoth Source # 
Instance details

Defined in Control.Functor.Dichotomous

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

Defined in Control.Functor.Dichotomous

Methods

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

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

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

Defined in Control.Functor.Dichotomous

Methods

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

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

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

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

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

max :: RightOrBoth a b -> RightOrBoth a b -> RightOrBoth a b #

min :: RightOrBoth a b -> RightOrBoth a b -> RightOrBoth a b #

(Read b, Read a) => Read (RightOrBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

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

Defined in Control.Functor.Dichotomous

Methods

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

show :: RightOrBoth a b -> String #

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

Generic (RightOrBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Associated Types

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

Methods

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

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

type Rep (RightOrBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

type Rep (RightOrBoth a b) = D1 ('MetaData "RightOrBoth" "Control.Functor.Dichotomous" "compactable-0.2.0.0-5KI6UAYCQgl1RWEyoYfh9X" 'False) (C1 ('MetaCons "Right'" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :+: C1 ('MetaCons "RBoth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)))

data These a b #

The These type represents values with two non-exclusive possibilities.

This can be useful to represent combinations of two values, where the combination is defined if either input is. Algebraically, the type These A B represents (A + B + AB), which doesn't factor easily into sums and products--a type like Either A (B, Maybe A) is unclear and awkward to use.

These has straightforward instances of Functor, Monad, &c., and behaves like a hybrid error/writer monad, as would be expected.

For zipping and unzipping of structures with These values, see Data.Align.

Constructors

This a 
That b 
These a b 

Instances

Instances details
Bifunctor These 
Instance details

Defined in Data.These

Methods

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

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

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

Swap These

Since: these-0.8

Instance details

Defined in Data.These

Methods

swap :: These a b -> These b a #

Assoc These

Since: these-0.8

Instance details

Defined in Data.These

Methods

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

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

Bitraversable These 
Instance details

Defined in Data.These

Methods

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

Bifoldable These 
Instance details

Defined in Data.These

Methods

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

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

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

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

Eq2 These

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

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

Ord2 These

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

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

Read2 These

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

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

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

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

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

Show2 These

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

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

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

NFData2 These

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

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

Hashable2 These

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

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

Dichotomous These Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: These a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (These a b) Source #

Semigroup a => Monad (These a) 
Instance details

Defined in Data.These

Methods

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

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

return :: a0 -> These a a0 #

Functor (These a) 
Instance details

Defined in Data.These

Methods

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

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

Semigroup a => Applicative (These a) 
Instance details

Defined in Data.These

Methods

pure :: a0 -> These a a0 #

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

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

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

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

Foldable (These a) 
Instance details

Defined in Data.These

Methods

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

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

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

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

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

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

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

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

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

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

null :: These a a0 -> Bool #

length :: These a a0 -> Int #

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

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

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

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

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

Traversable (These a) 
Instance details

Defined in Data.These

Methods

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

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

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

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

Eq a => Eq1 (These a)

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

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

Ord a => Ord1 (These a)

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

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

Read a => Read1 (These a)

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

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

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

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

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

Show a => Show1 (These a)

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

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

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

NFData a => NFData1 (These a)

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

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

Hashable a => Hashable1 (These a)

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

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

Monoid m => Compactable (These m) Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

compact :: These m (Maybe a) -> These m a Source #

separateThese :: These m (These l r) -> (These m l, These m r) Source #

filter :: (a -> Bool) -> These m a -> These m a Source #

partition :: (a -> Bool) -> These m a -> (These m a, These m a) Source #

mapMaybe :: Functor (These m) => (a -> Maybe b) -> These m a -> These m b Source #

contramapMaybe :: Contravariant (These m) => (Maybe b -> a) -> These m a -> These m b Source #

mapThese :: Functor (These m) => (a -> These l r) -> These m a -> (These m l, These m r) Source #

contramapThese :: Contravariant (These m) => (These l r -> a) -> These m a -> (These m l, These m r) Source #

applyMaybe :: Applicative (These m) => These m (a -> Maybe b) -> These m a -> These m b Source #

applyThese :: Applicative (These m) => These m (a -> These l r) -> These m a -> (These m l, These m r) Source #

bindMaybe :: Monad (These m) => (a -> These m (Maybe b)) -> These m a -> These m b Source #

bindThese :: Monad (These m) => (a -> These m (These l r)) -> These m a -> (These m l, These m r) Source #

traverseMaybe :: (Applicative g, Traversable (These m)) => (a -> g (Maybe b)) -> These m a -> g (These m b) Source #

traverseThese :: (Applicative g, Traversable (These m)) => (a -> g (These l r)) -> These m a -> g (These m l, These m r) Source #

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

Defined in Data.These

Associated Types

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

Methods

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

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

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

Defined in Data.These

Methods

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

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

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

Defined in Data.These

Methods

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

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

toConstr :: These a b -> Constr #

dataTypeOf :: These a b -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Data.These

Methods

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

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

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

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

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

max :: These a b -> These a b -> These a b #

min :: These a b -> These a b -> These a b #

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

Defined in Data.These

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

Defined in Data.These

Methods

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

show :: These a b -> String #

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

Generic (These a b) 
Instance details

Defined in Data.These

Associated Types

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

Methods

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

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

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

Defined in Data.These

Methods

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

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

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

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

Defined in Data.These

Methods

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

hash :: These a b -> Int #

(Binary a, Binary b) => Binary (These a b)

Since: these-0.7.1

Instance details

Defined in Data.These

Methods

put :: These a b -> Put #

get :: Get (These a b) #

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

(NFData a, NFData b) => NFData (These a b)

Since: these-0.7.1

Instance details

Defined in Data.These

Methods

rnf :: These a b -> () #

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

Defined in Data.These

type Rep (These a b) 
Instance details

Defined in Data.These

data None a b Source #

Constructors

None 

Instances

Instances details
Dichotomous None Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: None a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (None a b) Source #

Eq (None a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

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

Ord (None a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

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

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

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

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

max :: None a b -> None a b -> None a b #

min :: None a b -> None a b -> None a b #

Read (None a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

readList :: ReadS [None a b] #

readPrec :: ReadPrec (None a b) #

readListPrec :: ReadPrec [None a b] #

Show (None a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

show :: None a b -> String #

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

Generic (None a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Associated Types

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

Methods

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

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

type Rep (None a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

type Rep (None a b) = D1 ('MetaData "None" "Control.Functor.Dichotomous" "compactable-0.2.0.0-5KI6UAYCQgl1RWEyoYfh9X" 'False) (C1 ('MetaCons "None" 'PrefixI 'False) (U1 :: Type -> Type))

newtype MaybeBoth a b Source #

Constructors

MaybeBoth 

Fields

Instances

Instances details
Dichotomous MaybeBoth Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: MaybeBoth a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (MaybeBoth a b) Source #

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

Defined in Control.Functor.Dichotomous

Methods

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

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

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

Defined in Control.Functor.Dichotomous

Methods

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

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

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

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

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

max :: MaybeBoth a b -> MaybeBoth a b -> MaybeBoth a b #

min :: MaybeBoth a b -> MaybeBoth a b -> MaybeBoth a b #

(Read a, Read b) => Read (MaybeBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

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

Defined in Control.Functor.Dichotomous

Methods

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

show :: MaybeBoth a b -> String #

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

Generic (MaybeBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Associated Types

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

Methods

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

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

type Rep (MaybeBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

type Rep (MaybeBoth a b) = D1 ('MetaData "MaybeBoth" "Control.Functor.Dichotomous" "compactable-0.2.0.0-5KI6UAYCQgl1RWEyoYfh9X" 'True) (C1 ('MetaCons "MaybeBoth" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMaybeOrBoth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (a, b)))))

data MaybeRight a b Source #

Constructors

MRNothing 
MRight b 

Instances

Instances details
Dichotomous MaybeRight Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: MaybeRight a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (MaybeRight a b) Source #

Eq b => Eq (MaybeRight a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

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

Ord b => Ord (MaybeRight a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

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

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

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

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

max :: MaybeRight a b -> MaybeRight a b -> MaybeRight a b #

min :: MaybeRight a b -> MaybeRight a b -> MaybeRight a b #

Read b => Read (MaybeRight a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Show b => Show (MaybeRight a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

show :: MaybeRight a b -> String #

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

Generic (MaybeRight a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Associated Types

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

Methods

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

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

type Rep (MaybeRight a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

type Rep (MaybeRight a b) = D1 ('MetaData "MaybeRight" "Control.Functor.Dichotomous" "compactable-0.2.0.0-5KI6UAYCQgl1RWEyoYfh9X" 'False) (C1 ('MetaCons "MRNothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MRight" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)))

data MaybeRightOrBoth a b Source #

Constructors

MRBNothing 
MRBRight b 
MRBoth a b 

Instances

Instances details
Dichotomous MaybeRightOrBoth Source # 
Instance details

Defined in Control.Functor.Dichotomous

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

Defined in Control.Functor.Dichotomous

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

Defined in Control.Functor.Dichotomous

(Read b, Read a) => Read (MaybeRightOrBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

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

Defined in Control.Functor.Dichotomous

Generic (MaybeRightOrBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Associated Types

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

type Rep (MaybeRightOrBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

type Rep (MaybeRightOrBoth a b) = D1 ('MetaData "MaybeRightOrBoth" "Control.Functor.Dichotomous" "compactable-0.2.0.0-5KI6UAYCQgl1RWEyoYfh9X" 'False) (C1 ('MetaCons "MRBNothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MRBRight" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :+: C1 ('MetaCons "MRBoth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b))))

data MaybeLeft a b Source #

Constructors

MLNothing 
MLeft a 

Instances

Instances details
Dichotomous MaybeLeft Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: MaybeLeft a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (MaybeLeft a b) Source #

Eq a => Eq (MaybeLeft a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

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

Ord a => Ord (MaybeLeft a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

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

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

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

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

max :: MaybeLeft a b -> MaybeLeft a b -> MaybeLeft a b #

min :: MaybeLeft a b -> MaybeLeft a b -> MaybeLeft a b #

Read a => Read (MaybeLeft a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Show a => Show (MaybeLeft a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

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

show :: MaybeLeft a b -> String #

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

Generic (MaybeLeft a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Associated Types

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

Methods

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

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

type Rep (MaybeLeft a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

type Rep (MaybeLeft a b) = D1 ('MetaData "MaybeLeft" "Control.Functor.Dichotomous" "compactable-0.2.0.0-5KI6UAYCQgl1RWEyoYfh9X" 'False) (C1 ('MetaCons "MLNothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MLeft" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data MaybeLeftOrBoth a b Source #

Constructors

MLBNothing 
MLBLeft a 
MLBoth a b 

Instances

Instances details
Dichotomous MaybeLeftOrBoth Source # 
Instance details

Defined in Control.Functor.Dichotomous

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

Defined in Control.Functor.Dichotomous

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

Defined in Control.Functor.Dichotomous

(Read a, Read b) => Read (MaybeLeftOrBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

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

Defined in Control.Functor.Dichotomous

Generic (MaybeLeftOrBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Associated Types

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

Methods

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

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

type Rep (MaybeLeftOrBoth a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

type Rep (MaybeLeftOrBoth a b) = D1 ('MetaData "MaybeLeftOrBoth" "Control.Functor.Dichotomous" "compactable-0.2.0.0-5KI6UAYCQgl1RWEyoYfh9X" 'False) (C1 ('MetaCons "MLBNothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MLBLeft" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "MLBoth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b))))

data MaybeEither a b Source #

Constructors

MENothing 
MELeft a 
MERight b 

Instances

Instances details
Dichotomous MaybeEither Source # 
Instance details

Defined in Control.Functor.Dichotomous

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

Defined in Control.Functor.Dichotomous

Methods

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

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

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

Defined in Control.Functor.Dichotomous

Methods

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

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

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

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

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

max :: MaybeEither a b -> MaybeEither a b -> MaybeEither a b #

min :: MaybeEither a b -> MaybeEither a b -> MaybeEither a b #

(Read a, Read b) => Read (MaybeEither a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

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

Defined in Control.Functor.Dichotomous

Methods

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

show :: MaybeEither a b -> String #

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

Generic (MaybeEither a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Associated Types

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

Methods

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

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

type Rep (MaybeEither a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

type Rep (MaybeEither a b) = D1 ('MetaData "MaybeEither" "Control.Functor.Dichotomous" "compactable-0.2.0.0-5KI6UAYCQgl1RWEyoYfh9X" 'False) (C1 ('MetaCons "MENothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MELeft" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "MERight" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b))))

data TheseOrNot a b Source #

Constructors

This' a 
That' b 
These' a b 
Not 

Instances

Instances details
Dichotomous TheseOrNot Source # 
Instance details

Defined in Control.Functor.Dichotomous

Methods

dichotomy :: TheseOrNot a b -> Maybe (These a b) Source #

ymotohcid :: Maybe (These a b) -> Maybe (TheseOrNot a b) Source #

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

Defined in Control.Functor.Dichotomous

Methods

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

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

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

Defined in Control.Functor.Dichotomous

Methods

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

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

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

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

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

max :: TheseOrNot a b -> TheseOrNot a b -> TheseOrNot a b #

min :: TheseOrNot a b -> TheseOrNot a b -> TheseOrNot a b #

(Read a, Read b) => Read (TheseOrNot a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

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

Defined in Control.Functor.Dichotomous

Methods

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

show :: TheseOrNot a b -> String #

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

Generic (TheseOrNot a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous

Associated Types

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

Methods

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

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

type Rep (TheseOrNot a b) Source # 
Instance details

Defined in Control.Functor.Dichotomous