[Haskell-cafe] problem with servant and type constrains

Roel van Dijk vandijk.roel at gmail.com
Thu Oct 17 13:54:18 UTC 2019


You could try and enable the {-# ScopedTypeVariables #-} language extension
[1].

Then you can write an explicit forall so that the type variable a scopes
over the where clause:

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

You could also do this without the language extension by explicitly passing
the type variable via some proxy, but I recommend using the
ScopedTypeVariables language extension.

1 -
https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#lexically-scoped-type-variables

Op wo 16 okt. 2019 om 21:40 schreef PICCA Frederic-Emmanuel <
frederic-emmanuel.picca at synchrotron-soleil.fr>:

> 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
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20191017/8b418608/attachment.html>


More information about the Haskell-Cafe mailing list