[Haskell-beginners] fromIntegral

Felipe Lessa felipe.lessa at gmail.com
Fri Oct 1 11:38:03 EDT 2010


On Fri, Oct 1, 2010 at 12:08 PM, Russ Abbott <russ.abbott at gmail.com> wrote:
]
] On Thu, Sep 30, 2010 at 10:25 PM, Felipe Lessa <felipe.lessa at gmail.com>
] wrote:
]] Now, maybe 'fromIntegral' has something more than polymorphism?
]] Well, it has typeclasses.  But we can represent those as
]] data types, so we could write
]]
]]  fromIntegralD :: Integral a -> Num b -> a -> b
]]  fromIntegralD intrDictA numDictB =
]]    fromIntegral numDictB . toInteger intrDictA
]
] I'm afraid I don't understand this. Moreover, I couldn't get the preceding
] to load without error.

Let's simplify things a little bit to make a runnable example.
Suppose we have

> class MonoidClass a where
>   mc_empty  :: a
>   mc_append :: a -> a -> a

We can construct the following function:

> mc_concat :: MonoidClass a => [a] -> a
> mc_concat []     = mc_empty
> mc_concat (x:xs) = mc_append x (mc_concat xs)

Pretty standard stuff.

Now, the 'MonoidClass' class could also be a plain data type:

> data MonoidDict a = MD {md_empty  :: a
>                        ,md_append :: a -> a -> a}

I have just put the members of the class as fields of a data
type.

Now 'mc_concat' can be written as:

> md_concat :: MonoidDict a -> [a] -> a
> md_concat md []     = md_empty md
> md_concat md (x:xs) = md_append md x (md_concat md xs)

So, while 'mc_concat' has constraints, 'md_concat' is just as
pure polymorphic as 'length' is.


]] Functions that are polymorphic but do not have constraints are
]] not really overloaded because of parametricity, which means that
]] they can't change the way they work based on the specific choices
]] of types you make.
]
] I don't understand the preceding paragraph. Would you mind elaborating.

Take 'length', for example.  It has type

    length :: [a] -> Int

As it is polymorphic on the list's element type, it can't behave
any differently when I use it on an [Int] from when I use it on a
[Double].

]] > If so, can I say the same sort of thing about constants like 1 and []?
]] > In
]] > particular there is no single value []. Instead [] is a symbol which at
]] > compile time must be compiled to the empty list of some particular type,
]] > e.g., [Int].  There is no such Haskell value as [] :: [a] since [a] (as
]] > type) is not an actual type. I want to say the same thing about 1, i.e.,
]] > that there is no such Haskell value as 1 :: (Num t) => t. When the
]] > symbol 1
]] > appears in a program, the compiler must decide during compilation
]] > whether it
]] > is intended to be 1::Int or 1::Integer or 1::Double, etc.
]]
]] Well, [a] *is* an actual type, a polymorphic one.
]
] Here is the example that raised that issue for me. Let's say I define null'
] as follows.
]
]    null' xs = xs == [ ]
]
] If I don't include a declaration in the file, Haskell (reasonably) concludes
] the following.
]
]   > :t null'
]   null' :: (Eq a) => [a] -> Bool
]
] If I write the following at the top level, everything is fine.
]   > null' [ ]
]   True
]
] But if I include the following in the file that defines null', I get an
] error message.
]
]   test = null' [ ]
]
]       Ambiguous type variable `a' in the constraint:
]            `Eq a' arising from a use of `null'' at null.hs:6:17-24
]          Probable fix: add a type signature that fixes these type
] variable(s)
]
] Why is that? And how can it be fixed?  I know I can fix it as follows.

If your function was, for example,

> null'' :: [a] -> Bool
> null'' [] = True
> null'' _  = False

then there would be no error.  I assume you already figured that
out.  null'' works because it doesn't need to know what kind of
list is.  By parametricity, its behaviour can't change based on
its type.

However, null' *can* change its behaviour based on the elements
type!  It can use any of the functions in Eq class.  For example,

> nullW :: Eq a => [a] -> Bool
> nullW [x,y] = x == y
> nullW _     = False

Note that this functions has the same type as your null', however
its behaviour depends on which kind of 'a' you give to it, as
different 'a's have different (==)s.

Another way of seeing this is by passing the type class as an
argument (I'll omit /=):

> data EqDict a = EQ {eq_equals :: a -> a -> Bool}
>
> -- Takes equality for 'a' and returns equality for '[a]'.
> -- Just like the type class which is
> --
> --   instance Eq a => Eq [a] where ...
> listEqDict :: EqDict a -> EqDict [a]
> listEqDict eq = EQ equals
>     where
>       equals []     []     = True
>       equals (x:xs) (y:ys) = eq_equals eq x y && equals xs ys
>       equals _      _      = False
>
> nullDict :: EqDict a -> [a] -> Bool
> nullDict eq xs = eq_equals (listEqDict eq) xs []

So while null'' only takes the list as argument, nullDict also
needs to know which EqDict you want to use.  With type classes,
this EqDict is chosen based on 'a's type.

And that's precisely what the error message says.  It says that
type 'a' is ambigous because of the 'Eq a' constraint.


] It seemed to me that similar reasoning applied to things like 1.  How is the
] following explained?
]
]    Prelude> 111111111111111111111111111111111111111111
]    111111111111111111111111111111111111111111
]    it :: (Num t) => t
]    Prelude> maxBound :: Int
]    2147483647
]    it :: Int
]    Prelude> 111111111111111111111111111111111111111111 - (1::Int)
]    -954437178
]    it :: Int
]
] Does it make sense to say that the long string of 1's is really of type (Num
] t) => t?
]
] If so, what does the compiler think it's doing when it processes(?) it as an
] Int so that it can subtract 1 :: Int from it?  It didn't treat it as
] maxBound :: Int.  And yet it didn't generate an error message.

This is the same thing.  The type

    (Num t) => t

really is the same as

    NumDict t -> t

Hope that helps, =)

--
Felipe.


More information about the Beginners mailing list