Trouble with multi-parameter type classes / type applications / scoped type variables

Hello! I’m trying out eff but I think that my issue is not specific to that library.

I am trying to write a memorable password generator as an exercise in working with State and Reader. My state is modeled as a tuple:

type PwGen g = (g, Text)

where g is supposed to be some instance of RandomGen. Here’s an example function that doesn’t compile; it is just a helper function that replaces the current state’s generator with a new one (plus another helper function gets, which I wrote just to prove that I could at least make something work):

gets :: (State s m) => (s -> a) -> m a
gets f = f <$> get

updateGen :: (State (PwGen g) m) => g -> m ()
updateGen g = do
  pw <- gets snd
  put (g, pw)

I didn’t include the RandomGen g constraint in the context of updateGen because I don’t actually use any of those methods. In any event, here’s what GHC says about that:

[1 of 2] Compiling MemorablePassword.Generator

/workspaces/memorable-password-generator/src/MemorablePassword/Generator.hs:24:9: error:
    • Could not deduce (State (a0, b0) m) arising from a use of ‘gets’
      from the context: State (PwGen g) m
        bound by the type signature for:
                   updateGen :: forall g (m :: * -> *). State (PwGen g) m => g -> m ()
        at src/MemorablePassword/Generator.hs:22:1-45
      The type variables ‘a0’, ‘b0’ are ambiguous
      Relevant bindings include
        updateGen :: g -> m ()
          (bound at src/MemorablePassword/Generator.hs:23:1)
      These potential instances exist:
        instance Monad m => State s (StateT s m)
          -- Defined in ‘Control.Effect.State’
        ...plus one instance involving out-of-scope types
        (use -fprint-potential-instances to see them all)
    • In a stmt of a 'do' block: pw <- gets snd
      In the expression:
        do pw <- gets snd
           put (g, pw)
      In an equation for ‘updateGen’:
          updateGen g
            = do pw <- gets snd
                 put (g, pw)
   |
24 |   pw <- gets snd
   |         ^^^^^^^^

/workspaces/memorable-password-generator/src/MemorablePassword/Generator.hs:25:3: error:
    • Could not deduce (State (g, b0) m) arising from a use of ‘put’
      from the context: State (PwGen g) m
        bound by the type signature for:
                   updateGen :: forall g (m :: * -> *). State (PwGen g) m => g -> m ()
        at src/MemorablePassword/Generator.hs:22:1-45
      The type variable ‘b0’ is ambiguous
      Relevant bindings include
        pw :: b0 (bound at src/MemorablePassword/Generator.hs:24:3)
        g :: g (bound at src/MemorablePassword/Generator.hs:23:11)
        updateGen :: g -> m ()
          (bound at src/MemorablePassword/Generator.hs:23:1)
      These potential instances exist:
        instance Monad m => State s (StateT s m)
          -- Defined in ‘Control.Effect.State’
        ...plus one instance involving out-of-scope types
        (use -fprint-potential-instances to see them all)
    • In a stmt of a 'do' block: put (g, pw)
      In the expression:
        do pw <- gets snd
           put (g, pw)
      In an equation for ‘updateGen’:
          updateGen g
            = do pw <- gets snd
                 put (g, pw)
   |
25 |   put (g, pw)
   |   ^^^^^^^^^^^

At first I thought I might need to make a functional dependency m -> g, since presumably the particular monad I use has the generator type built in, but it seems that functional dependencies don’t actually work on top-level functions, just class/instance declarations.

I can tell from this message what is going on—I’m missing something that tells GHC that get has type PwGen g, since all it seems to be able to infer is that it’s a tuple from my use of snd. I haven’t been able to figure out exactly how to actually give it that information though.

My guess is that it has something to do with type applications, since I spotted that being used in the documentation for eff. I’m clearly not doing that right though:

updateGen :: (State (PwGen g) m) => g -> m ()
updateGen g = do
  pw <- gets @(PwGen g) snd
  put (g, pw)

yields

[1 of 2] Compiling MemorablePassword.Generator

/workspaces/memorable-password-generator/src/MemorablePassword/Generator.hs:24:22: error:
    Not in scope: type variable ‘g’
   |
24 |   pw <- gets @(PwGen g) snd
   |

I tried adding RandomGen g as well as forall g. to the context (the latter also needed me to enable ExplicitForAll) but I still got the same error that the type variable g was not in scope.

1 Like

