Mon, 24 Apr 2000 11:05:56 +0400 (MSD), S.D.Mechveliani <[EMAIL PROTECTED]> pisze:

> In  ghc-4.06, -O   s1  costs 10 times more than  s,
>                    s2  costs same as  s1.

Probably because Prelude.lhs contains:

{-# SPECIALISE sum     :: [Int] -> Int #-}
{-# SPECIALISE sum     :: [Integer] -> Integer #-}

but I have not investigated it.

> I wonder whether I understand at all what  newtype  is for. Why could
> the programmer need to define a copy of a type, but not a synonym?

Because he does not want to allow confusion between these types,
using one in the place of another; or because he wants the type to
be abstract outside.

For example he makes a type representing a set of small integers
and does not want to exhibit the representation, which is a plain
Int treated as a sequence of bits. He wants values of the type to be
manipulated only by his functions, so he can change the representation
at any time with guaranteed compatibility.

> I see only one reason. Because one needs to define some instances
> differently than for the base type.

This is another reason. It's especially common for complex function
types made instances of Monad.

> Also the Haskell-98 Report, does not it specify that newtype is
> only for tagging a new label to the thing preserving the physical
> representation?

newtype is treated exactly as data for the purpose of typechecking,
classes, module exports and related stuff, but is transparent for
code generation, bottoms etc.

The language definition cannot say anything about the physical
representation. It's not C. Nothing prohibits the implementation from
attaching runtime type information to every value, for example in an
interpreter. Or from treating some types specially. But the language
definition's intent is such that it's possible for values of newtype
to be always represented as the oldtype.

> And if the conversion in this case is only tagging/untagging of a 
> label, why the language has to introduce `cast' for this?

Because in the type system they are distinct types. No less distinct than
    data LineCol = LC {line :: Int, col :: Int}
is distinct from (Int,Int).

Moreover, such casting need not to have any meaningful value in
practice. Take a bit set. The fact that it's implemented as an Int
is irrelevant. It's a set, not a number.

> And I do not understand, why Haskell does not support `deriving'
> for all the instances (user's too), at least, for newtype.

It could be a good idea. But what about deriving Show and Read
(should derived Show instance for newtype N = N Int produce "N 5" or
"5" for show (N 5)?). I can see arguments for both choices.

> When the user writes
>                      class C a where c :: a -> a
>                      instance C Int where  c = (+2)
>                      newtype Int1 = Int1 Int deriving(Eq,Ord,Num,C),
> 
> is not it clear automatically how  Num, C  are defined?

For newtypes it usually is, but not always.

import AnotherModule (
    Bar,           -- Abstract type.
    reverseBarInt) -- :: Bar [Int] -> Bar [Int]
    where

class Foo a where
    reverseFoo :: Bar [a] -> Bar [a]
instance Foo Int where
    reverseFoo = reverseBarInt

What does it mean to derive Foo Int1 from Foo Int?

> Further, for
>                    data D a = D ...
> if the user had defined for  a <--> D a  the castings
>                                                    f  :: a   -> D a,
>                                                    f' :: D a -> a  
> (reciprocally inverse ones),
> could the compiler understand what does this mean
>                           ...= D...deriving ((C by maps (f,f')),...)
> ?

IMHO such complication is definitely not needed. It's ugly.

-- 
 __("<    Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/              GCS/M d- s+:-- a23 C+++$ UL++>++++$ P+++ L++>++++$ E-
  ^^                  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK                  5? X- R tv-- b+>++ DI D- G+ e>++++ h! r--%>++ y-


Reply via email to