[Haskell-cafe] ambiguous constraint errors

Isaac Dupree isaacdupree at charter.net
Thu May 29 07:14:05 EDT 2008


Evan Laforge wrote:
> I have two related questions:
> 
> #1
> 
> I'm getting some annoying type errors that I don't fully understand,
> and wind up having to do a workaround that I don't totally like.
> Here's a simplified version of my situation:
> 
> data Ambi m = Ambi {
>     ambi_monad :: m Int
>     , ambi_int :: Int
>     }
> 
> some_ambi :: Monad m => Ambi m
> some_ambi = Ambi (return 5) 10
> 
> ambi_table :: Monad m => [(String, Ambi m)]
> ambi_table = [("default", some_ambi)]
> 
> get_int :: String -> Maybe Int
> get_int sym = fmap ambi_int (lookup sym ambi_table)
> 
> -----------
> 
> get_int produces:
>     Ambiguous type variable `m' in the constraint:
>       `Monad m' arising from a use of `ambi_table' at ambi.hs:13:40-49
> 
> So I guess this means I'm not telling it which 'm', so it doesn't know
> how to resolve the 'return'... but the thing is, I'm not even using
> that value, so it doesn't matter what it resolves to.  So it works if
> I pick some random monad:
> 
> get_int sym = fmap ambi_int (lookup sym ambi_table :: Maybe (Ambi Maybe))
> 
> Note that I can't leave it as 'Monad m => Ambi m' because I still get
> an ambiguous type variable complaint.
> 
> I'm a little disconcerted by having to pick some random dummy monad.
> Even worse, everything this type touches starts requiring explicit
> type declarations everywhere.  Is there some easier way to do this?
> 
> #2
> 
> This is somewhat related to another issue I've been having, which is
> that I have some kind of complicated type, e.g. '(SomeMonad some,
> Monad m) => some (SomethingM m Status)' that I use in a lot of places.
>  It would be a lot less typing and easier to modify later if I wrote a
> type alias:
> 
> type Command = (Monad some, Monad m) => some (State.StateT () m Status)
> 
> but of course, this isn't allowed, since the type variables don't
> appear on the lhs, and if I put a context there, it's a syntax error.

-fglasgow-exts (not sure which extension) allows the above, though I'm 
not quite sure what it *means*.  It also allows
type Command some m = (Monad some, Monad m) => some (State.StateT () m 
Status)
which allows the polymorphism in the types to be shared across more of 
the function that's defined using Command: more opportunity for 
explicitness.

> While I can write it with data:
> 
> data (Monad some, Monad m) => Command some m = Command (some
> (State.StateT () m Status))
> 
> I've been told this doesn't mean what I expect it to, which is that
> the context constraints propagate up to and unify with the containing
> type (out of curiosity, since it's accepted, what *does* this do?  I
> think I read it somewhere once, but now I forget and can't find it).
> And sure enough, using this type doesn't make my type declarations
> have the right contexts.
That Haskell-98 syntax only tells the compiler to break some times when 
the context isn't met.  But you want the compiler to not-break at other 
times by supplying the information about the context being available 
when something else requires it.

with {-# LANGUAGE GADTs #-} you should be able to use a different syntax 
for the same sort of thing but with the meaning you wanted:  (beware of 
layout messed up by e-mail line wrapping) :
data Command some m where
   Command :: (Monad some, Monad m) => some (State.StateT () m Status) 
-> Command some m

This might be a better choice than the type synonym actually, since it's 
in some ways less unpredictable in meaning to the type system (well, 
again assuming that GHC is the only Haskell implementation that matters 
to you).

> So the first problem means that I have to declare types in various
> inconvenient places, and the second one means that I have to type out
> all the various class constraints (I can still alias away the
> non-polymorphic bits), and all my type declarations start looking much
> more complicated than they are.

It's a really annoying problem!  The multi-param-type-class hack Daniil 
Elovkov mentioned is another way it's done sometimes, that also uses a 
few compiler extensions.  CPP macros are even uglier but they can work 
too.  Choose whatever suits you best.  None of the solutions that make 
polymorphism more syntactically convenient will get rid of your 
ambiguity annoyances, and I'm not sure if the Haskell98 default()ing 
system is willing to default Monads.

-Isaac


More information about the Haskell-Cafe mailing list