linnet-0.1.0.2: Lightweight library for building HTTP API

Safe HaskellSafe
LanguageHaskell2010

Linnet.Internal.HList

Documentation

data HList xs where Source #

Constructors

HNil :: HList '[] 
(:::) :: a -> HList as -> HList (a ': as) infixr 6 
Instances
Monad m => Compile CNil m (HList ([] :: [Type])) Source # 
Instance details

Defined in Linnet.Compile

(Eq a, Eq (HList as)) => Eq (HList (a ': as)) Source # 
Instance details

Defined in Linnet.Internal.HList

Methods

(==) :: HList (a ': as) -> HList (a ': as) -> Bool #

(/=) :: HList (a ': as) -> HList (a ': as) -> Bool #

Eq (HList ([] :: [Type])) Source # 
Instance details

Defined in Linnet.Internal.HList

Methods

(==) :: HList [] -> HList [] -> Bool #

(/=) :: HList [] -> HList [] -> Bool #

(Show a, Show (HList as)) => Show (HList (a ': as)) Source # 
Instance details

Defined in Linnet.Internal.HList

Methods

showsPrec :: Int -> HList (a ': as) -> ShowS #

show :: HList (a ': as) -> String #

showList :: [HList (a ': as)] -> ShowS #

Show (HList ([] :: [Type])) Source # 
Instance details

Defined in Linnet.Internal.HList

Methods

showsPrec :: Int -> HList [] -> ShowS #

show :: HList [] -> String #

showList :: [HList []] -> ShowS #

(KnownSymbol ct, ToResponse ct a, ToResponse ct SomeException, Compile cts m (HList es), MonadCatch m) => Compile (Coproduct (Proxy ct) cts) m (HList (Endpoint m a ': es)) Source # 
Instance details

Defined in Linnet.Compile

Methods

compile :: HList (Endpoint m a ': es) -> ReaderT Request m Response Source #

class AdjoinHList ls l | ls -> l where Source #

Methods

adjoin :: HList ls -> HList l Source #

Instances
AdjoinHList' (NeedAdjoin ls) ls l => AdjoinHList ls l Source # 
Instance details

Defined in Linnet.Internal.HList

Methods

adjoin :: HList ls -> HList l Source #

class FnToProduct fn ls out | fn ls -> out, ls out -> fn where Source #

Methods

fromFunction :: fn -> HList ls -> out Source #

Instances
v ~ fn => FnToProduct fn ([] :: [Type]) v Source # 
Instance details

Defined in Linnet.Internal.HList

Methods

fromFunction :: fn -> HList [] -> v Source #

FnToProduct fnOut tail out => FnToProduct (input -> fnOut) (input ': tail) out Source # 
Instance details

Defined in Linnet.Internal.HList

Methods

fromFunction :: (input -> fnOut) -> HList (input ': tail) -> out Source #