servant-zeppelin-0.1.0.2: Types and definitions of servant-zeppelin combinators.

Safe HaskellNone
LanguageHaskell2010

Servant.Zeppelin.Internal.Types

Synopsis

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 # 

Methods

(==) :: DependencyList m bs fs -> DependencyList m bs fs -> Bool #

(/=) :: DependencyList m bs fs -> DependencyList m bs fs -> Bool #

AllSatisfy * bs (Show' *) => Show (DependencyList m bs fs) Source # 

Methods

showsPrec :: Int -> DependencyList m bs fs -> ShowS #

show :: DependencyList m bs fs -> String #

showList :: [DependencyList m bs fs] -> ShowS #

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 # 

Methods

(==) :: SideLoaded a deps -> SideLoaded a deps -> Bool #

(/=) :: SideLoaded a deps -> SideLoaded a deps -> Bool #

(Show a, Show (DependencyList Identity deps deps)) => Show (SideLoaded a deps) Source # 

Methods

showsPrec :: Int -> SideLoaded a deps -> ShowS #

show :: SideLoaded a deps -> String #

showList :: [SideLoaded a deps] -> ShowS #

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

inflator

Associated Types

type Full m base :: * Source #

Methods

inflator :: base -> m (Full m base) Source #

Instances

Inflatable Identity base Source #

Anything can be expanded into itself in the trivial context.

Associated Types

type Full (Identity :: * -> *) base :: * Source #

Methods

inflator :: base -> Identity (Full Identity base) Source #

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 :&: NilDeps

Minimal complete definition

getDependencies

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 # 
type Apply * Constraint (Inflatable' * (* -> *) m) base = Inflatable m base

data Full' :: m -> base ~> * Source #

Defunctionalized Full type family to be used with Map.

Instances

type Apply * * (Full' * (* -> *) m) base Source # 
type Apply * * (Full' * (* -> *) m) base = Full m base