[Haskell-beginners] Re: [Haskell-cafe] What is an "expected type"
...
Daniel Fischer
daniel.is.fischer at web.de
Sun Jun 28 12:52:32 EDT 2009
Am Sonntag 28 Juni 2009 18:06:52 schrieb Brandon S. Allbery KF8NH:
> On Jun 28, 2009, at 12:02 , michael rice wrote:
> > dec2bin :: Integer -> [Integer]
> > dec2bin n = dec2bin' n []
> > where dec2bin' n acc
> >
> > | n == 0 = acc
> > | otherwise = let r = rem n 2
> >
> > m = div (n - r) 2
> > in dec2bin' m (r : acc)
> >
> > is there any way to assign a type signature to the helper function?
>
> Same way you do for a top level binding:
> >> dec2bin :: Integer -> [Integer]
> >> dec2bin n = dec2bin' n []
> >> where dec2bin' :: Integer -> [Integer] -> [Integer]
> >> dec2bin' n acc
> >>
> >> | n == 0 = acc
> >> | otherwise = let r = rem n 2
> >>
> >> m = div (n - r) 2
> >> in dec2bin' m (r : acc)
But, to mention it before it bites, putting type signatures involving type variables on
local helper functions is not entirely straightforward. Consider
inBase :: Integral a => a -> a -> [a]
0 `inBase` b = [0]
n `inBase` b = local n []
where
local 0 acc = acc
local m acc = case m `divMod` b of
(q,r) -> local q (r:acc)
Now try giving a type signature to local. You can't.
What is the type of local?
It's (type of b) -> [type of b] -> [type of b],
but "type of b" isn't available.
If you try
local :: a -> [a] -> [a]
or
local :: Integral a => a -> [a] -> [a],
you are saying that local works for *every* type a (or for every type a which is an
instance of Integral), because the 'a' from local's type signature is a new (implicitly
forall'd) type variable.
To be able to give local a type signature, you must bring the type variable 'a' into
scope:
{-# LANGUAGE ScopedTypeVariables #-}
inBase :: forall a. Integral a => a -> a -> [a]
0 `inBase` b = [0]
n `inBase` b = local n []
where
local :: a -> [a] -> [a] -- now this a is the same a as the one above
local 0 acc = acc
local m acc = case m `divMod` b of
(q,r) -> local q (r:acc)
More information about the Beginners
mailing list