
Hello, I'm wondering why you can write
data FSet a = Show a => M (a -> Double)
a :: FSet Double a = M $ \x -> 0
and it works, but
type FSet a = Show a => (a -> Double)
a :: FSet Double a _ = 0
fails with
All of the type variables in the constraint `Show a' are already in scope (at least one must be universally quantified here) In the type synonym declaration for `FSet'
If I understood the GHC manual, this should work, as FSet a should be replaced in a, so a type signature would come:
a :: Show a => (a -> Double)
which is OK. Sorry if this is FAQ, but I did some searches and nothing came out. Thanks in advance, Emilio

Hola Emilio!
On 6/7/07, Emilio Jesús Gallego Arias
Hello,
I'm wondering why you can write
data FSet a = Show a => M (a -> Double)
a :: FSet Double a = M $ \x -> 0
and it works, but
type FSet a = Show a => (a -> Double)
type only works for redefinitions (i.e. adding the |Show a| constraint makes FSet a different type to (a -> Double)). In addition you seem to be trying to pack a dictionary with the type (something you cannot do in Haskell without existentials). This is just a guess, but it seems that a definition using existentials is what you're looking for. data FSet a = forall a. Show a => FSet (a -> Double) Cheers, PD: Saluda Ángel de mi parte :)

Hi Alfonso!
"Alfonso Acosta"
type FSet a = Show a => (a -> Double)
type only works for redefinitions (i.e. adding the |Show a| constraint makes FSet a different type to (a -> Double)).
Yes, I know. What I mean, if type is a type macro, why cannot it expand type constraints too? Quoting the GHC manual
7.4.1.3. Liberalised type synonyms
Type synonyms are like macros at the type level, and GHC does validity checking on types only after expanding type synonyms.
Seemed to me like a syntactical restriction, however that parses OK, but the typer complains. I guess this is due to types like
type A a = Show a => a type B a = Show a => a
so if you do
f :: A a -> B b it should get translated to f :: (Show a => a) -> (Show b => b)
Which is not valid. I wonder if regrouping all the contexts in the left side should work:
f :: (Show a, Show b) => a -> b
In addition you seem to be trying to pack a dictionary with the type (something you cannot do in Haskell without existentials). This is
Why? My first guess it that there's no way to translate that to system F, but if we look at 'type' as a macro, it could make sense.
just a guess, but it seems that a definition using existentials is what you're looking for.
data FSet a = forall a. Show a => FSet (a -> Double)
That would be
data FSet = forall a. Show a => FSet (a -> Double)
not? The above is like
data FSet b = forall a. Show a => FSet (a -> Double)
I'm not looking yet for existential types, as then my functions will have to hold for every a, which turns out to be very inconvenient. The reason I don't want to use data, which works ok, is because I'd like to use FSet as a function, but not to write the type constraint in every function using as it is now.
type FSet a = a -> Double a :: Show a => FSet a ...
Thanks for your answer, Emilio pd: Greetings from Angel too :)

Hi again,
On 6/8/07, Emilio Jesús Gallego Arias
I guess this is due to types like
type A a = Show a => a type B a = Show a => a
You're right. This is not valid in the standard nor GHC.
so if you do
f :: A a -> B b it should get translated to f :: (Show a => a) -> (Show b => b)
Which is not valid. I wonder if regrouping all the contexts in the left side should work:
f :: (Show a, Show b) => a -> b
Maybe it can be feasible to implement that behavior, but it clearly doesn't work like that right now. Maybe some GHC guru reading this could explain why? You can get the effect you want by using existentials to pack the constraint with the type type Discard a = forall b. Show b => a -> b -> (a, String) thus, a function f :: Discard a -> Discard b would expand to something like f :: (forall b. Show b => a -> b -> (a, String)) -> (forall c. Show c => b -> c -> (c, String))
In addition you seem to be trying to pack a dictionary with the type (something you cannot do in Haskell without existentials). This is
Why? My first guess it that there's no way to translate that to system F, but if we look at 'type' as a macro, it could make sense.
No idea, but that's how it works (I've been hitting myself against the wall to solve similar problems and existentials seem the only way to go).
just a guess, but it seems that a definition using existentials is what you're looking for.
data FSet a = forall a. Show a => FSet (a -> Double)
That would be
data FSet = forall a. Show a => FSet (a -> Double)
not?
Yep, you're right. a is alredy universally quantified in the RHS. This is probably what you're looking for: type FSet a = forall a. Show a => FSet (a -> Double)
I'm not looking yet for existential types, as then my functions will have to hold for every a, which turns out to be very inconvenient.
hold?
The reason I don't want to use data, which works ok, is because I'd like to use FSet as a function, but not to write the type constraint in every function using as it is now.
I know, it can be a pain to have to carry the type class constraints everywhere. Maybe the type redefinition using existentials I wrote above can help. Otherwise I guess you'll have to cope with writting the constraint in every function signature.

Hi Alfonso!
"Alfonso Acosta"
On 6/8/07, Emilio Jesús Gallego Arias
wrote: Yep, you're right. a is alredy universally quantified in the RHS. This is probably what you're looking for:
type FSet a = forall a. Show a => (a -> Double)
I'm not looking yet for existential types, as then my functions will have to hold for every a, which turns out to be very inconvenient.
hold?
See,
type FSet = forall a . Show a => (a -> Double)
up :: Double -> Double up x = x + 1
m :: FSet m = up
This doesn't work. I really want to use some functions that are not general enough. If the function cannot touch it's value (as it's the case with forall), then the function is almost useless, unless you'd like to do some type level programming. I'd like to have different functions for the same type, so I cannot pack it into a type class.
The reason I don't want to use data, which works ok, is because I'd like to use FSet as a function, but not to write the type constraint in every function using as it is now.
I know, it can be a pain to have to carry the type class constraints everywhere. Maybe the type redefinition using existentials I wrote above can help. Otherwise I guess you'll have to cope with writting the constraint in every function signature.
Yeah, in general Haskell types don't carry constraints, however, I don't see the reason that this doesn't work when using type level macros, as
type F a = C a => a
should just be a macro and substitute. Regards, Emilio

On Jun 8, 2007, at 16:25 , Emilio Jesús Gallego Arias wrote:
Yeah, in general Haskell types don't carry constraints, however, I don't see the reason that this doesn't work when using type level macros, as
type F a = C a => a
should just be a macro and substitute.
It is. That's the problem. Macros can't know anything about the contexts in which they're used. In the type system, this translates to implicit "forall" constraints:
type F' a = forall a. C a => a
The result of this is that a simple use like
foo :: F a -> F a
expands the macros literally, with the implicit "forall" because the macro expansion has to assume it is independent of everything else:
foo' :: (forall a. C a => a) -> (forall a. C a => a)
This means the two "a"s are independent and can't be unified by the typechecker. In theory I suppose the simple macro expansion could be replaced by some type expression which would allow the typechecker to recognize that any (F a)s used in a given type can be unified, but I have no idea what it would look like. (Then again, I'm no type hacker.) And I find myself wondering if that would lead to problems when expanding complex types. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
participants (3)
-
Alfonso Acosta
-
Brandon S. Allbery KF8NH
-
egallego@babel.ls.fi.upm.es