servant-hateoas-0.3.4: HATEOAS extension for servant
Safe HaskellSafe-Inferred
LanguageGHC2021

Servant.Hateoas.Internal.Polyvariadic

Synopsis

IsFunction

type family IsFun f where ... Source #

Type-level function to determine if a Type is a function.

Equations

IsFun (_ -> _) = 'True 
IsFun _ = 'False 

Simple Polyvariadic composition

class b ~ IsFun f => PolyvariadicComp f b where Source #

Class for polyvariadic composition.

This is copied from the package erisco/control-dotdotdot.

Associated Types

type Return f b :: Type Source #

type Replace f r b :: Type Source #

Methods

pcomp :: (Return f b -> r) -> f -> Replace f r b Source #

pcomp f g has g consume all arguments and then has f consume the result of g.

Instances

Instances details
'False ~ IsFun a => PolyvariadicComp a 'False Source # 
Instance details

Defined in Servant.Hateoas.Internal.Polyvariadic

Associated Types

type Return a 'False Source #

type Replace a r 'False Source #

Methods

pcomp :: (Return a 'False -> r) -> a -> Replace a r 'False Source #

PolyvariadicComp b (IsFun b) => PolyvariadicComp (a -> b) 'True Source # 
Instance details

Defined in Servant.Hateoas.Internal.Polyvariadic

Associated Types

type Return (a -> b) 'True Source #

type Replace (a -> b) r 'True Source #

Methods

pcomp :: (Return (a -> b) 'True -> r) -> (a -> b) -> Replace (a -> b) r 'True Source #

(...) :: (PolyvariadicComp f b, IsFun f ~ b) => (Return f b -> r) -> f -> Replace f r b infixr 9 Source #

Infix for pcomp.

Polyvariadic composition with two functions

class (b ~ IsFun f, b ~ IsFun g) => PolyvariadicComp2 f g b where Source #

Like PolyvariadicComp but allows to consume all arguments twice, by two functions with the exact same arguments but potentially different return types.

Associated Types

type Return2 f g b :: Type Source #

type Replace2 f g r b :: Type Source #

Methods

pcomp2 :: (Return2 f g b -> r) -> f -> g -> Replace2 f g r b Source #

pcomp2 f g h has each g and h consume all arguments and then has f consume the result of g and h.

This is highly similar to (&&&) from Arrow but for polyvariadic composition.

Instances

Instances details
('False ~ IsFun a, IsFun b ~ 'False) => PolyvariadicComp2 a b 'False Source # 
Instance details

Defined in Servant.Hateoas.Internal.Polyvariadic

Associated Types

type Return2 a b 'False Source #

type Replace2 a b r 'False Source #

Methods

pcomp2 :: (Return2 a b 'False -> r) -> a -> b -> Replace2 a b r 'False Source #

(IsFun b ~ IsFun c, PolyvariadicComp2 b c (IsFun b)) => PolyvariadicComp2 (a -> b) (a -> c) 'True Source # 
Instance details

Defined in Servant.Hateoas.Internal.Polyvariadic

Associated Types

type Return2 (a -> b) (a -> c) 'True Source #

type Replace2 (a -> b) (a -> c) r 'True Source #

Methods

pcomp2 :: (Return2 (a -> b) (a -> c) 'True -> r) -> (a -> b) -> (a -> c) -> Replace2 (a -> b) (a -> c) r 'True Source #