[Haskell-beginners] fromIntegral

Daniel Fischer daniel.is.fischer at web.de
Sat Oct 2 18:17:58 EDT 2010


On Saturday 02 October 2010 21:53:11, Russ Abbott wrote:
> Daniel, I appreciate your help.  Let me tell you where I'm coming from.
>  I teach an introductory Haskell course once a year.  I'm not a Haskell
> expert, and I tend to forget much of what I knew from one year to the
> next.  Perhaps more importantly, one reason for asking these questions
> is to explain what's going on to students who are just seeing Haskell
> for the first time.

Hrrrmmphhhh.
What's going on behind the scene is complex and implementation dependent 
(and I know only a little about how GHC does it).

Perhaps it's best to say that for the time being, they should regard 
polymorphic expressions like [] as either one symbol denoting different 
values of different types or one value having many types, whichever they 
feel more comfortable with.

Both are possible ways of implementing polymorphism and unless they want to 
build their own implementation they need not choose how to nail it down.
Coming to grips with the gory details is difficult enough when you have a 
good understanding of the higher level.

> We are now 2 weeks into the course.  If this can't
> be explained (at least at an intuitive level) without displaying lots of
> intermediate code, it doesn't help me.

Well, at that point Core is not a good idea. At an intuitive level, I think 
both of the above work.
If you want to know what happens in more detail, you have to look at the 
compiler's intermediate representation(s), but to get proficient in using a 
language, that's not necessary.

>
> So here are a couple of questions about this example.
>
> What does it mean to say a Num instance for Char.

You write an

instance Num Char where

and you say how the operations should work on Chars.

> Can you give me an
> example of what that means in a program that will execute.  (Preferably
> the program would be as simple as possible.)

module Main (main) where

-- ord and chr convert between Char and Int
import Data.Char (ord, chr)

-- Number of elements Char has.
-- One could also choose 256 for example.
charMod :: Int
charMod = ord maxBound + 1

-- We lift addition, subtraction and multiplication
-- from Int, should be familiar from C (1-byte char, 256 values)
-- or Java (2-byte char, 65536 values).
-- negate and fromInteger are not quite the same because
-- the number of Chars is not a power of 2.
instance Num Char where
    a + b = chr $ (ord a + ord b) `mod` charMod
    a - b = chr $ (ord a - ord b) `mod` charMod
    a * b = chr $ (ord a * ord b) `mod` charMod
    negate a = chr $ negate (ord a) `mod` charMod
    abs a = a
    signum a = chr $ signum (ord a)
    fromInteger n = chr $ fromInteger n `mod` charMod

test :: Bool
test = [97] == "a"
-- aka True

main :: IO ()
main = do
    putStrLn
        [67,104,97,114,97,99,116,101,114,115,32,97,115,32,110,117
        ,109,98,101,114,115,44,32,105,116,32,119,111,114,107,115,46]
    putStrLn $ map (8600 -) "The quick brown fox jumps over the lazy dog."

-- That only uses fromInteger, so one could leave the other functions
-- undefined here, but you could substitute e.g. '0'+'1' for 97, 't'-'3' 
for 67, '\n'*11 for 110, ...

>
> Is there a way to display a value along with its type during program
> execution?

At the ghci prompt (or hugs), you can

query the type of an expression with the :t command (or spell it out, 
:type)

Prelude> :type True
True :: Bool
Prelude> :t \f -> [map f [1 .. 4], "now"]
\f -> [map f [1 .. 4], "now"]
  :: (Num a, Enum a) => (a -> Char) -> [[Char]]

Prelude> :set +t
Prelude> length "Hey there!"
10
it :: Int
Prelude> []
[]
it :: [a]

Hugs> :set +t
Hugs> length "Hullo"
5 :: Int
Hugs> []
[] :: [a]

Those print only the type of the final value, so if you want to display the 
types of intermediate values in a real programme, you need something 
different.

> I know about Show; is there something similar like
> ShowWithType (or even ShowType) that (if implemented) will generate a
> string of a value along with its type?

Not really. There is Data.Typeable, though, which contains the typeOf 
function:

Prelude Data.Typeable> :t typeOf
typeOf :: (Typeable a) => a -> TypeRep

it is, however, probably of limited use for that purpose, since

Prelude Data.Typeable> typeOf Nothing

<interactive>:1:0:
    Ambiguous type variable `a' in the constraint:
      `Typeable a' arising from a use of `typeOf' at <interactive>:1:0-13
    Probable fix: add a type signature that fixes these type variable(s)


>
> It makes sense to me to say that [ ] is a function that takes a type as
> an argument and generates an value.

Note that that's an implementation detail. That's not at the Haskell level.

> If that's the case, it also makes
> sense to say that [ ] == [ ] can't be evaluated because there is simply
> no == for functions.

No. [] as a function taking a type as argument is an interpretation below 
the Haskell level, while (==) operates on the Haskell level.

>
> It also makes sense to me to say that == is a collection of more
> concrete functions from which one is selected depending on the type
> required by the expression within which == appears.

That's one way to look at it. Probably the best for the beginning.

>
> Since the required type is known at compile time, it would seem that the
> selection of which == to use could be made at compile time. One
> shouldn't have to carry along a dictionary.  (Perhaps someone said that
> earlier. But if so, why the long discussion about Dictionaries?)

Ah, but what if you compile a library? Then you don't know at which types 
the function will be used in later programmes, so you have to have some 
method of determining which particular (==) to use when you later compile 
the programme.

> This seems like a standard definition of an overloaded function.
> So why is there an objection to simply saying that == is overloaded
> and letting it go at that?

I don't know, I wouldn't object to it. As long as you point out that it's 
not quite the same overloading as e.g. in Java, you can't have an 
overloading of a function with different numbers of arguments in Haskell.

>
> The answer to why tail ['a'] == [ ] is ok would go something like this.
> (Is this ok?)
>
> a. [ ] is a function that takes a type argument and generates the empty
> list of that type. In particular [ ] is not a primitive value.
>
> b. The type of the lhs is [Char].
>
> c. That selects == :: [Char] -> [Char] -> Bool as the version of == to
> use in the expression.
>
> d. That inserts Char as the Type argument to be passed to the [ ]
> function on the rhs.
>
> e. All the preceding can be done at compile time.
>
> f. When executed, the lhs and rhs will both execute the [ ] function
> with argument Char. They both generate the value [ ] :: [Char]. Those
> two values will be identical and the value of the expression will be
> True.
>

If you want to understand what happens at the lower Core level, that's 
okay, but it utterly doesn't work at the Haskell level.

At the Haskell level, we have

(==) :: Eq a => a -> a -> Bool

so (==) takes two arguments of the same type, but it can take two Bools, 
two Ints, ...

The LHS is [Char], hence the RHS must be too if the expression is to be 
well-typed. The RHS, [] has the inferred type [a], i.e. it can be a list of 
any type. That type can be unified with [Char] (since it is more general), 
the unification is done, fixing the type of [] *in this expression* as 
[Char].

>
> All of the preceding is something I would feel comfortable saying to
> someone who is just 2 weeks into Haskell.

I wouldn't.

> There may be a lot of pieces
> to that explanation, but none of them require much prerequisite Haskell
> knowledge.
>
> -- Russ



More information about the Beginners mailing list