minion-0.1.0.1: A Haskell introspectable web router
Safe HaskellSafe-Inferred
LanguageHaskell2010

Web.Minion.Args.Internal

Synopsis

Documentation

data (a :: Type) :+ (b :: Type) infixl 9 Source #

Instances

Instances details
(Show (RHList as), Show a) => Show (RHList (as :+ a)) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

showsPrec :: Int -> RHList (as :+ a) -> ShowS #

show :: RHList (as :+ a) -> String #

showList :: [RHList (as :+ a)] -> ShowS #

RHListToHList as => RHListToHList (as :+ a) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type HListTypes (as :+ a) :: [Type] Source #

Methods

revHListToList :: RHList (as :+ a) -> HList (HListTypes (as :+ a)) Source #

type HListTypes (as :+ a) Source # 
Instance details

Defined in Web.Minion.Args.Internal

type HListTypes (as :+ a) = a ': HListTypes as

data HList ts where Source #

Constructors

HNil :: HList '[] 
(:#) :: t -> HList ts -> HList (t ': ts) infixr 1 

Instances

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

Defined in Web.Minion.Args.Internal

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 Web.Minion.Args.Internal

Methods

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

show :: HList '[] -> String #

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

data RHList ts where Source #

Reversed HList

Constructors

RHNil :: RHList Void 
(:#!) :: t -> RHList ts -> RHList (ts :+ t) infixr 1 

Instances

Instances details
Show (RHList Void) Source # 
Instance details

Defined in Web.Minion.Args.Internal

(Show (RHList as), Show a) => Show (RHList (as :+ a)) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

showsPrec :: Int -> RHList (as :+ a) -> ShowS #

show :: RHList (as :+ a) -> String #

showList :: [RHList (as :+ a)] -> ShowS #

type family MapElem ts t t' where ... Source #

Equations

MapElem (ts :+ t) t t' = ts :+ t' 
MapElem (ts :+ x) t t' = MapElem ts t t' :+ x 
MapElem Void t t' = Void 

type family RevToList ts where ... Source #

Equations

RevToList Void = '[] 
RevToList (as :+ a) = a ': RevToList as 

class RHListToHList (ts :: Type) where Source #

Associated Types

type HListTypes ts :: [Type] Source #

Instances

Instances details
RHListToHList Void Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type HListTypes Void :: [Type] Source #

RHListToHList as => RHListToHList (as :+ a) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type HListTypes (as :+ a) :: [Type] Source #

Methods

revHListToList :: RHList (as :+ a) -> HList (HListTypes (as :+ a)) Source #

class GetByType t ts where Source #

Methods

getByType :: HList ts -> t Source #

Instances

Instances details
GetByType t (t ': ts) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

getByType :: HList (t ': ts) -> t Source #

GetByType t ts => GetByType t (x ': ts) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

getByType :: HList (x ': ts) -> t Source #

class Reverse' (l1 :: [Type]) (l2 :: [Type]) (l3 :: [Type]) | l1 l2 -> l3 where Source #

Methods

reverse' :: HList l1 -> HList l2 -> HList l3 Source #

Instances

Instances details
Reverse' ('[] :: [Type]) l2 l2 Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

reverse' :: HList '[] -> HList l2 -> HList l2 Source #

Reverse' l (x ': l') z => Reverse' (x ': l) l' z Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

reverse' :: HList (x ': l) -> HList l' -> HList z Source #

class Reverse xs sx | xs -> sx, sx -> xs where Source #

Methods

reverseHList :: HList xs -> HList sx Source #

Instances

Instances details
(Reverse' xs ('[] :: [Type]) sx, Reverse' sx ('[] :: [Type]) xs) => Reverse xs sx Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

reverseHList :: HList xs -> HList sx Source #

data Lenient e Source #

Instances

Instances details
IsLenient (Lenient a :: Type) Source # 
Instance details

Defined in Web.Minion.Args.Internal

data Strict Source #

Instances

Instances details
IsLenient Strict Source # 
Instance details

Defined in Web.Minion.Args.Internal

data Required Source #

Instances

Instances details
IsRequired Required Source # 
Instance details

Defined in Web.Minion.Args.Internal

data Optional Source #

Instances

Instances details
IsRequired Optional Source # 
Instance details

Defined in Web.Minion.Args.Internal

class IsRequired a where Source #

Instances

Instances details
IsRequired Optional Source # 
Instance details

Defined in Web.Minion.Args.Internal

IsRequired Required Source # 
Instance details

Defined in Web.Minion.Args.Internal

class IsLenient a where Source #

Instances

Instances details
IsLenient Strict Source # 
Instance details

Defined in Web.Minion.Args.Internal

IsLenient (Lenient a :: Type) Source # 
Instance details

Defined in Web.Minion.Args.Internal

type family Arg presence parsing a where ... Source #

Equations

Arg Required (Lenient e) a = Either e a 
Arg Required Strict a = a 
Arg Optional (Lenient e) a = Maybe (Either e a) 
Arg Optional Strict a = Maybe a 

newtype WithHeader presence parsing m a Source #

Constructors

WithHeader (m (Arg presence parsing a)) 

Instances

Instances details
Monad m => Hidden m (WithHeader a b m v) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

runHidden :: Hide (WithHeader a b m v) -> m () Source #

RunDelayed as m => RunDelayed (WithHeader required lenient m a ': as) m Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type DelayedArgs (WithHeader required lenient m a ': as) :: [Type] Source #

Methods

runDelayed :: HList (WithHeader required lenient m a ': as) -> m (HList (DelayedArgs (WithHeader required lenient m a ': as))) Source #

type DelayedArgs (WithHeader required lenient m a ': as) Source # 
Instance details

Defined in Web.Minion.Args.Internal

type DelayedArgs (WithHeader required lenient m a ': as) = Arg required lenient a ': DelayedArgs as

newtype WithQueryParam presence parsing m a Source #

Constructors

WithQueryParam (m (Arg presence parsing a)) 

Instances

Instances details
Monad m => Hidden m (WithQueryParam a b m v) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

runHidden :: Hide (WithQueryParam a b m v) -> m () Source #

RunDelayed as m => RunDelayed (WithQueryParam required lenient m a ': as) m Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type DelayedArgs (WithQueryParam required lenient m a ': as) :: [Type] Source #

Methods

runDelayed :: HList (WithQueryParam required lenient m a ': as) -> m (HList (DelayedArgs (WithQueryParam required lenient m a ': as))) Source #

type DelayedArgs (WithQueryParam required lenient m a ': as) Source # 
Instance details

Defined in Web.Minion.Args.Internal

type DelayedArgs (WithQueryParam required lenient m a ': as) = Arg required lenient a ': DelayedArgs as

newtype WithPiece a Source #

Constructors

WithPiece a 

Instances

Instances details
Monad m => Hidden m (WithPiece a) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

runHidden :: Hide (WithPiece a) -> m () Source #

RunDelayed as m => RunDelayed (WithPiece a ': as) m Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type DelayedArgs (WithPiece a ': as) :: [Type] Source #

Methods

runDelayed :: HList (WithPiece a ': as) -> m (HList (DelayedArgs (WithPiece a ': as))) Source #

type DelayedArgs (WithPiece a ': as) Source # 
Instance details

Defined in Web.Minion.Args.Internal

type DelayedArgs (WithPiece a ': as) = a ': DelayedArgs as

newtype WithPieces a Source #

Constructors

WithPieces [a] 

Instances

Instances details
Monad m => Hidden m (WithPieces a) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

runHidden :: Hide (WithPieces a) -> m () Source #

RunDelayed as m => RunDelayed (WithPieces a ': as) m Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type DelayedArgs (WithPieces a ': as) :: [Type] Source #

Methods

runDelayed :: HList (WithPieces a ': as) -> m (HList (DelayedArgs (WithPieces a ': as))) Source #

type DelayedArgs (WithPieces a ': as) Source # 
Instance details

Defined in Web.Minion.Args.Internal

type DelayedArgs (WithPieces a ': as) = [a] ': DelayedArgs as

newtype WithReq m r Source #

Constructors

WithReq (m r) 

Instances

Instances details
Monad m => Hidden m (WithReq m a) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

runHidden :: Hide (WithReq m a) -> m () Source #

(RunDelayed as m, IsRequest r) => RunDelayed (WithReq m r ': as) m Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type DelayedArgs (WithReq m r ': as) :: [Type] Source #

Methods

runDelayed :: HList (WithReq m r ': as) -> m (HList (DelayedArgs (WithReq m r ': as))) Source #

type DelayedArgs (WithReq m r ': as) Source # 
Instance details

Defined in Web.Minion.Args.Internal

type DelayedArgs (WithReq m r ': as) = RequestValue r ': DelayedArgs as

newtype Hide a Source #

Constructors

Hide a 

Instances

Instances details
Hidden m a => Hidden m (Hide a) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

runHidden :: Hide (Hide a) -> m () Source #

(RunDelayed as m, Hidden m a) => RunDelayed (Hide a ': as) m Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type DelayedArgs (Hide a ': as) :: [Type] Source #

Methods

runDelayed :: HList (Hide a ': as) -> m (HList (DelayedArgs (Hide a ': as))) Source #

type DelayedArgs (Hide a ': as) Source # 
Instance details

Defined in Web.Minion.Args.Internal

type DelayedArgs (Hide a ': as) = DelayedArgs as

class Hidden m a where Source #

Methods

runHidden :: Hide a -> m () Source #

Instances

Instances details
Hidden m a => Hidden m (Hide a) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

runHidden :: Hide (Hide a) -> m () Source #

Monad m => Hidden m (WithPiece a) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

runHidden :: Hide (WithPiece a) -> m () Source #

Monad m => Hidden m (WithPieces a) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

runHidden :: Hide (WithPieces a) -> m () Source #

Monad m => Hidden m (WithReq m a) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

runHidden :: Hide (WithReq m a) -> m () Source #

Monad m => Hidden m (WithHeader a b m v) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

runHidden :: Hide (WithHeader a b m v) -> m () Source #

Monad m => Hidden m (WithQueryParam a b m v) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Methods

runHidden :: Hide (WithQueryParam a b m v) -> m () Source #

class FunArgs (ts :: [Type]) where Source #

Associated Types

type ts ~> r :: Type Source #

Methods

apply :: (ts ~> r) -> HList ts -> r Source #

Instances

Instances details
FunArgs ('[] :: [Type]) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type '[] ~> r Source #

Methods

apply :: ('[] ~> r) -> HList '[] -> r Source #

FunArgs as => FunArgs (a ': as) Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type (a ': as) ~> r Source #

Methods

apply :: ((a ': as) ~> r) -> HList (a ': as) -> r Source #

class Monad m => RunDelayed ts m where Source #

Associated Types

type DelayedArgs ts :: [Type] Source #

Methods

runDelayed :: HList ts -> m (HList (DelayedArgs ts)) Source #

Instances

Instances details
Monad m => RunDelayed ('[] :: [Type]) m Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type DelayedArgs '[] :: [Type] Source #

Methods

runDelayed :: HList '[] -> m (HList (DelayedArgs '[])) Source #

(RunDelayed as m, Hidden m a) => RunDelayed (Hide a ': as) m Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type DelayedArgs (Hide a ': as) :: [Type] Source #

Methods

runDelayed :: HList (Hide a ': as) -> m (HList (DelayedArgs (Hide a ': as))) Source #

RunDelayed as m => RunDelayed (WithHeader required lenient m a ': as) m Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type DelayedArgs (WithHeader required lenient m a ': as) :: [Type] Source #

Methods

runDelayed :: HList (WithHeader required lenient m a ': as) -> m (HList (DelayedArgs (WithHeader required lenient m a ': as))) Source #

RunDelayed as m => RunDelayed (WithPiece a ': as) m Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type DelayedArgs (WithPiece a ': as) :: [Type] Source #

Methods

runDelayed :: HList (WithPiece a ': as) -> m (HList (DelayedArgs (WithPiece a ': as))) Source #

RunDelayed as m => RunDelayed (WithPieces a ': as) m Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type DelayedArgs (WithPieces a ': as) :: [Type] Source #

Methods

runDelayed :: HList (WithPieces a ': as) -> m (HList (DelayedArgs (WithPieces a ': as))) Source #

RunDelayed as m => RunDelayed (WithQueryParam required lenient m a ': as) m Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type DelayedArgs (WithQueryParam required lenient m a ': as) :: [Type] Source #

Methods

runDelayed :: HList (WithQueryParam required lenient m a ': as) -> m (HList (DelayedArgs (WithQueryParam required lenient m a ': as))) Source #

(RunDelayed as m, IsRequest r) => RunDelayed (WithReq m r ': as) m Source # 
Instance details

Defined in Web.Minion.Args.Internal

Associated Types

type DelayedArgs (WithReq m r ': as) :: [Type] Source #

Methods

runDelayed :: HList (WithReq m r ': as) -> m (HList (DelayedArgs (WithReq m r ': as))) Source #