a bunch of newbie questions

what's the difference between data and co-data exactly? or between inductive data types and co-inductive data types? can you give me some reference points that explain these?
(read "56")::Integer
does it in fact pass the type (Integer) to the function (read)? I guess what we want is for the (Integer) implementation of the (read) function to evaluate, not really to cast the value of (read) function to (Integer). in the regex libraries, (~=) cast this way results in completely different things altogether, should type classes have namespaces associated with them? somewhat like Integer.read "56"? this way of selecting the intended implementation, does it work without trouble with multiparameter type classes as well? theoretically is it possible to do a strictness analysis without any help from the programmer? thanks a bunch in advance. __________________________________________________ Do You Yahoo!? Tired of spam? Yahoo! Mail has the best spam protection around http://mail.yahoo.com

Imam Tashdid ul Alam wrote:
what's the difference between data and co-data exactly? or between inductive data types and co-inductive data types?
In Haskell there is no such difference, as inductive and coinductive types coincide in the semantic setting in which Haskell is usually interpreted. If there were a difference, that is, if we interpret Haskell minus general recursion in a somewhat simpler semantic setting, then data types would contain inly finite values, whereas codata types could also contain infinite values.
can you give me some reference points that explain these?
Papers by Uustalu and Vene might be a good start. Watch out for corecursion and coalgebras.
(read "56")::Integer
does it in fact pass the type (Integer) to the function (read)?
No, it just says that the result of read should be an Integer.
I guess what we want is for the (Integer) implementation of the (read) function to evaluate, not really to cast the value of (read) function to (Integer).
Exactly. And that's what is happening. Based on the information provided when giving the result type.
in the regex libraries, (~=) cast this way results in completely different things altogether, should type classes have namespaces associated with them? somewhat like Integer.read "56"?
I don't think that we need this.
this way of selecting the intended implementation, does it work without trouble with multiparameter type classes as well?
Yes, as long as enough type information is provided for the typechecker to decide what is the correct instance to use. One way of reducing the amount of information needed is using functional dependencies.
theoretically is it possible to do a strictness analysis without any help from the programmer?
Yes, such analyses exist, and are implemented in GHC, for example. They are just approximative, and cannot be exact by computability reasons. Ciao, Janis. -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de

Janis Voigtlaender
Yes, as long as enough type information is provided for the typechecker to decide what is the correct instance to use. (snip)
I've always been a little surprised when this doesn't happen more widely for things other than instances. For instance, when IntMap.size, Map.size and Set.size (or whatever) are all in scope as "size", it should be fairly obvious what (size x) is about once we've inferred, for other reasons, that x is an IntMap. Similarly with records, if we had field names that cause functions for extracting the value of those fields, where we used the same field name in two different record types, I figure that there's usually no ambiguity because we can usually infer the type of the object to which the 'extractor' is being applied. Am I just not seeing the big picture, or would people not find this use of type information to resolve such ambiguities as nice as I would, or is it harder to do that than I'm expecting? -- Mark

Mark T.B. Carroll wrote:
Janis Voigtlaender
writes: (snip) Yes, as long as enough type information is provided for the typechecker to decide what is the correct instance to use. (snip)
I've always been a little surprised when this doesn't happen more widely for things other than instances. For instance, when IntMap.size, Map.size and Set.size (or whatever) are all in scope as "size", it should be fairly obvious what (size x) is about once we've inferred, for other reasons, that x is an IntMap. Similarly with records, if we had field names that cause functions for extracting the value of those fields, where we used the same field name in two different record types, I figure that there's usually no ambiguity because we can usually infer the type of the object to which the 'extractor' is being applied.
Am I just not seeing the big picture, or would people not find this use of type information to resolve such ambiguities as nice as I would, or is it harder to do that than I'm expecting?
I think this is because in Haskell the only way to overload function names is to use type classes and instances just as the one and only way to qualify an identifier is by using modules. This has the advantage that different concerns are clearly separated out and dealt with in exactly one place by one concern-specific mechanism. Perhaps the basic problem is that (size) really belongs in a type class and IntMap, Set, Map etc were created before anyone bothered to try and factor their portions of common functionality into type classes. This factoring is a non-trivial problem however (as you can see from the various posts on the subject of sequences) since the design space is not nearly as well understood as basic mathematical objects like monoids, monads etc and without a mathematical foundation it is difficult to design a type class factoring with any confidence. For record fields, I suggested a while back that the compiler could automatically create the relevant type classes and instances eg: data Point i = Point {x :: i} would ensure that a global typeclass was created if not already present: class (.x) a b | a -> b where (.x) :: a -> b and would also create an instance for that type: instance (.x) (Point i) i where (.x) (Point k) = k where ".x" is parsed as a single lexeme and treated as a postfix operator ie: -- no space between '.' and fieldname exp .x or exp.x === (.x) exp but exp . x === (.) exp x -- composition To refer to a particular field name directly you could use: g = ((.x) :: Point a -> a) but I also thought it might be nice to have a special syntax to make things less clunky eg: g = Point^x (It could not be written as Point.x because Point is not a module name, unless you wanted to destroy the very simple rule that Foo.xyz qualifies xyz by the module Foo) In any case with the trivial syntactic sugar above it would already be possible to use the same record names in multiple types simultaneously. I think the reason there was no positive feedback about this idea before is that unfortunately it looks as if the record system is to be extended to deal with subtyping or horrible anonymous records such as {x=5} that don't have an explicit value constructor in front of them instead of just concentrating on making the existing system (which I really like apart from the lack of field name overloading and dot access syntax) more usable as above. For value constructors, a change in the type inference algorithm would be needed if they were to be resolved based on their types so you could write eg: data Location = Left | Right | Up | Down data Hand = Left | Right foo :: Location -> Hand foo Left = Left foo Up = Left foo Right = Right foo Down = Right and again there could be a syntax like Location^Left as a less clunky alternative to (Left::Location) in cases where ambiguity needs to be resolved explicitly eg if someone didn't want to write a top level type signature for their function. Imho this would make life a lot easier because you could concentrate on names that are appropriate to the type without having to know about all the other types you'd want to use unqualified in the same scope. Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Hello Mark, Friday, August 4, 2006, 3:03:54 PM, you wrote:
I've always been a little surprised when this doesn't happen more widely for things other than instances. For instance, when IntMap.size, Map.size and Set.size (or whatever) are all in scope as "size", it should be fairly obvious what (size x) is about once we've inferred, for other reasons, that x is an IntMap. Similarly with records, if we had
this is called ad-hoc polymorphism which is not supported by Haskell. instead Haskell supports parametric polymorphism via type classes. i'm not a language lawyer ;) but thinks that difference between C++ which supports former and Haskell that supports later is the following: C++ can infer only result type based on arguments type while Haskell can infer in _both_ directions. i can imagine C++ type inferring algorithm, with a little imagination i even can think about Haskell's algorithm :) but two-way type inferring together with ad-hoc polymorphism make me a little nervous :) how about, for example, two ad-hoc-polymorphic functions: f (g x)? or dozens of such calls enclosed? how error messages should be generated: "it may be Int::f with Char::g or Char::f with Bool::g or ... or ... or ..." ? one more cause is that Haskell was defined by scientists, not practical programmers, and scientists prefer to use more systematic ways to do the same things nevertheless, there is no principal differences. in many cases you can define type classes, include your ad-hoc polymorphic functions into these classes and sleep easy. in particular, as Brian already said, there is a proposal to use automatically generated type classes for record fields -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
this is called ad-hoc polymorphism which is not supported by Haskell. instead Haskell supports parametric polymorphism via type classes.
I think you are wrong here Bulat. In fact, I think a) Haskell supports parametric polymorphism, e.g. id :: t -> t id x = x b) Haskell supports ad-hoc polymorphism via type classes Martin

