servant-zeppelin-client-0.1.0.0: Client library for servant-zeppelin combinators.

Safe HaskellNone
LanguageHaskell2010

Servant.Zeppelin.Client

Contents

Synopsis

Documentation

projectDependency :: forall fs m. ProjectDependency bs b => DependencyList m bs fs -> b Source #

newtype DepClient ix f Source #

DependentClient is a wrapper around a dependently typed function that when given a singleton STrue has return type SideLoaded a deps, and when given SFalse has return type a. For example:

data Person =
  Person { personId   :: PersonId
         , personName :: String
         } deriving (Eq, Show, Generic)

instance FromJSON Person

data Photo =
  Photo { photoId      :: PhotoId
        , photoCaption :: String
        , artistId     :: PersonId
        } deriving (Eq, Show, Generic)

instance FromJSON Photo

data Album =
  Album { albumId     :: AlbumId
        , albumName   :: String
        , albumOwner  :: PersonId
        , albumPhotos :: [PhotoId]
        } deriving (Eq, Show, Generic)

instance FromJSON Album

type API = "albums" :> Capture "albumId" AlbumId
                    :> Get '[JSON, PlainText] Album
                    :> SideLoad '[Person, [Photo]]

type AlbumDeps =  '[Person, [Photo]]

getAlbumClientFull :: Manager
                   -> BaseUrl
                   -> AlbumId
                   -> IO (Either ServantError (SideLoaded Album AlbumDeps))
getAlbumClientFull m burl aid =
  flip runClientM (ClientEnv m burl) $
    runDepClient (client api aid) STrue

getAlbumClient :: Manager
               -> BaseUrl
               -> AlbumId
               -> IO (Either ServantError Album)
getAlbumClient m burl aid =
  flip runClientM (ClientEnv m burl) $
    runDepClient (client api aid) SFalse

Constructors

DepClient 

Fields

Re-exports

data SideLoaded a deps :: * -> [*] -> * #

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) 

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) 

Methods

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

show :: SideLoaded a deps -> String #

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

data SideLoad fs :: [*] -> * #

Combinator to indicate the availablity of side loaded data.

"albums" :> Get '[JSON] Album :> SideLoad '[Person, [Photo]]

Instances

type Client * ((:>) * * (Verb * k1 method status cts a) (SideLoad deps)) # 
type Client * ((:>) * * (Verb * k1 method status cts a) (SideLoad deps))

type SBool = Sing Bool #

Orphan instances

(MimeUnrender * JSON a, MimeUnrender * JSON (SideLoaded a deps), ReflectMethod k1 method) => HasClient * ((:>) * * (Verb * k1 method status cts a) (SideLoad deps)) Source # 

Associated Types

type Client ((:>) * * (Verb * k1 method status cts a) (SideLoad deps)) (api :: (:>) * * (Verb * k1 method status cts a) (SideLoad deps)) :: * #

Methods

clientWithRoute :: Proxy ((* :> *) (Verb * k1 method status cts a) (SideLoad deps)) api -> Req -> Client ((* :> *) (Verb * k1 method status cts a) (SideLoad deps)) api #

(FromJSON (DependencyList Identity ds ds), FromJSON a) => FromJSON (SideLoaded a ds) Source # 
(FromJSON (DependencyList Identity ds ds), KnownSymbol (NamedDependency d), FromJSON d) => FromJSON (DependencyList Identity ((:) * d ds) ((:) * d ds)) Source # 

Methods

parseJSON :: Value -> Parser (DependencyList Identity ((* ': d) ds) ((* ': d) ds)) #

parseJSONList :: Value -> Parser [DependencyList Identity ((* ': d) ds) ((* ': d) ds)] #

FromJSON (DependencyList Identity ([] *) ([] *)) Source #