| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Servant.Zeppelin.Internal.Types
- data DependencyList :: (* -> *) -> [*] -> [*] -> * where
- NilDeps :: DependencyList m '[] '[]
- (:&:) :: b -> DependencyList m bs fs -> DependencyList m (b ': bs) (f ': fs)
- type family NamedDependency a :: Symbol
- data SideLoaded a deps = SideLoaded a (DependencyList Identity deps deps)
- class Inflatable m base where
- class AllSatisfy bs (Inflatable' m) => HasDependencies m a bs | a -> bs, bs -> m where
- type family AllSatisfy (subjects :: [k]) (test :: k ~> Constraint) :: Constraint where ...
- data Inflatable' :: m -> base ~> Constraint
- data Full' :: m -> base ~> *
Documentation
data DependencyList :: (* -> *) -> [*] -> [*] -> * where Source #
DependencyList m bs fs is a type representing a heterogeneous list parameterized
by bs , which can be transformed into a hetergeneous list of type fs in the context
provided by m.
Constructors
| NilDeps :: DependencyList m '[] '[] | |
| (:&:) :: b -> DependencyList m bs fs -> DependencyList m (b ': bs) (f ': fs) infixr 5 |
Instances
| AllSatisfy * bs (Eq' *) => Eq (DependencyList m bs fs) Source # | |
| AllSatisfy * bs (Show' *) => Show (DependencyList m bs fs) Source # | |
type family NamedDependency a :: Symbol Source #
Labels for the objects created in the dependency mapping. Necessary for JSON instances.
type instance NamedDependency Person = "person" type instance NamedDependency [Photo] = "photos"
data SideLoaded a deps Source #
SideLoaded a deps represents a type a with an hlist of its inflated dependencies.
Constructors
| SideLoaded a (DependencyList Identity deps deps) |
Instances
| (Eq a, Eq (DependencyList Identity deps deps)) => Eq (SideLoaded a deps) Source # | |
| (Show a, Show (DependencyList Identity deps deps)) => Show (SideLoaded a deps) Source # | |
class Inflatable m base where Source #
Inflatable represents a type b which can be expanded inside of a context m.
type PGMonad = ReaderT Connection (ExceptT QueryError IO) instance Inflatable PGMonad PersonId where type Full PGMonad PersonId = Person inflator = getPersonById
Minimal complete definition
Instances
| Inflatable Identity base Source # | Anything can be expanded into itself in the trivial context. |
class AllSatisfy bs (Inflatable' m) => HasDependencies m a bs | a -> bs, bs -> m where Source #
Indicate that a type has dependencies, and supply the uninflated values.
data Album =
Album { albumId :: AlbumId
, albumArtist :: PersonId
, albumPhotos :: [PhotoId]
, albumTitle :: Text
}
instance HasDependencies PGMonad Album '[Person, [PhotoId]] where
getDependencies album = albumArtist album :&: albumPhotos album :&: NilDepsMinimal complete definition
Methods
getDependencies :: a -> DependencyList m bs (Map (Full' m) bs) Source #
type family AllSatisfy (subjects :: [k]) (test :: k ~> Constraint) :: Constraint where ... Source #
All subjects must satisfy the test constraint.
Equations
| AllSatisfy '[] test = () | |
| AllSatisfy (subj ': rest) test = (Apply test subj, AllSatisfy rest test) |
data Inflatable' :: m -> base ~> Constraint Source #
Parially applied Inflatable constraint.
Instances
| type Apply * Constraint (Inflatable' * (* -> *) m) base Source # | |