Fixing a type variable inside a function

Andre Pang ozone@algorithm.com.au
Sat, 17 May 2003 00:35:00 +1000


Hi all, I'm having some trouble trying to get a particular function 
working.

Let's say I have a type class, and I have two functions -- fromString 
and toString -- which can convert a string to an instance of that type 
class, and convert an instance of that type class to a string, 
respectively.  e.g.

     module SillyFreeTypeVariables where

     class MyTypeClass c where
	toString :: c -> String
	fromString :: String -> c

     data Instance1 = Instance1
     instance MyTypeClass Instance1 where
	toString _ = "Instance1"
	fromString "Instance1" = Instance1

     data Instance2 = Instance2
     instance MyTypeClass Instance2 where
	toString _ = "Instance2"
	fromString "Instance2" = Instance2

Now, there's a function foo:

     foo :: MyTypeClass c => c

foo generates things things which belong to MyTypeClass.  I want to use 
it as follows:

     SillyFreeTypeVariables> foo :: Instance1
     Instance1
     SillyFreeTypeVariables> foo :: Instance2
     Instance2

My problem is: how can foo be written?  I've tried:

     foo = fromString (toString undefined))

but this gives back an error message:

     Ambiguous type variable `a' in the top-level constraint:
	`MyTypeClass a'
	    arising from use of `toString' at SillyFreeTypeVariables.hs:18

Which is understandable, because the type of '(toString undefined)' is 
ambiguous, since there's a free type variable there ("toString 
undefined" doesn't actually return a type, only a type class 
constraint, which the type checker complains about).  What I'd like is 
that to be able to fix the type variable in MyTypeClass for 
"undefined", so that it is the same type as the result type of foo, e.g.

     foo :: MyTypeClass resultType => resultType
     foo = fromString (toString (undefined :: resultType))

but I can't seem to do this -- GHC's scoped type variables don't seem 
to help either, or at least I couldn't get it working.  I'm pretty sure 
that fixing the free type variable would work because if I change foo 
to look like

     foo :: MyTypeClass resultType => resultType
     foo = fromString (toString (undefined :: Instance1))

then the typechecker is happy and it compiles and runs, although now I 
can obviously only get foo to return something with a type of 
Instance1, thus rendering it useless :).  I don't want to pass a 
parameter to foo to get this to work.  Is it possible?

Thanks muchly!


-- 
% Andre Pang : trust.in.love.to.save