[Haskell-cafe] Are casts required?

2011-06-06 Thread Patrick Browne
Are casts required to run the code below?
If so why?
Thanks,
Pat


-- Idetifiers for objects
class (Integral i) = IDs i where
 startId :: i
 newId :: i - i
 newId i = succ i
 sameId, notSameId :: i - i - Bool
-- Assertion is not easily expressible in Haskell
-- notSameId i newId i  = True
 sameId i j = i == j
 notSameId i j = not (sameId i j)
 startId = 1


instance IDs Integer where



-- are casts need here?
sameId (newId startId::Integer) 3
sameId (3::Integer) (4::Integer)
notSameId (3::Integer) (newId (3::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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are casts required?

2011-06-06 Thread Ryan Ingram
I always forget to reply all.  Silly gmail.

On Mon, Jun 6, 2011 at 2:07 AM, Ryan Ingram ryani.s...@gmail.com wrote:

 Hi Pat.  There aren't any casts in that code.  There are type annotations,
 but this is different than the idea of a cast like in C.

 For example
 ((3 :: Integer) :: Int)
 is a compile error.

 What you are seeing is that 3 has the type (forall a. Num a = a); that is,
 the literal '3' gets converted by the compiler into

 fromInteger (I# 3#)

 where 3# represents the machine word '3' and I# is the internal constructor
 Word# - Integer.

 class Num a where
 ...
 fromInteger :: Integer - a

 So by 'casting', or rather, providing a type annotation, you are specifying
 what instance of Num gets the call to 'fromInteger'.

 As to whether you *need* a type annotation: it depends.  For example:
 foo () = sameId newId 3
 the compiler will infer the type of 'foo' to be
 foo :: forall a. IDs a = () - a

 If you declare foo as a value, though, you run into the dreaded
 monomorphism restriction, and you might get a complaint from the compiler
 about ambiguity.
 foo2 = sameId newId 3


 The monomorphism restriction forces values to be values; otherwise consider
 this


 -- the usual 'expensive' computation
 fib :: Num a = a - a
 fib 0 = 1
 fib n = fib (n-1) + fib (n-2)

 x = fib 10

 What's the type of x?  Most generally, it's
 x :: Num a = a

 But this means that x will be recalculated every time it's used; the value
 can't be saved since x doesn't represent a single value but rather a
 separate value for each instance of Num.  You are allowed to manually
 specify this type, but without it, the compiler says 'You meant this to be a
 value!' and forces it to a particular type if it can, or complains about
 ambiguity if it can't.  As to how it does so, look up the rules for
 defaulting and monomorphism in the Haskell report.

   -- ryan



 On Mon, Jun 6, 2011 at 12:45 AM, Patrick Browne patrick.bro...@dit.iewrote:

 Are casts required to run the code below?
 If so why?
 Thanks,
 Pat


 -- Idetifiers for objects
 class (Integral i) = IDs i where
  startId :: i
  newId :: i - i
  newId i = succ i
  sameId, notSameId :: i - i - Bool
 -- Assertion is not easily expressible in Haskell
 -- notSameId i newId i  = True
  sameId i j = i == j
  notSameId i j = not (sameId i j)
  startId = 1


 instance IDs Integer where



 -- are casts need here?
 sameId (newId startId::Integer) 3
 sameId (3::Integer) (4::Integer)
 notSameId (3::Integer) (newId (3::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

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are casts required?

2011-06-06 Thread Daniel Fischer
On Montag, 6. Juni 2011, 09:45, Patrick Browne wrote:
 Are casts required to run the code below?
 If so why?
 Thanks,
 Pat
 
 
 -- Idetifiers for objects
 class (Integral i) = IDs i where
  startId :: i
  newId :: i - i
  newId i = succ i
  sameId, notSameId :: i - i - Bool
 -- Assertion is not easily expressible in Haskell
 -- notSameId i newId i  = True
  sameId i j = i == j
  notSameId i j = not (sameId i j)
  startId = 1
 
 
 instance IDs Integer where
 
 
 
 -- are casts need here?
 sameId (newId startId::Integer) 3
 sameId (3::Integer) (4::Integer)
 notSameId (3::Integer) (newId (3::Integer))

The type signatures (not casts) are needed if the compiler cannot determine 
the instance to use from the context. If you have e.g. a declaration

foo :: Integer
foo = whatever

then sameId foo (newId 5) doesn't need a type signature since foo's type is 
known and determines the rest. Without such information, the compiler can't 
determine the instance it should use, so fails with an ambiguous type.
[Some module might contain

instance IDs Int where
  startId = 0
  newId k = 3*k
  sameId i j = ((i `xor` j) .. 7) == 0

or something, then what?]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are casts required?

2011-06-06 Thread Steffen Schuldenzucker


Hi Patrick,

On 06/06/2011 09:45 AM, Patrick Browne wrote:

Are casts required to run the code below?
If so why?
Thanks,
Pat


-- Idetifiers for objects
class (Integral i) =  IDs i where
  startId :: i
  newId :: i -  i
  newId i = succ i
  sameId, notSameId :: i -  i -  Bool
-- Assertion is not easily expressible in Haskell
-- notSameId i newId i  = True
  sameId i j = i == j
  notSameId i j = not (sameId i j)
  startId = 1


instance IDs Integer where



-- are casts need here?
sameId (newId startId::Integer) 3


I'll take this as an example. First of all, note that

WHAT YOU'VE WRITTEN IS NOT A CAST

, that is, if x is an Int, then x :: Double is a type error. What the 
'::' does is (in this situation) that it specializes the type of a 
polymorphic value.


In GHCi, omitting the ':: Integer' part, I get

*Main let x1' = sameId (newId startId) 3

interactive:1:10:
Ambiguous type variable `i' in the constraint:
  `IDs i' arising from a use of `sameId' at interactive:1:10-33
Probable fix: add a type signature that fixes these type variable(s)

Let's take the above expression apart:

We have:

*Main :t newId startId
newId startId :: (IDs i) = i

*Main :t 3
3 :: (Num t) = t

*Main :t sameId
sameId :: (IDs i) = i - i - Bool

Now, when trying to evaluating your expression, the machine ultimately 
has to know what (newId startId) and 3 are. This, of course, depends on 
the type chosen for i and t, respectively.

For example, if I define the following instance:

instance IDs Int where
startId = 2

we have:

*Main sameId (newId startId :: Integer) 3
False
*Main sameId (newId startId :: Int) 3
True

, so the result type clearly depends on the types chosen.
But, lacking an explicit signature, there is no way for the machine to 
tell which types should be used, in particular as the information which 
types were chosen is completely lost in the resulting type 'Bool'.


The example above does not look as if it was created to illustrate your 
problem. Then however, note that you don't have to use a class if you 
don't expect people to overwrite your default implementations. Normal 
Functions are sufficient:


 -- I always want this
 {-# LANGUAGE NoMonomorphismRestriction #-}

 startId :: (Integral i) = i
 startId = 1

 newId :: (Integral i) = i - i
 newId = succ

 sameId, notSameId :: (Integral i) = i - i - Bool
 sameId = (==)
 notSameId i j = not $ sameId i j

Ok, now this works even without the signatures:

*Main sameId (newId startId) 3
False

, which is probably caused by defaulting on the top level (IIRC, an 
unresolved Integral type variable defaults to Integer. Don't have the 
documentation at hand right now.) like this:


*Main let i3 = 3 :: (Integral x = x)
*Main :t i3
i3 :: Integer

and the same thing happens on the (newId startId) side, too.

As one last remark, your original problem that caused the Ambiguous 
type variable error looks very similar to the well-known (show . read) 
problem.


-- Steffen

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are casts required?

2011-06-06 Thread Daniel Fischer
On Montag, 6. Juni 2011, 11:08, Ryan Ingram wrote:
  Hi Pat.  There aren't any casts in that code.  There are type
  annotations, but this is different than the idea of a cast like in C.
  
  For example
 
  ((3 :: Integer) :: Int)
 
  is a compile error.
  
  What you are seeing is that 3 has the type (forall a. Num a = a);
  that is, the literal '3' gets converted by the compiler into
  
  fromInteger (I# 3#)
  
  where 3# represents the machine word '3' and I# is the internal
  constructor Word# - Integer.

Close, but not correct. In GHC, we have

data Int = I# Int#

and (if we're using integer-gmp)

data Integer
= S# Int#
| J# Int# ByteArray#

So, 3# is the *signed* machine int '3' and you'd get

fromInteger (S# 3#)

using the literal '3'.

  
  class Num a where
 
  ...
  fromInteger :: Integer - a
 
  So by 'casting', or rather, providing a type annotation, you are
  specifying what instance of Num gets the call to 'fromInteger'.
 
  As to whether you need a type annotation: it depends.  For example:
  foo () = sameId newId 3

Types don't match,

sameId :: IDs i = i - i - Bool
newId :: IDs i = i - i

Make that

foo () = startId

to get Ryan's types.

 
  the compiler will infer the type of 'foo' to be
 
  foo :: forall a. IDs a = () - a
 
  If you declare foo as a value, though, you run into the dreaded
  monomorphism restriction, and you might get a complaint from the
  compiler about ambiguity.
 
  foo2 = sameId newId 3

And

foo2 = startId

 
  The monomorphism restriction forces values to be values; otherwise
  consider this
  
  
  -- the usual 'expensive' computation
  fib :: Num a = a - a
  fib 0 = 1
  fib n = fib (n-1) + fib (n-2)
  
  x = fib 10
  
  What's the type of x?  Most generally, it's
 
  x :: Num a = a
 
  But this means that x will be recalculated every time it's used; the
  value can't be saved since x doesn't represent a single value but
  rather a separate value for each instance of Num.  You are allowed to
  manually specify this type, but without it, the compiler says 'You
  meant this to be a value!' and forces it to a particular type if it
  can, or complains about ambiguity if it can't.  As to how it does so,
  look up the rules for defaulting and monomorphism in the Haskell
  report.
 
-- ryan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe