[Haskell-cafe] problem with servant and type constrains

PICCA Frederic-Emmanuel frederic-emmanuel.picca at synchrotron-soleil.fr
Wed Oct 16 19:40:26 UTC 2019


Hello, I have a type for my APi like this

type SubscribeAPI a = "upload" :> ReqBody '[JSON] (JobSpecSub a) :> Post '[JSON] ()
type HomepageAPI = "homepage"  :> QueryParam "id" Int :> Get '[HTML] Homepage
type XdsMeAPI a = "xdsme" :> ReqBody '[FormUrlEncoded] XdsMeRequest :> Post '[JSON] (JobSpecSub a)
type LogsAPI = "logs" :> ReqBody '[FormUrlEncoded] LogsRequest :> Post '[HTML] Html
type ResumXdsAPI = "resumxds" :> ReqBody '[FormUrlEncoded] ResumXdsRequest :> Post '[HTML] Html
type SessionIdAPI = "sessionid" :> ReqBody '[FormUrlEncoded] SessionIdRequest :> Post '[HTML] Html

type MyApi a = SubscribeAPI a :<|> HomepageAPI :<|> XdsMeAPI a :<|> LogsAPI :<|> ResumXdsAPI :<|> SessionIdAPI

myApi :: Job a => Proxy (MyApi a)
myApi = Proxy

When I try to write the handler for this API, I have this error message for the next code

myAPIServer :: Job a => Beamline -> JobQueue a -> Server (MyApi a)
myAPIServer beam jobQueue = handleJobSpec :<|> handleHomepage :<|> handleXdsMe :<|> handleLogs :<|> handleResumXds :<|> handleSessionId
  where
    handleJobSpec :: Job b => JobSpecSub b -> Handler ()
    handleJobSpec jobSpec = liftIO $ enqueue jobSpec jobQueue


    • Couldn't match type ‘a’ with ‘b’
      ‘a’ is a rigid type variable bound by
        the type signature for:
          myAPIServer :: forall a.
                         Job a =>
                         Beamline -> JobQueue a -> Server (MyApi a)
        at src/Web.hs:235:1-66
      ‘b’ is a rigid type variable bound by
        the type signature for:
          handleJobSpec :: forall b. Job b => JobSpecSub b -> Handler ()
        at src/Web.hs:238:5-56
      Expected type: JobQueue b
        Actual type: JobQueue a
    • In the second argument of ‘enqueue’, namely ‘jobQueue’
      In the second argument of ‘($)’, namely ‘enqueue jobSpec jobQueue’
      In the expression: liftIO $ enqueue jobSpec jobQueue
    • Relevant bindings include
        jobSpec :: JobSpecSub b (bound at src/Web.hs:239:19)
        handleJobSpec :: JobSpecSub b -> Handler ()
          (bound at src/Web.hs:239:5)
        jobQueue :: JobQueue a (bound at src/Web.hs:236:18)
        myAPIServer :: Beamline -> JobQueue a -> Server (MyApi a)
          (bound at src/Web.hs:236:1)
    |
239 |     handleJobSpec jobSpec = liftIO $ enqueue jobSpec jobQueue
    |                                                      ^^^^^^^^


I understand that I need to explain haskell that a ~ b.

So my question is how can I do this :)

thanks for your help

Frederic


More information about the Haskell-Cafe mailing list