haskus-utils-variant-3.2.1: Variant and EADT
Safe HaskellNone
LanguageHaskell2010

Haskus.Utils.Variant.VEither

Description

Variant biased towards one type

This allows definition of common type classes (Functor, etc.) that can't be provided for Variant

Synopsis

Documentation

data VEither es a Source #

Variant biased towards one type

Instances

Instances details
Monad (VEither es) Source #

Monad instance for VEither

>>> let x   = VRight True    :: VEither '[Int,Float] Bool
>>> let f v = VRight (not v) :: VEither '[Int,Float] Bool
>>> x >>= f
VRight False
Instance details

Defined in Haskus.Utils.Variant.VEither

Methods

(>>=) :: VEither es a -> (a -> VEither es b) -> VEither es b #

(>>) :: VEither es a -> VEither es b -> VEither es b #

return :: a -> VEither es a #

Functor (VEither es) Source #

Functor instance for VEither

>>> let x = VRight True :: VEither '[Int,Float] Bool
>>> fmap (\b -> if b then "Success" else "Failure") x
VRight "Success"
Instance details

Defined in Haskus.Utils.Variant.VEither

Methods

fmap :: (a -> b) -> VEither es a -> VEither es b #

(<$) :: a -> VEither es b -> VEither es a #

Applicative (VEither es) Source #

Applicative instance for VEither

>>> let x = VRight True  :: VEither '[Int,Float] Bool
>>> let y = VRight False :: VEither '[Int,Float] Bool
>>> (&&) <$> x <*> y
VRight False
>>> (||) <$> x <*> y
VRight True
Instance details

Defined in Haskus.Utils.Variant.VEither

Methods

pure :: a -> VEither es a #

(<*>) :: VEither es (a -> b) -> VEither es a -> VEither es b #

liftA2 :: (a -> b -> c) -> VEither es a -> VEither es b -> VEither es c #

(*>) :: VEither es a -> VEither es b -> VEither es b #

(<*) :: VEither es a -> VEither es b -> VEither es a #

Foldable (VEither es) Source #

Foldable instance for VEither

>>> let x   = VRight True    :: VEither '[Int,Float] Bool
>>> let y   = VLeft (V "failed" :: V '[String,Int]) :: VEither '[String,Int] Bool
>>> forM_ x print
True
>>> forM_ y print
Instance details

Defined in Haskus.Utils.Variant.VEither

Methods

fold :: Monoid m => VEither es m -> m #

foldMap :: Monoid m => (a -> m) -> VEither es a -> m #

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

foldr :: (a -> b -> b) -> b -> VEither es a -> b #

foldr' :: (a -> b -> b) -> b -> VEither es a -> b #

foldl :: (b -> a -> b) -> b -> VEither es a -> b #

foldl' :: (b -> a -> b) -> b -> VEither es a -> b #

foldr1 :: (a -> a -> a) -> VEither es a -> a #

foldl1 :: (a -> a -> a) -> VEither es a -> a #

toList :: VEither es a -> [a] #

null :: VEither es a -> Bool #

length :: VEither es a -> Int #

elem :: Eq a => a -> VEither es a -> Bool #

maximum :: Ord a => VEither es a -> a #

minimum :: Ord a => VEither es a -> a #

sum :: Num a => VEither es a -> a #

product :: Num a => VEither es a -> a #

Traversable (VEither es) Source # 
Instance details

Defined in Haskus.Utils.Variant.VEither

Methods

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

sequenceA :: Applicative f => VEither es (f a) -> f (VEither es a) #

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

sequence :: Monad m => VEither es (m a) -> m (VEither es a) #

(Show a, Show (V es)) => Show (VEither es a) Source # 
Instance details

Defined in Haskus.Utils.Variant.VEither

Methods

showsPrec :: Int -> VEither es a -> ShowS #

show :: VEither es a -> String #

showList :: [VEither es a] -> ShowS #

pattern VLeft :: forall x xs. V xs -> VEither xs x Source #

Left value

>>> VLeft (V "failed" :: V '[String,Int]) :: VEither '[String,Int] Bool
VLeft "failed"

pattern VRight :: forall x xs. x -> VEither xs x Source #

Right value

>>> VRight True :: VEither '[String,Int] Bool
VRight True

veitherFromVariant :: V (a ': es) -> VEither es a Source #

Convert a Variant into a VEither

>>> let x = V "Test" :: V '[Int,String,Double]
>>> veitherFromVariant x
VLeft "Test"

veitherToVariant :: VEither es a -> V (a ': es) Source #

Convert a VEither into a Variant

>>> let x = VRight True :: VEither '[Int,Float] Bool
>>> veitherToVariant x
True

veitherToValue :: forall a. VEither '[] a -> a Source #

Extract from a VEither without left types

>>> let x = VRight True :: VEither '[] Bool
>>> veitherToValue x
True

veitherBimap :: (V es -> V fs) -> (a -> b) -> VEither es a -> VEither fs b Source #

Bimap for VEither

>>> let x = VRight True :: VEither '[Int,Float] Bool
>>> veitherBimap id not x
VRight False

type VEitherLift es es' = LiftVariant es es' Source #

veitherLift :: forall es' es a. VEitherLift es es' => VEither es a -> VEither es' a Source #

Lift a VEither into another

veitherAppend :: forall ns es a. VEither es a -> VEither (Concat es ns) a Source #

Append errors to VEither

veitherPrepend :: forall ns es a. KnownNat (Length ns) => VEither es a -> VEither (Concat ns es) a Source #

Prepend errors to VEither

veitherCont :: (V es -> u) -> (a -> u) -> VEither es a -> u Source #

VEither continuations

veitherToEither :: VEither es a -> Either (V es) a Source #

Convert a VEither into an Either

>>> let x = VRight True :: VEither '[Int,Float] Bool
>>> veitherToEither x
Right True

veitherProduct :: KnownNat (Length (b ': e2)) => VEither e1 a -> VEither e2 b -> VEither (Tail (Product (a ': e1) (b ': e2))) (a, b) Source #

Product of two VEither