"Non type-variable argument" if I don't add a type annotation

I have this code:

drawIdentifiersPanel :: StateT AppState IO ()
drawIdentifiersPanel = do

  ...

  let 
    drawSel sel = do
      appState' <- get 
      let maybeValues = Map.lookup sel ( appState' ^. #appData . #allIdentifiers )
      case maybeValues of
        Nothing -> return ()
        Just values -> do
          let indexedValues = zip [ 0.. ] values
              toRun = map ( $ sel ) $ map drawValue indexedValues
          ( liftIO $ execStateT ( sequence_ toRun ) appState' ) >>= put 

  maybe ( return () ) drawSel ( appState' ^. #identifierTypeSel )

  ...

The compiler gives:

horrelate> /home/user/Projects/horrelate/src/IdentifiersPanel.hs:51:5: error:
horrelate>     • Non type-variable argument
horrelate>         in the constraint: MonadState AppState m
horrelate>       (Use FlexibleContexts to permit this)
horrelate>     • When checking the inferred type
horrelate>         drawSel :: forall (m :: * -> *).
horrelate>                    (MonadState AppState m, MonadIO m) =>
horrelate>                    String -> m ()
horrelate>       In the expression:
horrelate>         do appState <- get
horrelate>            liftIO $ Utils.setCursorPos' (appState & cursorPosRef) panelPos
horrelate>            liftIO
horrelate>              $ newIORef panelSize
horrelate>                  >>= DearImGui.beginChildOfSize "All Identifiers"
horrelate>            let comboActiveStr
horrelate>                  = fromMaybe "<No identifier type selected>"
horrelate>                      $ appState ^. #identifierTypeSel
horrelate>            ....
horrelate>       In an equation for ‘drawIdentifiersPanel’:
horrelate>           drawIdentifiersPanel
horrelate>             = do appState <- get
horrelate>                  liftIO $ Utils.setCursorPos' (appState & cursorPosRef) panelPos
horrelate>                  liftIO
horrelate>                    $ newIORef panelSize
horrelate>                        >>= DearImGui.beginChildOfSize "All Identifiers"
horrelate>                  ....
horrelate>    |
horrelate> 51 |     drawSel sel = do
horrelate>    |     ^^^^^^^^^^^^^^^^...
horrelate> 

But if I add a type signature:

  let
    drawSel :: String -> StateT AppState IO ()
    drawSel sel = do

It compiles fine. I wonder why is that?

The compiler infers a more general type than your annotation. Instead of just the IO monad your code works for any MonadIO m, so that is inferred. But then it also has the constraint MonadState AppState m which contains a non-type variable argument AppState. As suggested by the compiler you can also easily fix this by enabling the FlexibleContexts language extension.

For drawSel to run, its return type has to be StateT AppState IO (), given that it’s running in drawIdentifiersPanel :: StateT AppState IO (), right?

So I don’t understand how compiler infers its type to be
(MonadState AppState m, MonadIO m) => String -> m (),
Which can cover a return type of
MaybeT ( StateT AppState IO ) (),
ListT ( StateT AppState IO ) (),
and so on.

The compiler only uses the definition of a function to determine its type, not the context in which it is called. In general there could be many places where a function is called and it is not feasible to always use the context to determine the type. And sometimes functions are exported which means they could be used in places that the compiler does not have access to. I guess in local definitions the compiler could perhaps do some more work, but I believe that is not how it works right now.

Interesting, that is fairly insightful.

Regarding the language extension, it’s quite odd to me that the compiler doesn’t allow non-type variable in a constraint. If FlexibleContexts permits that, then it’ll probably solve this compilation. But I’ve heard that using language extension comes with some cost. In this case I found this GitLab wiki which listed its pros and cons at the end, and this StackOverflow post. Both look a little beyond me right now.

So I guess for this kind of error, it’s best to avoid turning on FlexibleContexts, and try to solve it by giving a type signature?

FlexibleContexts is a popular and common extension. I think a good recent resource for this is the GHC2021 proposal. You can see in the big table at the end that the members of the GHC steering committee (the two-letter abbreviations in the top row) unanimously voted to include FlexibleContexts and 29% of Haskell users want it to be included (popularity) and it is used in 29% of actual packages on Hackage (proliferation). (29% might not look like a lot, but it is not like the rest is against it)

The pros and cons on the GitLab wiki are mostly about the implementation in GHC, but that already exists, so they don’t really apply to you as a user. The stackoverflow post is mainly about how turning the extension on does not always solve all your problems. That is a fair point, but not a reason to avoid using it.

TL;DR: just enable the extension

Oh that is very interesting, thank you for showing those!

I guess turning it on should be okay.