| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Servant.API.Flatten
- flatten :: Proxy api -> Proxy (Flat api)
- type Flat api = Reassoc (Flatten api)
- type family Flatten (api :: k) :: k where ...
- type family Redex a b (c :: k) :: * where ...
- type Reassoc api = ReassocBranch api '[]
- type family ReassocBranch (currentAPI :: *) (otherEndpoints :: [*]) where ...
- type family Nths (idxs :: [Nat]) api where ...
- type family Nth (i :: Nat) api where ...
Documentation
flatten :: Proxy api -> Proxy (Flat api) Source #
Flatten (a Proxy to) an API type.
This performs a number of transformations on the API type so as to end up with all combinators distributed over endpoints. For example, the following API type:
type API =Capture"foo"Int:>(Capture"bar"String:>(Get'[JSON]String:<|>ReqBody'[JSON]Int:>Post'[JSON]Int):<|>Get'[JSON]Int):<|>Get'[JSON] [String]
gets transformed into:
Capture"foo"Int:>Capture"bar"String:>Get'[JSON]String:<|>Capture"foo"Int:>Capture"bar"String:>ReqBody'[JSON]Int:>Post'[JSON]Int:<|>Capture"foo"Int:>Get'[JSON]Int:<|>Get'[JSON] [String]
The main point of doing this is to avoid "nested types" for server-side handlers
and client functions. See this cookbook recipe
(particularly the notes on FactoringAPI) for more about "nested types".
To derive "flat" client functions for the API type above, API, you can do:
getfoobar:<|>postfoobar:<|>getfoo:<|>getstrings =client$flatten(Proxy::ProxyAPI)
To serve an implementation for that API with "flat" handler types, you can do:
-- we define all our handlers assuming all the arguments are distributed, -- and declare that this is an implementation forFlat API, notAPI. server :: Server (FlatAPI) server = (foo bar -> return $ show (foo + bar)):<|>(foo bar body -> return $ show (foo + bar - body^2)):<|>(foo -> return (foo * 2)):<|>(return ["hello", "world"]) api ::ProxyAPI api =Proxymain ::IO() main = Network.Wai.Handler.Warp.run 8080 $ serve (flattenapi) server
type Reassoc api = ReassocBranch api '[] Source #
Reassociates :<|> to the right.
type family ReassocBranch (currentAPI :: *) (otherEndpoints :: [*]) where ... Source #
Helper type family that "enumerates" the different endpoints left to right.
Equations
| ReassocBranch (a :<|> b) rest = ReassocBranch a (b ': rest) | |
| ReassocBranch a '[] = a | |
| ReassocBranch a (b ': rest) = a :<|> ReassocBranch b rest |