vary-0.1.0.3: Vary: Friendly and fast polymorphic variants (open unions/coproducts/extensible sums)
Safe HaskellNone
LanguageGHC2021

Vary.VEither

Synopsis

General Usage

This module is intended to be used qualified:

>>> import Vary.VEither (VEither(VLeft, VRight))
>>> import qualified Vary.VEither as VEither

And for many functions, it is useful or outright necessary to enable the following extensions:

>>> :set -XGHC2021
>>> :set -XDataKinds

Core type definition

data VEither (errs :: [Type]) a where Source #

Bundled Patterns

pattern VLeft :: forall a errs. Vary errs -> VEither errs a 
pattern VRight :: forall a errs. a -> VEither errs a 

Instances

Instances details
Foldable (VEither errs) Source # 
Instance details

Defined in Vary.VEither

Methods

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

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

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

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

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

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

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

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

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

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

null :: VEither errs a -> Bool #

length :: VEither errs a -> Int #

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

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

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

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

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

Traversable (VEither errs) Source # 
Instance details

Defined in Vary.VEither

Methods

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

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

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

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

Applicative (VEither errs) Source # 
Instance details

Defined in Vary.VEither

Methods

pure :: a -> VEither errs a #

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

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

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

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

Functor (VEither errs) Source # 
Instance details

Defined in Vary.VEither

Methods

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

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

Monad (VEither errs) Source # 
Instance details

Defined in Vary.VEither

Methods

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

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

return :: a -> VEither errs a #

Semigroup (VEither errs a) Source # 
Instance details

Defined in Vary.VEither

Methods

(<>) :: VEither errs a -> VEither errs a -> VEither errs a #

sconcat :: NonEmpty (VEither errs a) -> VEither errs a #

stimes :: Integral b => b -> VEither errs a -> VEither errs a #

Generic (VEither errs a) Source # 
Instance details

Defined in Vary.VEither

Associated Types

type Rep (VEither errs a) :: Type -> Type #

Methods

from :: VEither errs a -> Rep (VEither errs a) x #

to :: Rep (VEither errs a) x -> VEither errs a #

(Show a, Show (Vary errs)) => Show (VEither errs a) Source # 
Instance details

Defined in Vary.VEither

Methods

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

show :: VEither errs a -> String #

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

(NFData a, NFData (Vary errs)) => NFData (VEither errs a) Source # 
Instance details

Defined in Vary.VEither

Methods

rnf :: VEither errs a -> () #

(Eq a, Eq (Vary errs)) => Eq (VEither errs a) Source # 
Instance details

Defined in Vary.VEither

Methods

(==) :: VEither errs a -> VEither errs a -> Bool #

(/=) :: VEither errs a -> VEither errs a -> Bool #

(Ord a, Ord (Vary errs)) => Ord (VEither errs a) Source # 
Instance details

Defined in Vary.VEither

Methods

compare :: VEither errs a -> VEither errs a -> Ordering #

(<) :: VEither errs a -> VEither errs a -> Bool #

(<=) :: VEither errs a -> VEither errs a -> Bool #

(>) :: VEither errs a -> VEither errs a -> Bool #

(>=) :: VEither errs a -> VEither errs a -> Bool #

max :: VEither errs a -> VEither errs a -> VEither errs a #

min :: VEither errs a -> VEither errs a -> VEither errs a #

type Rep (VEither errs a) Source # 
Instance details

Defined in Vary.VEither

Conversion

toVary :: VEither errs a -> Vary (a : errs) Source #

Turns the VEither into a normal Vary, no longer considering the a a 'preferred' value.

fromVary :: Vary (a : errs) -> VEither errs a Source #

Turns a Vary into a VEither. Now the a is considered the 'preferred' value.

fromLeft :: forall err errs a. err :| errs => err -> VEither errs a Source #

Shorthand to construct a VEither from a single error value.

Instead of:

>>> (VLeft (Vary.from @Bool True)) :: VEither '[Bool] String
VLeft (Vary.from @Bool True) 

You can just write:

>>> VEither.fromLeft @Bool True :: VEither '[Bool] String
VLeft (Vary.from @Bool True) 

fromRight :: forall a errs. a -> VEither errs a Source #

Construct a VEither from an a.

Exists for symmetry with fromLeft. Indeed, this is just another name for VRight.

toEither :: VEither errs a -> Either (Vary errs) a Source #

Turns a VEither into a normal Either.

fromEither :: Either (Vary errs) a -> VEither errs a Source #

Turns a normal Either into a VEither.

veither :: (Vary errs -> c) -> (a -> c) -> VEither errs a -> c Source #

Case analysis on a VEither. Similar to either.

See also VEither.mapLeft, VEither.mapLeftOn and VEither.mapRight.

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

If you have a VEither which does not actually contain any errors, you can be sure it always contains an a.

Similar to Vary.intoOnly.

case analysis ("pattern matching"):

Besides the VLeft and VRight patterns, VEither supports a bunch of handy combinator functions, similar to Vary.on and co.

onLeft :: forall err b errs a. (err -> b) -> (VEither errs a -> b) -> VEither (err : errs) a -> b Source #

onRight :: (a -> b) -> (VEither errs a -> b) -> VEither errs a -> b Source #

Transforming

mapLeftOn :: forall x y xs ys a. Mappable x y xs ys => (x -> y) -> VEither xs a -> VEither ys a Source #

Map a function over one of the error values inside the VEither.

Any other VLeft and also VRight are kept untouched.

Similar to Vary.mapOn.

mapLeft :: (Vary xs -> Vary ys) -> VEither xs a -> VEither ys a Source #

Map a function over the VEither if it contains a VLeft, otherwise leave it alone.

See also VEither.mapLeftOn, VEither.mapRight and VEither.veither.

mapRight :: (x -> y) -> VEither errs x -> VEither errs y Source #

Map a function over the VEither if it contains a VRight, otherwise leave it alone.

Exists for symmetry with VEither.mapLeft and VEither.mapLeftOn.

Indeed, it is just another name for fmap.

See also VEither.veither.

morph :: forall ys xs a. Subset (a : xs) (a : ys) => VEither xs a -> VEither ys a Source #

morphed :: forall xs ys a res. Subset (a : xs) (a : ys) => (VEither ys a -> res) -> VEither xs a -> res Source #

Execute a function expecting a larger (or differently-ordered) variant with a smaller (or differently-ordered) variant, by calling morph on it before running the function.