neither-data-0.2.3.4: The Neither datatype
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Neither

Description

In this module, instances have been annotated with the interpretation of the Neither type that they use.

Synopsis

Documentation

data Neither a b #

The Neither type has a single constructor and ignores its type arguments

Constructors

Neither 

Instances

Instances details
Bitraversable Neither #

An empty container, that, when in an applicative, must always be a minimally wrapped constant value

Instance details

Defined in Data.Neither

Methods

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

Bifoldable Neither #

An empty container which folds to the starting value or the identity

Instance details

Defined in Data.Neither

Methods

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

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

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

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

Bifunctor Neither #

An empty container

Instance details

Defined in Data.Neither

Methods

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

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

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

Eq2 Neither #

Empty container that is equal to itself (with no values to compare)

Instance details

Defined in Data.Neither

Methods

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

Ord2 Neither #

Empty container that is equal to itself (with no values to compare)

Instance details

Defined in Data.Neither

Methods

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

Arrow Neither #

A dummy function representation

Instance details

Defined in Data.Neither

Methods

arr :: (b -> c) -> Neither b c #

first :: Neither b c -> Neither (b, d) (c, d) #

second :: Neither b c -> Neither (d, b) (d, c) #

(***) :: Neither b c -> Neither b' c' -> Neither (b, b') (c, c') #

(&&&) :: Neither b c -> Neither b c' -> Neither b (c, c') #

ArrowZero Neither #

A dummy function representation, so the zero arrow is merely unique by its type parameters

Instance details

Defined in Data.Neither

Methods

zeroArrow :: Neither b c #

ArrowPlus Neither #

The trivial single element monoid on a dummy function representation

Instance details

Defined in Data.Neither

Methods

(<+>) :: Neither b c -> Neither b c -> Neither b c #

ArrowChoice Neither #

A dummy function representation, where all choices are the same

Instance details

Defined in Data.Neither

Methods

left :: Neither b c -> Neither (Either b d) (Either c d) #

right :: Neither b c -> Neither (Either d b) (Either d c) #

(+++) :: Neither b c -> Neither b' c' -> Neither (Either b b') (Either c c') #

(|||) :: Neither b d -> Neither c d -> Neither (Either b c) d #

ArrowApply Neither #

A dummy function representation, where application returns another dummy

Instance details

Defined in Data.Neither

Methods

app :: Neither (Neither b c, b) c #

ArrowLoop Neither #

A dummy function representation, where recursion creation returns another dummy

Instance details

Defined in Data.Neither

Methods

loop :: Neither (b, d) (c, d) -> Neither b c #

Monad (Neither a) #

An empty container

Instance details

Defined in Data.Neither

Methods

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

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

return :: a0 -> Neither a a0 #

Functor (Neither a) #

An empty container

Instance details

Defined in Data.Neither

Methods

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

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

MonadFix (Neither a) #

All functions from Neither to Neither must have Neither as a fixed point (if you ignore types)

Instance details

Defined in Data.Neither

Methods

mfix :: (a0 -> Neither a a0) -> Neither a a0 #

MonadFail (Neither a) #

An empty container

Instance details

Defined in Data.Neither

Methods

fail :: String -> Neither a a0 #

Applicative (Neither a) #

An empty container

Instance details

Defined in Data.Neither

Methods

pure :: a0 -> Neither a a0 #

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

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

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

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

Foldable (Neither a) #

An empty container which folds to the starting value or the identity

Instance details

Defined in Data.Neither

Methods

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

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

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

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

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

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

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

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

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

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

null :: Neither a a0 -> Bool #

length :: Neither a a0 -> Int #

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

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

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

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

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

Traversable (Neither a) #

An empty container, that, when in an applicative, must always be a minimally wrapped constant value

Instance details

Defined in Data.Neither

Methods

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

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

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

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

Contravariant (Neither a) #

An empty container or an uncallable or no-op function representation

Instance details

Defined in Data.Neither

Methods

contramap :: (a0 -> b) -> Neither a b -> Neither a a0 #

(>$) :: b -> Neither a b -> Neither a a0 #

Eq1 (Neither a) #

