[Haskell-beginners] Re: Beginners Digest, Vol 28, Issue 5

C Gosch ch.gosch at googlemail.com
Sat Oct 2 06:14:44 EDT 2010


I could be wrong, as I am also new to Haskell. I suppose
the compiler simply cannot decide which type the lists you want to compare
are
(their constituent elements  must be instances of class Eq, but more is not
known).
Adding type signatures will help the compiler (it should say so as well,
check the
error messages):

testNull = ([]::[Int]) == ([]::[Int])

although I don't know why you would want to do such a thing (sorry I did not
follow the
whole thread).

Cheers
Christian


2010/10/2 <beginners-request at haskell.org>

> Send Beginners mailing list submissions to
>        beginners at haskell.org
>
> To subscribe or unsubscribe via the World Wide Web, visit
>        http://www.haskell.org/mailman/listinfo/beginners
> or, via email, send a message with subject or body 'help' to
>        beginners-request at haskell.org
>
> You can reach the person managing the list at
>        beginners-owner at haskell.org
>
> When replying, please edit your Subject line so it is more specific
> than "Re: Contents of Beginners digest..."
>
>
> Today's Topics:
>
>   1. Re:  fromIntegral (Russ Abbott)
>
>
> ----------------------------------------------------------------------
>
> Message: 1
> Date: Fri, 1 Oct 2010 22:52:34 -0700
> From: Russ Abbott <russ.abbott at gmail.com>
> Subject: Re: [Haskell-beginners] fromIntegral
> To: Daniel Fischer <daniel.is.fischer at web.de>
> Cc: beginners at haskell.org
> Message-ID:
>        <AANLkTikKF9g3MnGew5YkAK=xxszdiLHCd8a81Skqd6Kf at mail.gmail.com>
> Content-Type: text/plain; charset="iso-8859-1"
>
> It turns out that
>
>   test1 = 1 == 1
>
> will load (and return True), but
>
>  testNull = [ ] == [ ]
>
> won't load. Both 1 and [ ] seem to have similar sorts of type parameters in
> their types. Why are they treated differently?
>
>
> -- Russ
>
>
>
> On Fri, Oct 1, 2010 at 10:40 PM, Russ Abbott <russ.abbott at gmail.com>
> wrote:
>
> > I can even write
> >
> > test =
> >    let x = []
> >        y = 1 : x
> >        z = 'a' : x
> >    in ...
> >
> > But clearly I can't write tail y == tail z.  Does that imply that type
> > inferencing prevents one from writing a True expression?
> >
> >
> > -- Russ
> >
> >
> >
> > On Fri, Oct 1, 2010 at 10:24 PM, Russ Abbott <russ.abbott at gmail.com
> >wrote:
> >
> >> Thanks. I'm still wondering what [ ] refers to. I can load the following
> >> file without error.
> >>
> >> null' xs = xs == [ ]
> >>
> >> test =
> >>    let x = [ ]
> >>    in tail [1]  == x && tail ['a']  == x
> >>
> >> (I know I can define null' differently. I'm defining it this way so that
> I
> >> can ask this question.)
> >>
> >> When I execute test I get True.
> >>  > test
> >>  True
> >>
> >> So my question is: what is x after compilation? Is it really a thing of
> >> type
> >>      (Eq a) => [a] ?
> >> If so, how should I think of such a thing being stored so that it can be
> >> found equal to both tail [1] and tail ['a']?  Furthermore, this seems to
> >> show that (==) is not transitive since one can't even compile
> >>   tail [1] == tail ['a']
> >> much less find them to be equal. Yet they are each == to x.
> >>
> >> -- Russ
> >>
> >>
> >>
> >> On Fri, Oct 1, 2010 at 9:08 AM, Daniel Fischer <
> daniel.is.fischer at web.de>wrote:
> >>
> >>> On Friday 01 October 2010 17:08:08, Russ Abbott wrote:
> >>> > Thanks, Filipe
> >>> >
> >>> > I clearly over-stated my case.  I'd like to break it into a number of
> >>> > different question.  Please see below.
> >>> >
> >>> > On Thu, Sep 30, 2010 at 10:25 PM, Felipe Lessa
> >>> <felipe.lessa at gmail.com>wrote:
> >>> > > I'll try to clarify some concepts.  Please correct me if I am
> >>> > > wrong, and please forgive me if I misunderstood you.
> >>> > >
> >>> > > On Fri, Oct 1, 2010 at 12:54 AM, Russ Abbott <
> russ.abbott at gmail.com>
> >>> > >
> >>> > > wrote:
> >>> > > > In explaining fromIntegral, I want to say that it is really a
> >>> > > > collection
> >>> > >
> >>> > > of
> >>> > >
> >>> > > > overloaded functions:
> >>> > > >
> >>> > > > Integer -> Double
> >>> > > > Int -> Float
> >>> > > > ...
> >>> > > >
> >>> > > > When GHC compiles a line of code with fromIntegral it in, it must
> >>> > > > decide
> >>> > >
> >>> > > at
> >>> > >
> >>> > > > compile time which of these overloaded functions to compile to.
> >>> > > > This is
> >>> > >
> >>> > > in
> >>> > >
> >>> > > > contrast to saying that fromIngetral is a function of the type
> >>> > > > (Integral
> >>> > >
> >>> > > a,
> >>> > >
> >>> > > > Num b) => a -> b.  In reality there is no (single) function of
> the
> >>> > > > type (Integral a, Num b) => a -> b because (among other things)
> >>> > > > every function must map between actual types, but (Integral a,
> Num
> >>> > > > b) => a -> b does not say which actual types are mapped between.
> >>> > > >
> >>> > > > Is the preceding a reasonable thing to say?
> >>> > >
> >>> > > First of all, I do think that polymorphic functions are plain ol'
> >>> > > functions.  For example
> >>> > >
> >>> > >  id :: a -> a
> >>> > >  id x = x
> >>> > >
> >>> > > is a function.  Moreover, in GHC 'id' has only one
> >>> > > representation, taking a thunk and returning a thunk, so even at
> >>> > > the machine code level this is only one function.
> >>> >
> >>> > Agree.  I over stated my case.  The same can be said for
> >>> >   length  :: [a] -> Int
> >>> > It doesn't matter what the type of element in the list is. length
> runs
> >>> > the same way no matter what. So this is pure polymorphism.
> >>> >
> >>> > > 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.
> >>> >
> >>>
> >>> No wonder, Integral and Num are type classes and not datatypes (unless
> >>> you
> >>> have defined such datatypes in scope).
> >>>
> >>> The point is, you can represent type classes as dictionaries, e.g.
> >>>
> >>> data Num a = NumDict
> >>>    { plus :: a -> a -> a
> >>>    , minus :: a -> a -> a
> >>>    , ...
> >>>    , fromIntegerD :: Integer -> a
> >>>    }
> >>>
> >>> data Integral a = IntegralDict
> >>>    { quotD :: a -> a -> a
> >>>    , ...
> >>>    , toIntegerD a
> >>>    }
> >>>
> >>> Then a type-class polymorphic function like fromIntegral becomes a
> >>> function
> >>> with some dictionaries as additional arguments.
> >>>
> >>> foo :: (Class1 a, Class2 b) => a -> b
> >>>
> >>> becomes
> >>>
> >>> fooDict :: Class1Dict a -> Class2Dict b -> a -> b
> >>>
> >>> To do that explicitly is of course somewhat cumbersome as one has to
> >>> always
> >>> carry the dictionaries around and one can have more than one dictionary
> >>> per
> >>> type (e.g.
> >>>
> >>> intNum1 :: Num Int
> >>> intNum1 = NumDict
> >>>    { plus = (+)
> >>>    , ...
> >>>    , fromIntegerD = fromInteger
> >>>    }
> >>>
> >>> intNum2 :: Num Int
> >>> intNum2 = NumDict
> >>>    { plus = quot
> >>>    , -- more nonsense
> >>>    , fromInteger = const 1
> >>>    }
> >>> ).
> >>>
> >>> Internally, GHC implements type classes via dictionaries and passes
> them
> >>> as
> >>> extra arguments to overloaded functions, as you can see by inspecting
> the
> >>> Core output (-ddump-simpl).
> >>>
> >>> > > Better yet, the compiler could write this code for us internally.
> >>>
> >>> And GHC does.
> >>>
> >>> > > Now, using thunks we can get a single machine code for
> >>> > > 'fromIntegralD' as well.
> >>>
> >>> But that's not terribly efficient, so with -O, GHC tries to eliminate
> >>> dictionaries and use the specialised functions (like
> >>> plusInteger :: Integer -> Integer -> Integer).
> >>>
> >>> > >
> >>> > > In sum, I think all functions are really just that, functions.
> >>> > >
> >>> > > --
> >>> > >
> >>> > > You may call functions that have typeclass constraints
> >>> > > "overloaded functions", but they still are functions.
> >>> > >
> >>> > > 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.
> >>> >
> >>>
> >>> For a function like
> >>>
> >>> length :: [a] -> Int
> >>>
> >>> , because it doesn't know anything about the type a at which it will be
> >>> called, it cannot do anything with the contents of the list (well, it
> >>> could
> >>> call seq on them, but it would do that for every type), it can only
> >>> inspect
> >>> the spine of the list.
> >>>
> >>> The code is completely independent of what type of data the pointers to
> >>> the
> >>> contents point to, so `length [True,False]' and `length [()]' can and
> do
> >>> call the exact same machine code.
> >>>
> >>> > > > 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,
> >>>
> >>> You seem to mean the ghci prompt here, not the top level of a module.
> >>>
> >>> > 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?
> >>>
> >>> null' has an Eq constraint, so to evaluate test, an Eq dictionary is
> >>> needed, but there's no way to determine which one should be used.
> >>>
> >>> At a lower level, the type of null' is
> >>>
> >>> null' :: EqDict a -> [a] -> Bool
> >>>
> >>> The (hidden) first argument is missing and GHC doesn't know which one
> to
> >>> pass.
> >>>
> >>> At the ghci-prompt, ghci's extended default rules let it selet the Eq
> >>> dictionary of () and all's fine.
> >>>
> >>> In a source file, GHC restricts itself to the default rules specified
> in
> >>> the language report, which state that for defaulting to take place, at
> >>> least one of the constraints must be a numeric class. There's none
> here,
> >>> so
> >>> no defaulting and the type variable of the constraint remains
> ambiguous.
> >>>
> >>> > And how can it be fixed?  I know I can fix it as follows.
> >>> >
> >>> >   test = null' ([ ] :: [Integer])
> >>> >
> >>> >   > :reload
> >>> >   >
> >>> >   > test
> >>> >
> >>> >   True
> >>>
> >>> In that situation, I think giving a type signature is the only wayน.
> >>>
> >>> test = null' ([] :: Num a => [a])
> >>>
> >>> also works.
> >>>
> >>> น -XExtendedDefaultRules might work too.
> >>> >
> >>> > That's what suggested to me that [ ] had to be compiled into a
> concrete
> >>> > value.
> >>>
> >>> Try
> >>>
> >>> null'' [] = True
> >>> null'' _ = False
> >>>
> >>> test'' = null'' []
> >>>
> >>> No type class constraints, no problems.
> >>>
> >>> >
> >>> >
> >>> > 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?
> >>>
> >>> Integer literals stand for (fromInteger Integer-value-of-literal), so
> the
> >>> literal itself can have any type belonging to Num. If you force it to
> >>> have
> >>> a particular type, the corresponding fromInteger function is determined
> >>> and
> >>> can be applied if the value is needed.
> >>>
> >>> >
> >>> > 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.
> >>>
> >>> For efficiency, fromInteger wraps, for a b-bit Integral type, the
> result
> >>> of
> >>> fromInteger n is n `mod` 2^b.
> >>>
> >>> >
> >>> > Thanks
> >>> >
> >>> > -- Russ
> >>>
> >>>
> >>
> >
> -------------- next part --------------
> An HTML attachment was scrubbed...
> URL:
> http://www.haskell.org/pipermail/beginners/attachments/20101002/23bab169/attachment.html
>
> ------------------------------
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
> End of Beginners Digest, Vol 28, Issue 5
> ****************************************
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20101002/604a99e0/attachment-0001.html


More information about the Beginners mailing list