Servant - Type on UVerb list is not recognised when using a type variable

Hi everyone, my first posting here. I am playing around with Servant at the moment and the application employed the following function to retrieve a flashcard from an appropriate storage (a member of type class Storage ExerciseWithMetadata) by its UUID. The list of all exercises is retrieved using readAll, filtered for the id and then turned into a Maybe using safeHead (i.e. listToMaybe).

For a Just value, Status Code 200 is returned with a jsonapi document created from the exercise. If no exercise with the id exists, a 404 error is returned.

ExercisesWithMetadata is an Exercise wrapped with additional information that need not be delivered by the web api.

httpGetExercise ::
  (Storage ExerciseWithMetadata s) =>
  s ->
  UUID ->
  Handler
    ( Union
        '[ WithStatus 200 (Document Exercise),
           WithStatus 404 ()
         ]
    )
httpGetExercise exerciseStore id = liftIO $ do
  maybeExercise <- safeHead . filter ((== id) . view #id) <$> readAll exerciseStore
  case maybeExercise of
    Just ex -> respond (WithStatus @200 $ mkDocument (ex ^. #exercise) Nothing Nothing)
    Nothing -> respond (WithStatus @404 ())

This works very well, but since I will need other kinds of objects as well, a more general approach seemed called for, so I replaced that with the following function:

httpGetItem ::
  forall content preparedContent s.
  (Storage content s) =>
  s ->
  (content -> Bool) ->
  (content -> preparedContent) ->
  Handler
    ( Union
        '[WithStatus 200 (Document preparedContent), WithStatus 404 ()]
    )
httpGetItem itemStore filterProperty prepare = liftIO $ do
  maybeItem <- safeHead . filter filterProperty <$> readAll itemStore
  case maybeItem of
    Just item -> respond (WithStatus @200 $ mkDocument (prepare item) Nothing Nothing)
    Nothing -> respond (WithStatus @404 ())

This is rather straightforward. The Types ExercisesWIthMetada and Exercise have been replaced with variables, the property for the filter is passed as a function and so is a function that extracts the Exercise from an ExercisesWithMetadata. in the original function.

The original function could then be implemented as

httpGetExercise exerciseStore id = httpGetItem exerciseStore ((==id) . view #id) (view #exercise) 

But now the compiler (GHC 9.2.7) denies fealty when it comes to respond:

app/Main.hs:114:18: error:
    • Expected one of:
          '[WithStatus 200 (Document preparedContent), WithStatus 404 ()]
      But got:
          WithStatus 200 (Document preparedContent)
    • In the expression:
        respond
          (WithStatus @200 $ mkDocument (prepare item) Nothing Nothing)

It seems obvious that there is no conceptual error involved here (semantically, the type clearly is in the list) but that I’m being bitten here by technical intricacies of type-level prorgramming. I haven’t found anything useful about the origins of the error and possible remedies so far, so I thought I might ask here.

For the sake of completeness, here are my enabled extensions and imports:

{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGAUGE ScopedTypeVariables #-}

...

import Control.Lens hiding ((.=))
import Control.Monad
import Control.Monad.Except
import Data.Aeson
import Data.ByteString.Lazy.Internal qualified as BS
import Data.Generics.Labels
import Data.IORef
import Data.List (find)
import Data.Maybe
import Data.Text qualified as T
import Data.UUID
import Data.UUID.V4
import GHC.Generics
import Network.JSONApi as JA
import Network.Wai
import Network.Wai.Handler.Warp
import Servant
import Servant.API
1 Like

You can try compiling with -fprint-explicit-kinds. That might show you that the kinds do not match.

1 Like

Apparently, respond doesn’t seem to have very good type inference with “abstract” types: Its basic job is to automatically inject an x into an n-ary sum of types xs where xs contains x:

respond :: (IsMember x xs, ...) => x -> f (Union xs) 

You can always work around this by writing out the injection explicitly, with the knowledge that Union xs is a synonym for NS I xs from sop-core. In your case, you want to inject into the first component, which is realised by Z . I:

Z . I :: x -> Union (x : xs)

Concretely, you can replace respond by pure . Z . I:

import qualified Data.SOP as SOP
...
  case maybeItem of
    Just item -> pure . SOP.Z . SOP.I $ WithStatus @200 $ mkDocument (prepare item) Nothing Nothing

Let me know if sth is unclear or too sketchy.

1 Like

You can also try to give an explicit type signature to your mkDocument call in order to help respond:

    Just item -> respond (WithStatus @200 $ (mkDocument (prepare item) Nothing Nothing) :: Document preparedContent)
1 Like

Thanks for the replies! Rephrasing respond as pure . SOP.Z . SOP.I did the trick. The explicit type signature didn’t help.