
On Saturday 02 October 2010 23:28:59, Thomas wrote:
So, instantiating Char for Num would require you to provide implementations for (+), (*), (-), negate, abs, signum and fromInteger for Char. While syntactically possible, I don't see any semantically reasonable way to do so.
For some values of reasonable, defining the operations via the Enum instance is semantically reasonable. It's however not the best approach, even if for some odd reason you need 21-bit integers.
Is there a way to display a value along with its type during program execution? 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?
AFAIK in GHCi you can do both, but not simultaneously: Prelude> let a = 5::Int Prelude> :t a a :: Int Prelude> a 5
:set +t makes ghci display the type of an expression entered at the prompt (except if it's an IO-action, then it behaves a little different).
It makes sense to me to say that [ ] is a function that takes a type as an argument and generates an value. If that's the case, it also makes sense to say that [ ] == [ ] can't be evaluated because there is simply no == for functions.
Prelude> :t [] [] :: [a]
So [] is a list type, not a function type.
Right. [] as a function taking a type as argument is how it's represented at the Core level in GHC, not how it's understood at the Haskell level or the assembly level.
Prelude> [] == [] True
You can actually compare [] to itself.
At the ghci prompt, since that uses extended default rules and chooses to compare at the type [()]. In a source file, you'd have to turn on the extended default rules ({-# LANGUAGE ExtendedDefaultRules #-}) or tell the compiler which type to use.
So your reasoning does not seem to be valid to me. At least not on the Haskell source code level (which is what you and your students work with). Daniel referred to the Core level when saying that [] was a function there.
My reasoning would go somewhere along the following line: [] has a polymorphic type, specifically it's an empty list of elements of any type ([] :: [a], type variable a is not restricted)
So, [] will compare to any empty list, no matter what its elements' type actually is.
You need an Eq instance, of course.
Given:
let xs = [] ys = 1:xs zs = 'a': xs
Then "tail ys == tail zs" will not type check. Neither "tail ys" nor "tail zs" are polymorphic: ys :: [Integer]
Well, tail ys is polymorphic, its type is tail ys :: Num a => [a] the type variable a is defaulted to Integer if there are no further constraints on a. If you use it for other stuff, it can be used at other types too. Prelude> let xs = []; ys = 1:xs; ws = length xs:tail ys; vs = pi:tail ys in (tail ws, tail vs) ([],[]) it :: (Floating a) => ([Int], [a])
zs :: [Char]
So the expression "tail ys == tail zs" is invalid - the lhs and rhs must have the same type but they do not. Nothing will get compared, no tail will be determined - it will just plainly be rejected from the compiler (or interpreter).
For comparison: "tail ys == []" is different. (tail ys) :: [Integer] [] :: [a]
So we set (well, GHC does this for us) type variable a to Integer and have: tail ys :: [Integer] == [] :: [Integer] which is perfectly valid.
Yep.
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.
See above - [] is not a function.
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?) 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?
(==) :: (Eq a) => a -> a -> Bool
So, yes, (==) feels a little like an overloaded function.
And such functions are often called overloaded.
It is a function that accepts any Eq-comparable type. However, overloading IIRC does not behave identically.
Overloading in Java, C# etc. behaves differently. Overloading is still a good term to describe (==) etc. in my opinion. One has to be aware that the word denotes different though related concepts for different languages, of course.
For example function arity is not required to be the same when overloading methods - and restrictions on types are very different, too.
HTH, Thomas