
Hi, Below are some questions about the logical interpretation of types and type classes. Thanks, Pat module J where type Id = String type Position = Integer data Person = Person Id Position deriving Show -- Is this an axiom at type level? class Pos a where getPos :: a -> Position -- The :type command says -- forall a. (Pos a) => a -> Position -- How do I write this in logic? (e.g. implies, and, or, etc) -- What exactly is being asserted about the type variable and/or about the class? -- I am not sure of the respective roles of => and -> in a logical context -- Is the following a fact at type level, class level or both? instance Pos Person where getPos (Person i p) = p -- Is it the evaluation or the type checking that provides a proof of type correctness? -- getPos(Person "1" 2) This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie

On 01/09/2011, at 8:48 , Patrick Browne wrote:
Hi, Below are some questions about the logical interpretation of types and type classes.
Thanks, Pat
module J where type Id = String type Position = Integer data Person = Person Id Position deriving Show
-- Is this an axiom at type level? class Pos a where getPos :: a -> Position
One way to think of a type class is that it defines a set of types. For example, Eq is the set of types that support equality, and Pos is the set of types that have a position. By giving the class definition you've defined what it means to be a member of that set, namely that members must support the 'getPos' method, but without instances that set is empty. Whether you treat this bare class definition as an axiom depends on what you want from your logical system.
-- The :type command says -- forall a. (Pos a) => a -> Position -- How do I write this in logic? (e.g. implies, and, or, etc)
Type systems are logical systems, there is no difference. Granted, some systems correspond to parts of others, but there is no single logical system that can be considered to be *the logic*. An equivalent question would be: "how do I write this in functional programming?"
-- What exactly is being asserted about the type variable and/or about the class?
If you ignore the possibility that the function could diverge, then it says "For all types a, given that 'a' is a member of the set Pos, and given a value of type 'a', then we can construct a Position". Note that this doesn't guarantee that there are any types 'a' that are members of Pos. In Haskell you can define a type class, but not give instances for it, and still write functions using the type class methods.
-- I am not sure of the respective roles of => and -> in a logical context
Once again, "which logic?". The type system that checks GHC core is itself a logical system. GHC core has recently ben rejigged so that type class constraints are just the types of dictionaries. In this case we have: forall (a: *). Pos a -> a -> Position In DDC core, there are other sorts of constraints besides type class constraints. In early stages of the compiler we encode type class constraints as dependent kinds, so have this: forall (a: *). forall (_: Pos a). a -> Position. Both are good, depending on how you're transforming the core program.
-- Is the following a fact at type level, class level or both? instance Pos Person where getPos (Person i p) = p
If you take the GHC approach, a type class declaration and instance is equivalent to this: data Pos a = PosDict { getPos :: Pos a -> a -> Position } dictPosPerson :: Pos Person dictPosPerson = PosDict (\d (Person i p) -> p) From this we've got two facts: Pos :: * -> * dictPosPerson :: Pos Person You could interpret this as: 1) There is a set of types named Pos 2) There is an element of this set named Person.
-- Is it the evaluation or the type checking that provides a proof of type correctness? -- getPos(Person "1" 2)
The type inferencer constructs a proof that a Haskell source program is well typed. It does this by converting it to GHC core, which is a formal logical system. The core program itself is a proof that there is a program which has its type. The type checker for GHC core then checks that this proof is valid. Ben.

On 8/31/11 6:48 PM, Patrick Browne wrote:
Hi, Below are some questions about the logical interpretation of types and type classes. [...]
-- Is this an axiom at type level?
It depends how exactly you mean "axiom". Under some interpretations, Haskell has no way to specify axioms, since all specifications are accompanied by their definitions (e.g., types are defined by their constructors, classes are defined by their members, functions are defined by their expressions). In other words, there is nothing which lacks computational content. In contrast, systems like Coq and Agda do have mechanisms for asserting axioms.
-- forall a. (Pos a) => a -> Position -- How do I write this in logic? (e.g. implies, and, or, etc) -- What exactly is being asserted about the type variable and/or about the class? -- I am not sure of the respective roles of => and -> in a logical context
Loosely speaking, * forall translates to universal quantification, * classes and type constructors translate to predicates, * type/data families translate to functions in the logic, * the arrows translate to implications, * products/tuples translate to conjunction, * coproducts/unions translate to disjunction, ... I'm hedging here because the exact translation will depend on what sort of semantics you want to get out of the logic. For example: the distinction between the (=>) and (->) arrows could be ignored since they both represent implication; however, there are distinctions about which one can be used where, and that would be lost if we pretend they're identical. Similarly, the extent to which tuples/unions are actually con-/disjunction depends on what sort of entailments you want to consider valid (consider, for example, if we moved to a language with linear or affine types).
-- Is the following a fact at type level, class level or both? instance Pos Person where getPos (Person i p) = p
Types and classes are at the same level, they're just in different syntactic categories. This instance is declaring the validity of the fact: Pos Person And is proving that fact by giving a proof for all the type class methods. In particular, it is giving the proof \ (Person i p) -> p for getPos@Person.
-- Is it the evaluation or the type checking that provides a proof of type correctness? -- getPos(Person "1" 2)
Type checking provides the proof of type correctness. However, note that Haskell is an inconsistent logic--- all types are inhabited. So while we can prove type correctness at compile time, that doesn't necessarily guarantee logical correctness (since we may have used inconsistencies somewhere important). -- Live well, ~wren