Empty container that is equal to itself (with no values to compare)

Instance details

Defined in Data.Neither

Methods

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

Ord1 (Neither a) #

Empty container that is equal to itself (with no values to compare)

Instance details

Defined in Data.Neither

Methods

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

MonadZip (Neither a) #

An empty container

Instance details

Defined in Data.Neither

Methods

mzip :: Neither a a0 -> Neither a b -> Neither a (a0, b) #

mzipWith :: (a0 -> b -> c) -> Neither a a0 -> Neither a b -> Neither a c #

munzip :: Neither a (a0, b) -> (Neither a a0, Neither a b) #

MonadIO (Neither a) #

An empty container

Instance details

Defined in Data.Neither

Methods

liftIO :: IO a0 -> Neither a a0 #

Alternative (Neither a) #

An empty container with no-ops

Instance details

Defined in Data.Neither

Methods

empty :: Neither a a0 #

(<|>) :: Neither a a0 -> Neither a a0 -> Neither a a0 #

some :: Neither a a0 -> Neither a [a0] #

many :: Neither a a0 -> Neither a [a0] #

MonadPlus (Neither a) #

An empty container with no-ops

Instance details

Defined in Data.Neither

Methods

mzero :: Neither a a0 #

mplus :: Neither a a0 -> Neither a a0 -> Neither a a0 #

Category Neither #

The constant functor from Set to 1

Instance details

Defined in Data.Neither

Methods

id :: forall (a :: k). Neither a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Neither b c -> Neither a b -> Neither a c #

Bounded (Neither a b) # 
Instance details

Defined in Data.Neither

Methods

minBound :: Neither a b #

maxBound :: Neither a b #

Enum (Neither a b) # 
Instance details

Defined in Data.Neither

Methods

succ :: Neither a b -> Neither a b #

pred :: Neither a b -> Neither a b #

toEnum :: Int -> Neither a b #

fromEnum :: Neither a b -> Int #

enumFrom :: Neither a b -> [Neither a b] #

enumFromThen :: Neither a b -> Neither a b -> [Neither a b] #

enumFromTo :: Neither a b -> Neither a b -> [Neither a b] #

enumFromThenTo :: Neither a b -> Neither a b -> Neither a b -> [Neither a b] #

Eq (Neither a b) # 
Instance details

Defined in Data.Neither

Methods

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

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

Floating (Neither a b) #

A trivial single element exponential field, where every number is Neither

Instance details

Defined in Data.Neither

Methods

pi :: Neither a b #

exp :: Neither a b -> Neither a b #

log :: Neither a b -> Neither a b #

sqrt :: Neither a b -> Neither a b #

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

logBase :: Neither a b -> Neither a b -> Neither a b #

sin :: Neither a b -> Neither a b #

cos :: Neither a b -> Neither a b #

tan :: Neither a b -> Neither a b #

asin :: Neither a b -> Neither a b #

acos :: Neither a b -> Neither a b #

atan :: Neither a b -> Neither a b #

sinh :: Neither a b -> Neither a b #

cosh :: Neither a b -> Neither a b #

tanh :: Neither a b -> Neither a b #

asinh :: Neither a b -> Neither a b #

acosh :: Neither a b -> Neither a b #

atanh :: Neither a b -> Neither a b #

log1p :: Neither a b -> Neither a b #

expm1 :: Neither a b -> Neither a b #

log1pexp :: Neither a b -> Neither a b #

log1mexp :: Neither a b -> Neither a b #

Fractional (Neither a b) #

A trivial single element field where every ratio is Neither

Instance details

Defined in Data.Neither

Methods

(/) :: Neither a b -> Neither a b -> Neither a b #

recip :: Neither a b -> Neither a b #

fromRational :: Rational -> Neither a b #

Integral (Neither a b) #

A number type that only contains zero, or a trivial single element euclidean domain

Instance details

Defined in Data.Neither

Methods

quot :: Neither a b -> Neither a b -> Neither a b #

rem :: Neither a b -> Neither a b -> Neither a b #

div :: Neither a b -> Neither a b -> Neither a b #