Martin Percossi wrote:
Bulat Ziganshin wrote:
this is called ad-hoc polymorphism which is not supported by Haskell. instead Haskell supports parametric polymorphism via type classes.
I think you are wrong here Bulat. In fact, I think a) Haskell supports parametric polymorphism, e.g. id :: t -> t id x = x b) Haskell supports ad-hoc polymorphism via type classes
Sometimes a distinction is made between ad-hoc polymorphism of the kind you'd get in C++ with method overloading, and "restricted parametric polymorphism" as in "Monad m =>" ie: 1) id :: t -> t -- Unrestricted parametric polymorphism 2) foo :: Monad m => m a -- Restricted parametric polymorphism for (m) and unrestricted for (a) 3) bar :: Int -> Int -> String bar :: Char -> Bool The only way to describe this is ad-hoc polymorphism, and the fact that any function is of the form A -> B means regardless of the arity of the overloaded functions it can also be supported by typeclasses (*) eg: class Bar a b where bar :: a -> b instance Bar Int (Int -> String) where ... instance Bar Char Bool where ... And a function or value in scope can be making use of unrestricted, restricted, and ad-hoc polymorphism at the same time eg: zap :: Monad m => Char -> m a zap :: Int -> String -> a String class Zap a b where zap :: a -> b instance Monad m => Zap Char (m a) where ... instance Zap Int (String -> a String) where ... (*) But there's one exception: you can't use typeclasses to resolve overloadings between values and functions because non-function values don't have a type of the form A -> B: cool :: Int cool :: Char -> String class Cool -- Ooops! fundamental problem encountered ;-) Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Hello Brian, Friday, August 4, 2006, 8:50:25 PM, you wrote:
class Bar a b where bar :: a -> b
(*) But there's one exception: you can't use typeclasses to resolve overloadings between values and functions because non-function values don't have a type of the form A -> B:
cool :: Int cool :: Char -> String
class Cool -- Ooops! fundamental problem encountered ;-)
class Cool a where cool :: a instance Cool Int instance Cool (Char -> String) ? -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Brian,
Friday, August 4, 2006, 8:50:25 PM, you wrote:
class Bar a b where bar :: a -> b
(*) But there's one exception: you can't use typeclasses to resolve overloadings between values and functions because non-function values don't have a type of the form A -> B:
cool :: Int cool :: Char -> String
class Cool -- Ooops! fundamental problem encountered ;-)
class Cool a where cool :: a
instance Cool Int instance Cool (Char -> String)
?
Yes thanks - someone else pointed this out to me off-list as well. I think that mental block must have been caused by watching too many episodes of Star Trek yesterday! Ok I give up, there's just no excuse... ;-) Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Hello Imam, Friday, August 4, 2006, 12:19:04 PM, you wrote:
(read "56")::Integer
does it in fact pass the type (Integer) to the function (read)?
it tells the compiler that result should be of type Integer. this info used by compiler to select among the different 'read' instances proper one. actually, in type inference algorithm, some types are already known from context (function types if you given type declarations, types of some results or parameters, types of global variables and fields in datatypes) and compiler infer types of all other values using this information
theoretically is it possible to do a strictness analysis without any help from the programmer?
compiler contains such analyzer, it just not so smart as people writing the program. in the definition inc n = n+1 compiler infers that function is strict -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (6)
-
Brian Hulley
-
Bulat Ziganshin
-
Imam Tashdid ul Alam
-
Janis Voigtlaender
-
mark@ixod.org
-
Martin Percossi