Skip to content

Generic + Nested records #1015

Closed
Closed
@mitchellwrosen

Description

@mitchellwrosen

Hello! I'd like some advice on how to write a nested record suitable for a servant servant and client. Is it possible? Here's what I've discovered so far.

Preamble.

{-# LANGUAGE DataKinds, DeriveGeneric, TypeOperators #-}

import Servant
import Servant.API.Generic
import Servant.Client
import Servant.Client.Generic
import Servant.Server.Generic

Outer API type: has a route, plus a nested API type (Inner).

data Outer route = Outer
  { outer :: route :- Get '[JSON] ()
  , inner :: route :- ToServant Inner AsApi
  } deriving Generic

Inner API type with a couple routes.

data Inner route = Inner
  { foo :: route :- Get '[JSON] ()
  , bar :: route :- Get '[JSON] ()
  } deriving Generic

Generating a server works, but note we have to call genericServer on the inner record as well. It would be great to only have to call this once.

outerServer :: ToServant Outer AsServer
outerServer =
  genericServer Outer
    { outer = pure ()
    , inner = genericServer Inner
        { foo = pure ()
        , bar = pure ()
        }
    }

Generating a client does not work so well. I have to match the inner client with :<|>, which means reverse-engineering the nesting that genericClient makes.

callOuter :: ClientM ()
callInnerFoo :: ClientM ()
callInnerBar :: ClientM ()
Outer
  { outer = callOuter
  , inner = callInnerFoo :<|> callInnerBar
  } = genericClient

Unfortunately this nested record type (my first attempt) does not work.

data Outer route = Outer
  { outer :: route :- Get '[JSON] ()
  , inner :: Inner route
  } deriving Generic

With this we can generate a nice server (note: only call to genericServer).

outerServer :: ToServant Outer AsServer
outerServer =
  genericServer Outer
    { outer = pure ()
    , inner = Inner
        { foo = pure ()
        , bar = pure ()
        }
    }

However, I'm unable to call genericClient at this type due to the equality constraints.

callOuter :: ClientM ()
Outer callOuter _ = genericClient
     Couldn't match type Client ClientM (Inner AsApi)
                     with Inner (AsClientT ClientM)
        arising from a use of genericClient
     In the expression: genericClient
      In a pattern binding: Outer callOuter _ = genericClient
   |
64 | Outer callOuter _ = genericClient
   |                     ^^^^^^^^^^^^^

Metadata

Metadata

Assignees

No one assigned

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions