linnet-0.4.0.1: Lightweight library for building HTTP API

Safe HaskellSafe
LanguageHaskell2010

Linnet.Internal.Coproduct

Synopsis

Documentation

data Coproduct a b where Source #

Constructors

Inl :: a -> Coproduct a b 
Inr :: b -> Coproduct a b 
Instances
(Eq a, Eq b) => Eq (Coproduct a b) Source # 
Instance details

Defined in Linnet.Internal.Coproduct

Methods

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

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

(Negotiable ct a, Negotiable ct SomeException, Negotiable ct (), Compile cts m (HList es), MonadCatch m) => Compile (ct :+: cts) m (HList (Endpoint m a ': es)) Source # 
Instance details

Defined in Linnet.Compile

Methods

compile :: HList (Endpoint m a ': es) -> Compiled m Source #

compileWithContext :: HList (Endpoint m a ': es) -> CompileContext -> Compiled m Source #

type (:+:) a b = Coproduct a b infixr 9 Source #

Type operator for Coproduct type

data CNil Source #

Instances
Eq CNil Source # 
Instance details

Defined in Linnet.Internal.Coproduct

Methods

(==) :: CNil -> CNil -> Bool #

(/=) :: CNil -> CNil -> Bool #

Monad m => Compile CNil m (HList ([] :: [Type])) Source # 
Instance details

Defined in Linnet.Compile

Methods

compile :: HList [] -> Compiled m Source #

compileWithContext :: HList [] -> CompileContext -> Compiled m Source #

class AdjoinCoproduct cs c | cs -> c where Source #

Flatten nested coproduct

Methods

adjoinCoproduct :: cs -> c Source #

Instances
AdjoinCoproduct' (AdjoinCoproductT cs) cs c => AdjoinCoproduct cs c Source # 
Instance details

Defined in Linnet.Internal.Coproduct

Methods

adjoinCoproduct :: cs -> c Source #