Network.HTTP.Req https vs http type confusion

Hey everyone,

I’m playing around with Network.HTTP.Req as an http/https client library to make some requests to a local REST API. I can’t seem to wrap my head around the typing/implementation of the Scheme/Url types. I would just like to be able to let the end user choose between http and https at runtime without duplicating much code. Here’s a concrete example:

    r <-
      if secure then
        req
          GET (https host /: "rest" /: "db" /: "status")
          NoReqBody
          jsonResponse
          $ port port'
            <> header "X-API-Key" apiKey
            <> "folder" =: folder
      else
        req
          GET (http host /: "rest" /: "db" /: "status")
          NoReqBody
          jsonResponse
          $ port port'
            <> header "X-API-Key" apiKey
            <> "folder" =: folder

What I would like to do is determine if the secure bool value is set in advance and only have the rest of the request code typed out once, i.e. something like this:

 let scheme' = if secure then https else http
 r <-
        req
          GET (scheme' host /: "rest" /: "db" /: "status")
          NoReqBody
          jsonResponse
          $ port port'
            <> header "X-API-Key" apiKey
            <> "folder" =: folder

Due to my unfamiliarity with the strange typing of the Url/Scheme types I can’t figure out how to make that happen. I get these errors:

  • Couldn't match type ‘'Http’ with ‘'Https’
     Expected: Text -> Url 'Https
       Actual: Text -> Url 'Http
   • In the expression: http
     In the expression: if secure then https else http
     In an equation for ‘scheme'’: scheme' = if secure then https else http [-Wdeferred-type-errors]

Url: https://hackage.haskell.org/package/req-3.13.2/docs/src/Network.HTTP.Req.html#Url

Scheme: https://hackage.haskell.org/package/req-3.13.2/docs/src/Network.HTTP.Req.html#Scheme

data Url (scheme :: Scheme) = Url Scheme (NonEmpty Text)
  -- NOTE The second value is the path segments in reversed order.
  deriving (Eq, Ord, Show, Data, Typeable, Generic)

type role Url nominal

instance (Typeable scheme) => TH.Lift (Url scheme) where
...
data Scheme
  = -- | HTTP
    Http
  | -- | HTTPS
    Https
  deriving (Eq, Ord, Show, Data, Typeable, Generic, TH.Lift)

It seems like it has to do with the TH/Lift’ing implementation, but I can’t understand it. Can anyone enlighten me on what’s happening and/or a decent solution for what I’m trying to do?

It’s not a TH/Lift thing, it’s a DataKinds thing. The library uses DataKinds to promote the type Scheme = Http | Https into a new kind Scheme with types 'Https :: Scheme and 'Http :: Scheme

so http :: Text -> Url 'Http and https :: Text -> Url 'Https are different types. Noting that the requests functions in Network.Http.Req don’t seem to need typeclass instances on the scheme type variable, we can wrap them all up with an existential and not worry about having to capture any typeclass information. The most common way to do this is to use package some:

data Some f where
  Some :: f a -> Some f

When you pattern-match on the Some, you will have a Url a but no idea what a is. That’s enough for our purposes, and we can write a variant of req which accepts a Some Url:

someReq ::
  (MonadHttp m, HttpMethod method, HttpBody body, HttpResponse response, HttpBodyAllowed (AllowsBody method) (ProvidesBody body)) =>
  method ->
  Some Url ->
  body ->
  Proxy response ->
  (forall scheme. Option scheme) ->
  m response
someReq method (Some url) body response option =
  req method url body response option

Note the use of forall scheme. Option scheme as an argument (you may need {-# LANGUAGE RankNTypes #-}). If we omit it, we get a type error (try it): when we pattern-match the Some to get our url :: Url a, we don’t know what a is, and in particular we don’t know whether it’s the same as scheme. In the version with forall, we accept a polymorphic argument, and can choose the type of scheme to match a.

None of the options you use in your example require any particular scheme, so you should be able to pass them in for the option parameter.

Good luck.

4 Likes

Thank you for the detailed reply!

This will take some time to digest since there are several new concepts for me, but it seems like a great learning opportunity.

I had the exact same issue with req long time ago, and for what it’s worth I fixed the error you get like this: https://github.com/TristanCacqueray/haskell-playground/blob/06a02378fa4300a2effa683769e2fd65db020939/req/hcurl.hs#L56-L61

But using forall scheme sounds like a better solution.

That seems like a decent way to solve it. Thanks for sharing.

The DataKinds, type promotion, and RankNTypes is hurting my brain at the moment.

Only if you don’t have to set scheme-specific options. Then you might need to pack the Option scheme into the Some with a type like:

-- Or use Data.Functor.Product or (:*:)
data UrlAndOption scheme = UrlAndOptions (Url scheme) (Option scheme)

Then, when you unpack the Some, GHC still won’t know what type it had, but it will know that it’s the same for the Url and the Option.