Hi, Why does the Haskell :type command only sometimes print the type-class? Should I expect type-class inference as well as type inference? Maybe the type-class is inferred where possible, but not always printed? Thanks, Pat -- Code k x = x + 3 data T = T class A a where g::a -> a g a = a instance A T where instance A Integer where -- The results from the above code. -- First in the case of a function. Inferred the Num class *Main> :t k k :: forall a. (Num a) => a -> a *Main> :t k 3 k 3 :: forall t. (Num t) => t -- Did not print type class *Main> :t k (3::Integer) k (3::Integer) :: Integer -- Second in the case of a method of a type class. -- Inferred Num *Main> :t g 3 g 3 :: forall t. (A t, Num t) => t -- Did not print class A. *Main> :t g T g T :: T -- Did not print any class. *Main> :t g (3::Integer) g (3::Integer) :: Integer This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie

On Fri, 2011-08-12 at 23:52 +0100, Patrick Browne wrote:
-- Second in the case of a method of a type class. -- Inferred Num *Main> :t g 3 g 3 :: forall t. (A t, Num t) => t -- Did not print class A. *Main> :t g T g T :: T -- Did not print any class.
This is because you already know that T is T. The compiler has checked that T is, in fact, an instance of A, but it need not tell you so because it has information that's strictly more specific than that.
*Main> :t g (3::Integer) g (3::Integer) :: Integer
Same thing. Integer is an instance of A, so telling you it's an Integer is even better (more specific). -- Chris Smith

On Fri, Aug 12, 2011 at 18:52, Patrick Browne
Why does the Haskell :type command only sometimes print the type-class?
Haskell infers the most specific type applicable. If the most specific it can get is a typeclass, that's what it produces; if it can infer an explicit type, it will.
Should I expect type-class inference as well as type inference? Maybe the type-class is inferred where possible, but not always printed?
Typeclasses are not independent of types, and are not inferred separately from types. If you want to know what typeclasses a type is a member of, use :info. Haskell supports polymorphism: a bound expression does not need to have a single specific type, it can apply to multiple types and adapt itself to the type at its use site. Typeclasses are part of how this is accomplished. So if a bound expression is polymorphic, you will see its type expressed in terms of type variables, possibly with typeclass contexts. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On Fri, Aug 12, 2011 at 19:08, Brandon Allbery
On Fri, Aug 12, 2011 at 18:52, Patrick Browne
wrote: Why does the Haskell :type command only sometimes print the type-class?
Haskell infers the most specific type applicable. If the most specific it can get is a typeclass, that's what it produces; if it can infer an explicit type, it will.
By the way, a possible source of confusion here is the combination of the monomorphism restriction and defaulting, especially GHCi's extended defaulting. The monomorphism restriction says that if you don't provide a way to *easily* infer a type for a binding (in practice this means there are no parameters), Haskell insists that the binding is not polymorphic unless you explicitly provide a type signature. Defaulting is how it accomplishes this: there is a list of default types that can be applied when a concrete type is required and none is available, and the first one that typechecks is used. The Haskell standard specifies Double and Integer as default types; GHCI's extended defaulting (or GHC in general with -XExtendedDefaultRules) adds () aka "unit". So, for example, something that you might expect to be (Num a => a) may end up being Integer due to the monomorphism restriction requiring a concrete type and defaulting supplying one. (There's a widely expressed sentiment that the monomorphism restriction should go away because the confusion it engenders is worse than the problems it solves; on the other hand, GHC recently added a new application of it (monomorphic pattern bindings). In any case, if you want to play around with types in GHCi, you may want to ":set -XNoMonomorphismRestriction -XNoMonoPatBinds" so you can see how types actually behave in the wild.) -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

The :info command is a great help. Why does :info g 4 produce a parse error, while :t g 4 does not? Thanks for all your help, Pat On 13/08/2011 00:08, Brandon Allbery wrote:
Typeclasses are not independent of types, and are not inferred separately from types. If you want to know what typeclasses a type is a member of, use :info.
On 12/08/2011 23:52, Patrick Browne wrote:
Hi, Why does the Haskell :type command only sometimes print the type-class? Should I expect type-class inference as well as type inference? Maybe the type-class is inferred where possible, but not always printed?
Thanks, Pat
-- Code k x = x + 3
data T = T class A a where g::a -> a g a = a instance A T where instance A Integer where
-- The results from the above code. -- First in the case of a function. Inferred the Num class *Main> :t k k :: forall a. (Num a) => a -> a *Main> :t k 3 k 3 :: forall t. (Num t) => t -- Did not print type class *Main> :t k (3::Integer) k (3::Integer) :: Integer
-- Second in the case of a method of a type class. -- Inferred Num *Main> :t g 3 g 3 :: forall t. (A t, Num t) => t -- Did not print class A. *Main> :t g T g T :: T -- Did not print any class. *Main> :t g (3::Integer) g (3::Integer) :: Integer
This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie

On 13 August 2011 17:34, Patrick Browne
The :info command is a great help. Why does :info g 4 produce a parse error, while :t g 4 does not?
From :help in ghci:
:info [<name> ...] display information about the given names By "names", it's referring to existing definitions, either in imported modules or defined within ghci using let, e.g.: Prelude> let foo = "foo" Prelude> :i foo foo :: [Char] -- Defined at <interactive>:1:5-7 So, ":info g" would work; as would ":info g T" (by getting the info of both g and T _separately_).. But ":info g 4" doesn't because of the _4_, as it is a literal value, not a name of a value. This also happens with literal Strings, etc. Doing ":t g 4" tells ghci to determine the type of the expression "(g 4)". Note that even if you did ":info g T" it will _not_ give you the info of the expression "(g T)". -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com
participants (6)
-
Ben Lippmeier
-
Brandon Allbery
-
Chris Smith
-
Ivan Lazar Miljenovic
-
Patrick Browne
-
wren ng thornton