Aha! Upgrading ExplicitForAll to ScopedTypeVariables and updating the type signature like so compiled:

updateGen :: forall g m. (State (PwGen g) m) => g -> m ()
updateGen g = do
  pw <- gets @(PwGen g) snd
  put (g, pw)

Huzzah! But now I have a problem when I actually try to use RandomGen g:

addDigits :: forall g m. (RandomGen g, State (PwGen g) m) => m ()
addDigits = do
  (gen, pw) <- get @(PwGen g)
  let
    (num, gen') = randomR (0, 99) gen
    pw' = format "%s%02d" (pw, num)
  put (gen', pw')

yields

/workspaces/memorable-password-generator/src/MemorablePassword/Generator.hs:25:14: error:
    • Could not deduce (RandomGen g0)
      from the context: (RandomGen g, State (PwGen g) m)
        bound by the type signature for:
                   addDigits :: forall g (m :: * -> *).
                                (RandomGen g, State (PwGen g) m) =>
                                m ()
        at src/MemorablePassword/Generator.hs:25:14-65
      The type variable ‘g0’ is ambiguous
    • In the ambiguity check for ‘addDigits’
      To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
      In the type signature:
        addDigits :: forall g m. (RandomGen g, State (PwGen g) m) => m ()
   |
25 | addDigits :: forall g m. (RandomGen g, State (PwGen g) m) => m ()
   |   

This reminds me of something I was seeing before I added TypeApplications, so probably I need another type application somewhere.

Hey @johnsonwj! It’d be helpful to have a minimal working example self-contained. So that one could just copy-n’paste it into an editor.

I didn’t try it with eff but the following seems to work with mtl. My guess that the trick is, as you guessed above at some point, to have functional dependency in the definition of State. The MonadState class from mtl have one.

{-#LANGUAGE ScopedTypeVariables #-}
{-#LANGUAGE TypeApplications #-}
{-#LANGUAGE FlexibleContexts #-}

import Control.Monad.State.Class hiding (gets)
import System.Random

type PwGen g = (g, String)

gets :: (MonadState s m) => (s -> a) -> m a
gets f = f <$> get

updateGen :: forall g m. (MonadState (PwGen g) m) => g -> m ()
updateGen g = do
  pw <- gets @(PwGen g) snd
  put (g, pw)

addDigits :: forall g m. (RandomGen g, MonadState (PwGen g) m) => m ()
addDigits = do
  (gen, pw) <- get @(PwGen g)
  let
    (num, gen') = randomR @Int @g (0, 99) gen   -- note type applications
    pw' = "dummy" -- format "%s%02d" (pw, num)
  put (gen', pw')

That makes sense - I have been assuming there was some reason there was not an m -> s fundep on the definition of eff's State class.

I tried checking out the repo and adding that myself, and to no one’s surprise, it isn’t free:

src/Control/Effect/State.hs:40:10: error:
    • Illegal instance declaration for ‘State s (EffT t m)’
        The liberal coverage condition fails in class ‘State’
          for functional dependency: ‘m -> s’
        Reason: lhs type ‘EffT t m’ does not determine rhs type ‘s’
        Un-determined variable: s
    • In the instance declaration for ‘State s (EffT t m)’

I’ll have to dig more into how EffT works…or just use mtl like a normal person :stuck_out_tongue:

@artem here is a more minimal working example:

{-# LANGUAGE AllowAmbiguousTypes #-}

module Foo where

import Control.Effect.State
import Control.Effect.Writer
import System.Random

addNum :: forall g m. (RandomGen g, State g m, Writer [Int] m) => m ()
addNum = do
    gen <- get @g
    let (num, gen') = randomR @Int @g (0, 100) gen
    put gen'
    tell [num]

This compiles with AllowAmbiguousTypes (in addition to all of the default extensions enabled by the eff library), but it fails to compile if I remove the pragma or leave out the type applications.

Here’s an equivalent mtl version which requires neither ambiguous types or type applications:

import Control.Monad.State
import Control.Monad.Writer
import System.Random

addNum :: forall g m. (RandomGen g, MonadState g m, MonadWriter [Int] m) => m ()
addNum = do
    gen <- get
    let (num, gen') = randomR (0, 100) gen
    put gen'
    tell [num]

I opened an issue in the eff repo with details about this and my (unsuccessful) attempts to add functional dependencies to that library, or advice about why that is a bad idea / alternative strategies.

1 Like