mod :: Neither a b -> Neither a b -> Neither a b #

quotRem :: Neither a b -> Neither a b -> (Neither a b, Neither a b) #

divMod :: Neither a b -> Neither a b -> (Neither a b, Neither a b) #

toInteger :: Neither a b -> Integer #

(Data a, Data b) => Data (Neither a b) # 
Instance details

Defined in Data.Neither

Methods

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

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

toConstr :: Neither a b -> Constr #

dataTypeOf :: Neither a b -> DataType #

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

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

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

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

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

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

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

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

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

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

Num (Neither a b) #

A trivial single element group with no-ops, where every integer is Neither

Instance details

Defined in Data.Neither

Methods

(+) :: Neither a b -> Neither a b -> Neither a b #

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

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

negate :: Neither a b -> Neither a b #

abs :: Neither a b -> Neither a b #

signum :: Neither a b -> Neither a b #

fromInteger :: Integer -> Neither a b #

Ord (Neither a b) # 
Instance details

Defined in Data.Neither

Methods

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

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

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

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

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

max :: Neither a b -> Neither a b -> Neither a b #

min :: Neither a b -> Neither a b -> Neither a b #

Read (Neither a b) # 
Instance details

Defined in Data.Neither

Real (Neither a b) #

A number type that only contains zero

Instance details

Defined in Data.Neither

Methods

toRational :: Neither a b -> Rational #

RealFrac (Neither a b) #

A number type that only contains zero

Instance details

Defined in Data.Neither

Methods

properFraction :: Integral b0 => Neither a b -> (b0, Neither a b) #

truncate :: Integral b0 => Neither a b -> b0 #

round :: Integral b0 => Neither a b -> b0 #

ceiling :: Integral b0 => Neither a b -> b0 #

floor :: Integral b0 => Neither a b -> b0 #

Show (Neither a b) # 
Instance details

Defined in Data.Neither

Methods

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

show :: Neither a b -> String #

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

Ix (Neither a b) #

There is only one Neither value

Instance details

Defined in Data.Neither

Methods

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

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

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

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

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

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

IsString (Neither a b) #

Every string is Neither

Instance details

Defined in Data.Neither

Methods

fromString :: String -> Neither a b #

Semigroup (Neither a b) #

The trivial single element semigroup

Instance details

Defined in Data.Neither

Methods

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

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

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

Monoid (Neither a b) #

The trivial single element monoid

Instance details

Defined in Data.Neither

Methods

mempty :: Neither a b #

mappend :: Neither a b -> Neither a b -> Neither a b #

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

Bits (Neither a b) #

A bitstring with zero length

Instance details

Defined in Data.Neither

Methods

(.&.) :: Neither a b -> Neither a b -> Neither a b #

(.|.) :: Neither a b -> Neither a b -> Neither a b #

xor :: Neither a b -> Neither a b -> Neither a b #

complement :: Neither a b -> Neither a b #

shift :: Neither a b -> Int -> Neither a b #

rotate :: Neither a b -> Int -> Neither a b #

zeroBits :: Neither a b #

bit :: Int -> Neither a b #

setBit :: Neither a b -> Int -> Neither a b #

clearBit :: Neither a b -> Int -> Neither a b #

complementBit :: Neither a b -> Int -> Neither a b #

testBit :: Neither a b -> Int -> Bool #

bitSizeMaybe :: Neither a b -> Maybe Int #

bitSize :: Neither a b -> Int #

isSigned :: Neither a b -> Bool #

shiftL :: Neither a b -> Int -> Neither a b #

unsafeShiftL :: Neither a b -> Int -> Neither a b #

shiftR :: Neither a b -> Int -> Neither a b #

unsafeShiftR :: Neither a b -> Int -> Neither a b #

rotateL :: Neither a b -> Int -> Neither a b #

rotateR :: Neither a b -> Int -> Neither a b #

popCount :: Neither a b -> Int #

FiniteBits (Neither a b) #

A bitstring with zero length

Instance details

Defined in Data.Neither

neither :: a -> b -> Neither a b #

Produces a Neither value whose types match the arguments, discarding the arguments