explicit signatures and default for integer literals

Hi all, an explicit given signature causes ghc to choose the right types for integer literals as in {-# OPTIONS -fglasgow-exts #-} import Data.Map f :: Ord a => [a] -> Map a Int f xs = fromList $ zip xs [0..] Here the Literal 0 is threated as (0::Int). But the setting {-# OPTIONS -fglasgow-exts #-} import Data.Map class New a b where new :: a -> b instance Ord a => New [(a,b)] (Map a b) where new = fromList g :: Ord a => [a] -> Map a Int g xs = new $ zip xs [0..] causes the error message Could not deduce (New [(a, b)] (Map a Int)) from the context (Ord a) arising from use of `new' at Why.hs:10:7-9 ghc seems to be unable to threat the Literal 0 as (0::Int) this time but I do not understand why :-( Can anyone explain it? Thanks, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ ---

*Main> :type fromList
fromList :: (Ord k) => [(k, a)] -> Map k a
*Main> :type new
new :: (New a b) => a -> b
The type of new probably accounts for the difference (even though it
still makes me wonder what the big deal is :)
Using functional dependencies seems to fix it, i.e.:
class New a b | a -> b where new :: a -> b
or, perhaps more appropriately:
class New a b | b -> a where new :: a -> b
Cheers,
D. Tenev
On 5/27/05, Mirko Rahn
Hi all,
an explicit given signature causes ghc to choose the right types for integer literals as in
{-# OPTIONS -fglasgow-exts #-}
import Data.Map
f :: Ord a => [a] -> Map a Int f xs = fromList $ zip xs [0..]
Here the Literal 0 is threated as (0::Int).
But the setting
{-# OPTIONS -fglasgow-exts #-}
import Data.Map
class New a b where new :: a -> b
instance Ord a => New [(a,b)] (Map a b) where new = fromList
g :: Ord a => [a] -> Map a Int g xs = new $ zip xs [0..]
causes the error message
Could not deduce (New [(a, b)] (Map a Int)) from the context (Ord a) arising from use of `new' at Why.hs:10:7-9
ghc seems to be unable to threat the Literal 0 as (0::Int) this time but I do not understand why :-(
Can anyone explain it?
Thanks,
-- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Dinko Tenev wrote:
*Main> :type new new :: (New a b) => a -> b
The type of new probably accounts for the difference (even though it still makes me wonder what the big deal is :)
The big deal is to export just abstract types. When exporting abstract types one needs functions to create them, e.g. fromList, singleton, ..., and therefore one needs names for the creating functions. In realistic situations this solution tends to produce a number of similiar named functions. (One for every possible input.) Exactly this is captured by the class New, since all this functions have the same name now.
Using functional dependencies seems to fix it, i.e.:
Yes of course, but
class New a b | a -> b where new :: a -> b
No, I want to be able to define instance a b instance a c ...
or, perhaps more appropriately:
class New a b | b -> a where new :: a -> b
No again, I want to be able to define instance b a instance c a ... I re-ask my question:
{-# OPTIONS -fglasgow-exts #-}
import Data.Map
class New a b where new :: a -> b
instance Ord a => New [(a,b)] (Map a b) where new = fromList
f :: Ord a => [a] -> Map a Int f xs = fromList $ zip xs [0..]
g :: Ord a => [a] -> Map a Int g xs = new $ zip xs [0..]
Why is ghc unable the determine the type of the Literal 0 in the definition of g? The definition of f works fine instead. Regards, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ ---

{-# OPTIONS -fglasgow-exts #-}
import Data.Map
class New a b where new :: a -> b
instance Ord a => New [(a,b)] (Map a b) where new = fromList
g :: Ord a => [a] -> Map a Int g xs = new $ zip xs [0..]
Why is ghc unable the determine the type of the Literal 0 in the definition of g?
Answer: Since somewhere an instance e.g. New [(a,Double)] (Map a Int) could be defined, leading to problems when threating 0 as (0::Int). Thanks to private communication, Cheers, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ ---

Am Montag, 30. Mai 2005 11:48 schrieb Mirko Rahn:
{-# OPTIONS -fglasgow-exts #-}
import Data.Map
class New a b where new :: a -> b
instance Ord a => New [(a,b)] (Map a b) where new = fromList
g :: Ord a => [a] -> Map a Int g xs = new $ zip xs [0..]
Why is ghc unable the determine the type of the Literal 0 in the definition of g?
Answer: Since somewhere an instance e.g. New [(a,Double)] (Map a Int) could be defined, leading to problems when threating 0 as (0::Int).
Thanks to private communication, Cheers,
It wasn't actually private, I accidentally sent it to haskell-cafe, sorry. Cheers, Daniel

On 5/31/05, Daniel Fischer
Why is ghc unable the determine the type of the Literal 0 in the definition of g?
Answer: Since somewhere an instance e.g. New [(a,Double)] (Map a Int) could be defined, leading to problems when threating 0 as (0::Int).
There could be such an instance, but that's obviously not the case. At the point where g is defined, GHC only knows about New [(a,b)] (Map a b), and New [(a,Double)] (Map a Int) doesn't fit. Consider this: *Main> :type new . flip zip [0..] new . flip zip [0..] :: (New [(a, b1)] b, Num b1, Enum b1) => [a] -> b Trying to infer New [(u, v)] w out of all that we know, i.e. New [(a,b)] (Map a b) should give us w === Map u v ---> New [(u, v)] (Map u v) so finally v === Int ---> New [(u, Int)] (Map u Int) to infer the context of g. Is there any good reason not to do this? Cheers, D. Tenev

Dinko Tenev wrote:
On 5/31/05, Daniel Fischer
wrote: Why is ghc unable the determine the type of the Literal 0 in the definition of g?
Answer: Since somewhere an instance e.g. New [(a,Double)] (Map a Int) could be defined, leading to problems when threating 0 as (0::Int).
There could be such an instance, but that's obviously not the case. At the point where g is defined, GHC only knows about New [(a,b)] (Map a b), and New [(a,Double)] (Map a Int) doesn't fit.
Consider this:
*Main> :type new . flip zip [0..] new . flip zip [0..] :: (New [(a, b1)] b, Num b1, Enum b1) => [a] -> b
Trying to infer
New [(u, v)] w
out of all that we know, i.e.
New [(a,b)] (Map a b)
should give us
w === Map u v ---> New [(u, v)] (Map u v)
so finally
v === Int ---> New [(u, Int)] (Map u Int)
to infer the context of g.
Is there any good reason not to do this?
Because I'm not smart enough to understand it? ;-)
Cheers,
D. Tenev _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On 5/31/05, Seth Kurtzberg
Because I'm not smart enough to understand it?
;-)
OK, sorry about the notation (I just didn't feel like doing so much typing, you know :) Here goes... First we observe that, g = new . flip zip [0..], so, without the type specification, it has the general type (New [(a, b1)] b, Num b1, Enum b1) => [a] -> b, as reported by GHC. Then we infer from (1) g :: (New [(u, v)] w, Num v, Enum v) => [u] -> w and (2) instance New [(a, b)] (Map a b) that in (New [(u, v)] w), w can only be (Map u v), so subst (Map u v) for w to obtain (3) g :: (New [(u, v)] (Map u v), Num v, Enum v) => [u] -> Map u v Furthermore, for g we have already specified (4) g :: Ord a => [a] -> Map a Int so finally substituting Int for v should give us (5) g :: (New [(u, Int)] (Map u Int), Num Int, Enum Int, Ord Int) => [u] -> Map u Int Is there any good reason why GHC won't do this? Particularly, is there any good reason not to infer (New [(u, v)] (Map u v)) from (New [(u, v)] w) as in (1), (2) --> (3) above? Cheers, D. Tenev

Dinko Tenev wrote:
First we observe that, g = new . flip zip [0..], so, without the type specification, it has the general type (New [(a, b1)] b, Num b1, Enum b1) => [a] -> b, as reported by GHC.
Then we infer from
(1) g :: (New [(u, v)] w, Num v, Enum v) => [u] -> w
and
(2) instance New [(a, b)] (Map a b)
that in (New [(u, v)] w), w can only be (Map u v)
This step in the reasoning requires a functional dependency, which you mentioned earlier you were unwilling to supply. Without functional dependencies w can, in fact, be something other than (Map u v).

On 5/31/05, robert dockins
Dinko Tenev wrote:
First we observe that, g = new . flip zip [0..], so, without the type specification, it has the general type (New [(a, b1)] b, Num b1, Enum b1) => [a] -> b, as reported by GHC.
Then we infer from
(1) g :: (New [(u, v)] w, Num v, Enum v) => [u] -> w
and
(2) instance New [(a, b)] (Map a b)
that in (New [(u, v)] w), w can only be (Map u v)
This step in the reasoning requires a functional dependency, which you mentioned earlier you were unwilling to supply. Without functional dependencies w can, in fact, be something other than (Map u v).
We need to infer New [(u, v)] w, and the only thing we know so far is New [(a, b)] (Map a b). In this context, what else could we possibly have for w besides (Map u v) ? Cheers, D. Tenev

Ghc can't assume "in this context" - the object file produced by
compilation could be linked into code that provides other instances.
Abe
On 5/31/05, Dinko Tenev
On 5/31/05, robert dockins
wrote: Dinko Tenev wrote:
First we observe that, g = new . flip zip [0..], so, without the type specification, it has the general type (New [(a, b1)] b, Num b1, Enum b1) => [a] -> b, as reported by GHC.
Then we infer from
(1) g :: (New [(u, v)] w, Num v, Enum v) => [u] -> w
and
(2) instance New [(a, b)] (Map a b)
that in (New [(u, v)] w), w can only be (Map u v)
This step in the reasoning requires a functional dependency, which you mentioned earlier you were unwilling to supply. Without functional dependencies w can, in fact, be something other than (Map u v).
We need to infer New [(u, v)] w, and the only thing we know so far is New [(a, b)] (Map a b). In this context, what else could we possibly have for w besides (Map u v) ?
Cheers,
D. Tenev _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Answer: Since somewhere an instance e.g. New [(a,Double)] (Map a Int) could be defined, leading to problems when threating 0 as (0::Int).
There could be such an instance, but that's obviously not the case.
No, suppose module A is the module with the definitions as before. Now: module B where import A instance New [(a,Double)] (Map a Int) where ... When compiling A ghc cannot be sure, that there is no such instance, since it could be defined elsewhere. regards, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ ---
participants (6)
-
Abraham Egnor
-
Daniel Fischer
-
Dinko Tenev
-
Mirko Rahn
-
robert dockins
-
Seth Kurtzberg