serpentine-0.2: Simple project template from stack

Safe HaskellNone
LanguageHaskell2010

Serpentine

Documentation

data IRec :: [*] -> * where Source

Constructors

IRNil :: IRec `[]` 
(:&) :: !r -> !(IRec rs) -> IRec (r : rs) infixr 9 

type StaticStarH a = a Source

type family PiecesNestedTuple ks :: [*] Source

type SPiece k = Sing k Source

class DefPieces t where Source

Methods

defPieces :: SList t Source

Instances

DefPieces ([] (Piece *)) Source 
(DefPieces ps, KnownSymbol s) => DefPieces ((:) (Piece *) (Static * s) ps) Source 
(DefPieces ps, PathPiece t, Typeable * t) => DefPieces ((:) (Piece *) (Capture * t) ps) Source 

sEnumAll :: forall a b. (a ~ EnumFromTo MinBound MaxBound, SBounded b, SEnum b) => SList a Source

mapValue :: forall rs b. (forall r. Sing r -> b) -> SList rs -> [b] Source

data SomeRoutePieces f where Source

Constructors

SomeRoutePieces :: Sing (a :: k) -> Sing (Apply g a) -> IRec (PiecesNestedTuple (Apply g a)) -> SomeRoutePieces g 

Instances

parseAllRoutes :: forall kp f. (SEnum kp, SBounded kp) => Proxy f -> (forall rt. Sing rt -> Sing (Apply f rt)) -> [Text] -> Maybe (SomeRoutePieces f) Source

parseManyRoutes :: forall routes f. Proxy f -> (forall rt. Sing rt -> Sing (Apply f rt)) -> SList routes -> [Text] -> Maybe (SomeRoutePieces f) Source

parseOneRoute :: forall r f. Proxy f -> (forall rt. Sing rt -> Sing (Apply f rt)) -> Sing r -> [Text] -> Maybe (IRec (PiecesNestedTuple (Apply f r))) Source

parseOne :: forall pieces. SList pieces -> [Text] -> Maybe (IRec (PiecesNestedTuple pieces)) Source

render :: forall f route. Proxy f -> (forall r. Sing r -> Sing (Apply f r)) -> Sing route -> IRec (PiecesNestedTuple (Apply f route)) -> [Text] Source

renderExample :: forall f route. Proxy f -> (forall r. Sing r -> Sing (Apply f r)) -> Sing route -> [Text] Source

renderExamplePieces :: forall pieces. SList pieces -> [Text] Source

renderPieces :: forall pieces. SList pieces -> IRec (PiecesNestedTuple pieces) -> [Text] Source

parseCapturePiece :: (PathPiece a, piece ~ Capture a) => SPiece piece -> Text -> Maybe a Source

renderStaticPiece :: forall static s. (static ~ Static s) => SPiece static -> Text Source

renderCapturePieceValue :: (piece ~ Capture a) => SPiece piece -> a -> Text Source

renderCapturePieceType :: forall a piece. (piece ~ Capture a) => SPiece piece -> Text Source