| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Serpentine.Try
Documentation
Instances
| SingI Crud AddR Source | |
| SingI Crud EditR Source | |
| SingI Crud DeleteR Source | |
| SingI Crud ViewR Source | |
| SingKind Crud (KProxy Crud) Source | |
| SuppressUnusedWarnings (TyFun Crud MyRoute -> *) DogRSym0 Source | |
| SuppressUnusedWarnings (k -> TyFun Crud [Piece k] -> *) (PlanCrudSym1 k) Source | |
| SuppressUnusedWarnings (TyFun k (TyFun Crud [Piece k] -> *) -> *) (PlanCrudSym0 k) Source | |
| data Sing Crud where Source | |
| type Apply MyRoute Crud DogRSym0 l0 = DogRSym1 l0 Source | |
| type DemoteRep Crud (KProxy Crud) = Crud Source | |
| type Apply [Piece k] Crud (PlanCrudSym1 k l1) l0 = PlanCrudSym2 k l1 l0 Source | |
| type Apply (TyFun Crud [Piece k] -> *) k (PlanCrudSym0 k) l0 = PlanCrudSym1 k l0 Source |
Instances
| SingI MyRoute UsersR Source | |
| SingI MyRoute ProfileR Source | |
| SingI MyRoute HomeR Source | |
| SingI Crud n0 => SingI MyRoute (DogR n) Source | |
| SingKind MyRoute (KProxy MyRoute) Source | |
| SuppressUnusedWarnings (TyFun Crud MyRoute -> *) DogRSym0 Source | |
| SuppressUnusedWarnings (TyFun MyRoute [Piece Item] -> *) PlanSym0 Source | |
| data Sing MyRoute where Source | |
| type Apply MyRoute Crud DogRSym0 l0 = DogRSym1 l0 Source | |
| type DemoteRep MyRoute (KProxy MyRoute) = MyRoute Source | |
| type Apply [Piece Item] MyRoute PlanSym0 l0 = PlanSym1 l0 Source |
type ProfileRSym0 = ProfileR Source
type UsersRSym0 = UsersR Source
type DeleteRSym0 = DeleteR Source
Instances
| SingI Item ItemInt Source | |
| SingI Item ItemText Source | |
| SingI Item ItemBool Source | |
| SingKind Item (KProxy Item) Source | |
| SuppressUnusedWarnings (TyFun Item * -> *) ItemTypeSym0 Source | |
| SuppressUnusedWarnings (TyFun MyRoute [Piece Item] -> *) PlanSym0 Source | |
| data Sing Item where Source | |
| type Apply * Item ItemTypeSym0 l0 = ItemTypeSym1 l0 Source | |
| type DemoteRep Item (KProxy Item) = Item Source | |
| type Apply [Piece Item] MyRoute PlanSym0 l0 = PlanSym1 l0 Source |
type ItemBoolSym0 = ItemBool Source
type ItemTextSym0 = ItemText Source
type ItemIntSym0 = ItemInt Source
type family Case_1627460809 n x t Source
Equations
| Case_1627460809 n x AddR = Apply (Apply (:$) (Apply StaticSym0 "add")) `[]` | |
| Case_1627460809 n x EditR = Apply (Apply (:$) (Apply StaticSym0 "edit")) (Apply (Apply (:$) (Apply CaptureSym0 n)) `[]`) | |
| Case_1627460809 n x DeleteR = Apply (Apply (:$) (Apply StaticSym0 "delete")) (Apply (Apply (:$) (Apply CaptureSym0 n)) `[]`) | |
| Case_1627460809 n x ViewR = Apply (Apply (:$) (Apply StaticSym0 "view")) (Apply (Apply (:$) (Apply CaptureSym0 n)) `[]`) |
type family PlanCrud a a :: [Piece n] Source
Equations
| PlanCrud n x = Case_1627460809 n x x |
type PlanCrudSym2 t t = PlanCrud t t Source
data PlanCrudSym1 l l Source
Constructors
| forall arg . (KindOf (Apply (PlanCrudSym1 l) arg) ~ KindOf (PlanCrudSym2 l arg)) => PlanCrudSym1KindInference |
Instances
| SuppressUnusedWarnings (k -> TyFun Crud [Piece k] -> *) (PlanCrudSym1 k) Source | |
| type Apply [Piece k] Crud (PlanCrudSym1 k l1) l0 = PlanCrudSym2 k l1 l0 Source |
data PlanCrudSym0 l Source
Constructors
| forall arg . (KindOf (Apply PlanCrudSym0 arg) ~ KindOf (PlanCrudSym1 arg)) => PlanCrudSym0KindInference |
Instances
| SuppressUnusedWarnings (TyFun k (TyFun Crud [Piece k] -> *) -> *) (PlanCrudSym0 k) Source | |
| type Apply (TyFun Crud [Piece k] -> *) k (PlanCrudSym0 k) l0 = PlanCrudSym1 k l0 Source |
type family Case_1627460817 x t Source
Equations
| Case_1627460817 x UsersR = Apply (Apply (:$) (Apply StaticSym0 "user")) (Apply (Apply (:$) (Apply StaticSym0 "index")) `[]`) | |
| Case_1627460817 x ProfileR = Apply (Apply (:$) (Apply StaticSym0 "profile")) (Apply (Apply (:$) (Apply CaptureSym0 ItemIntSym0)) `[]`) | |
| Case_1627460817 x HomeR = `[]` | |
| Case_1627460817 x (DogR crud) = Apply (Apply (:$) (Apply StaticSym0 "dog")) (Apply (Apply PlanCrudSym0 ItemIntSym0) crud) |
sPlanCrud :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply PlanCrudSym0 t) t :: [Piece n]) Source
type ItemTypeSym1 t = ItemType t Source
data ItemTypeSym0 l Source
Constructors
| forall arg . (KindOf (Apply ItemTypeSym0 arg) ~ KindOf (ItemTypeSym1 arg)) => ItemTypeSym0KindInference |
Instances
| SuppressUnusedWarnings (TyFun Item * -> *) ItemTypeSym0 Source | |
| type Apply * Item ItemTypeSym0 l0 = ItemTypeSym1 l0 Source |
renderAnyItem :: SItem x -> Applied1 ItemTypeSym0 x -> Text Source
renderMyRoute :: SMyRoute x -> Rec (Applied1 ItemTypeSym0) (Captures (Plan x)) -> [Text] Source