Andrea Rossato wrote:
Hello!

I cannot understand this piece of code:

type Z = Int
type T a = Z -> (a, Z)
newtype T1 a = T1 (Z -> (a,Z))

mkT :: a -> T a
mkT a = \x -> (a, x)

Hi Andrea,

The definition of mkT above is identical to just writing:

   mkT :: a -> (Z -> (a,Z))

which in turn is identical to:

   mkT :: a -> (Int -> (a, Int))

ie
   mkT :: a -> Int -> (a, Int)

because type decls just introduce a shorthand notation whose meaning is equivalent to substituting the right hand side of the type decl into the places in your code where you write T a or Z.


mkT1 :: a -> b -> (a,b)
mkT1 a = \x -> (a, x)

why mkT is a type constructor and mkT1 seems not to be?

mkT1 above is not a type constructor either. If you want to construct a value of the newtype T1 a then you would have to write:

   mkT1 :: a -> T1 a
   mkT1 a = T1 (\x -> (a,x))

In the above, the occurrence of T1 in the signature is called a type constructor, and the occurrence of T1 in T1(\x -> (a,x)) is just called a constructor (or "value constructor"). mkT1 is a function that constructs a value of type (T1 a) and so could perhaps also be called a value constructor although this would be unusual - usually the term is only used to describe the constructor specified on the rhs of the newtype (or constructors specified in the data) declaration.

It is maybe easier to just think of a newtype decl as being the same as a data decl except for the fact that you can only have one constructor on the rhs whereas a data decl allows multiple constructors, and a type decl by contrast as just introducing a simple alias for convenience.

(There are in fact two differences between a newtype decl and a data decl with 1 constructor but it's probably best to understand the above distinction between newtype/data vs type first)

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
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to