Re: [Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread Aaron McDaid

On 2/26/07, Thomas Nelson [EMAIL PROTECTED] wrote:

I'm brand new to haskell and I'm having trouble using classes.  The basic idea
is I want two classes, Sine and MetaSine, that are both instances of ISine.


'class' in Haskell doesn't mean the same as 'class' in C++ or Java. I
found it easier at first to thing of them as:
  A Haskell 'class' is more like a Java interface.
  Haskell types are more like what you might think of as 'class'es.
  Haskell 'instance' means Java 'implement'
  There is no word that means that same as 'instance' from Java/C++
terminology. I suppose we would call them 'values' or something.
Somebody more knowledgeable can describe the etymology of the terms,
but these 3 observations should help.


data Sine =
 Sine {  period :: Integer, offset :: Integer, threshold :: Integer,  
letter :: String}

instance Sine ISine where
 act time (Sine self)
 |on time self = [letter self]
 |otherwise = []


To be honest, I'm not sure what you're trying to do here, so beware of
my advice...
You might want to do this instead:

data Sine = Sine Integer Integer Integer String
instance ISine Sine where   -- note that ISine should come before Sine
 period (Sine p _ _ _ _) = p
 period (Sine _ o _ _ _) = o
-- and so on ...

There can only be a single function called period, which will take a
thing of any type which is an instance of ISine and return an Integer.
So every time you tell Haskell this type is to be an implementation
of ISine you have to write the period function for it as I have done
for Sine here.


-Thomas


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


Re: [Haskell-cafe] Newbie Q: GHCi: W here “List” module is imported from?

2007-02-16 Thread Aaron McDaid

On 2/16/07, Dmitri O.Kondratiev [EMAIL PROTECTED] wrote:


 where  then declaration:

 instance Ord []

 can be found?



With Hugs, it can be found in /usr/lib/hugs/libraries/Hugs/Prelude.hs
(on Debian anyway). For GHC, I guess it's in compiled into one of the
.hi files? From Hugs' Prelude.hs:

instance Ord a = Ord [a] where
   compare [] (_:_)  = LT
   compare [] [] = EQ
   compare (_:_)  [] = GT
   compare (x:xs) (y:ys) = primCompAux x y (compare xs ys)


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


Re: [Haskell-cafe] IO is not a monad

2007-02-07 Thread Aaron McDaid

Could seq be changed so that it will not give an error if it finds
undefined? Am I right in thinking that seq is supposed to
theoretically do nothing, but simply give a hint to the compiler so to
speak? If that is true, it should merely attempt to evaluate it, but
ignore it if it cannot evaluate it.
Is it realistic or desirable to change seq like this?

Anyway, as far as I can see it is already true that
  (= f) . return = f
because 'equality' for Monads simply means they do that same thing
when 'executed' or whatever. The only thing that can currently find a
difference between the above monads is seq and seq is a funny thing.

Aaron

On 2/7/07, Yitzchak Gale [EMAIL PROTECTED] wrote:

Just for the record, I think this completes the
requirements of my challenge. Please comment!
Is this correct?
Thanks.

 1. Find a way to model strictness/laziness properties
 of Haskell functions in a category in a way that is
 reasonably rich.

We use HaskL, the category of Haskell types, Haskell
functions, and strict composition:

f .! g = f `seq` g `seq` (f . g)

Let undef = \_ - undefined. A function f is strict iff
f .! undef = undef, lazy iff f .! undef /= undef, and
convergent iff f .! g /= undef for all g /= undef.

We consider only functors for which fmap is a
morphism.
A functor preserves strictness iff fmap is strict.
A functor preserves laziness iff fmap is convergent.

Note that with these definitions, undefined is lazy.

 2. Map monads in that category to Haskell, and
 see what we get.

Assume that return /= undef, and that = is convergent
in its second argument.

The monad laws are:

1. (= return) = id
2. (= f) . return = f
3. (= g) . (= f) = (= (= g) . f)
4. = is strict in its second argument.

 3. Compare that to the traditional concept of
 a monad in Haskell.

As long as we are careful to use the points-free
version, the laws are the same as the traditional
monad laws. In particular, we can use the usual
composition for these laws. But we must add the
strictness law.
___
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] IO is not a monad

2007-02-06 Thread Aaron McDaid

Hi,
Apologies for referring to this old thread...

I rearranged the code a little bit while experimenting but retained
the same behaviour:

Prelude let f = undefined :: Int - IO Int
Prelude (f 3  f 3) `seq` 42
42
Prelude (f 3) `seq` 42
*** Exception: Prelude.undefined

I think this makes it a little simpler for me to see the issue here.
Simply, 'undefined  undefined' is a bit more defined than simply
'undefined'. Just like 'undefined:undefined' is at least a non-empty
list; which can be matched by (_:_) for example. This explains the
differing behaviour of the two seemingly equivalent actions above.

So I think the above behaviour is more to do with how shallow seq is,
as others have probably already shown (but much of the rest of the thread is
beyond me).

Prelude undefined `seq` 5
*** Exception: Prelude.undefined
Prelude (undefined:undefined) `seq` 5
5

Aaron (relative newbie)



On 1/23/07, Brian Hulley [EMAIL PROTECTED] wrote:
 Brian Hulley wrote:
  Brian Hulley wrote:
  Yitzchak Gale wrote:
  I wrote:
  Prelude let f = undefined :: Int - IO Int
  Prelude f `seq` 42
  *** Exception: Prelude.undefined
  Prelude ((= f) . return) `seq` 42
  42
  The monad laws say that (= f) . return must be
  identical to f.
 
  I thought it was:
 
 return x = f = f x
 
  so here the lhs is saturated, so will hit _|_ when the action is
  executed just as the rhs will.

 Ooops! But that does not mean the equation holds because for example

 Prelude (return 3 = f) `seq` 42
 42
 Prelude (f 3) `seq` 42
 *** Exception: Prelude.undefined

 In the lhs you only hit _|_ when the composite (=) action is actually
 being executed whereas in the rhs you hit _|_ when computing the function
 which will return the action to execute so there is difference.

 Brian.
 --
 http://www.metamilk.com

 ___
 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


[Haskell-cafe] Polymorphism/monomorphism (and the restriction)

2006-09-21 Thread Aaron McDaid

Hi,
I think the following might help a little in understanding the 
monomorphic restriction (which I don't fully understand myself). I'm a 
bit of a newbie so apologies in advance if I've made a mistake or if my 
description isn't as useful to others as it seems to me. I've been 
following a thread on haskell@haskell.org and I think the below might 
help. I used GHCi, version 6.2.2 (it fails in hugs but that seems to be 
because of hugs non-compliance with the standard in this case).


First off, I'm guessing that I'm getting Haskell98 behaviour here and 
not some GHCi extension. Please tell me if this is not the case.


Run the code listing at the bottom of this email and you should get the 
output which I've also listed below.
This code experiments with Int, Float and (Num a) = a, and I 
tried to print x*2 and x/2 for each. (4::Int)/2 isn't allowed because / 
isn't defined for Ints.


You can see that
kN :: (Num a) = a
took two different types depending on what method ( / or * ) was applied 
to it.

kN / 2 = 2.0
kN * 2 = 8
kN/2 is a Float (it can't use Int as / isn't defined for Int, so it uses 
Float, for which / is defined).

kN*2 is an Int.
The above outputs demonstrates polymorphism, doesn't it? i.e. Not only 
has the compiler got a variety of types to choose from, but a variety of 
types can be used at runtime?


The output for kI and kF is obvious.

The interesting thing is that k behaves as a Float in both cases. This 
is monomorphism isn't it? i.e. the compiler may have a variety of types 
to choose from, but it picks one and sticks to it for every usage. In 
summary, k didn't give the same outputs as kN.


And the monomorphism restriction is a rule which means that sometimes 
things are forced to a monomorphic type (like k as Float here) when it 
could have given it a polymorphic type like kN :: (Num a) = a


I'm fairly new to these lists, so apologies if I'm covering old ground 
again. My first aim is to understand exactly what polymorphism and 
monomorphism is and demonstrate corresponding results, before thinking 
about the restriction.


Thanks,
Aaron

-- The code
kI :: Int
kI = 4

kF :: Float
kF = 4

kN :: (Num a) = a
kN = 4

k = 4

main = do
p kI * 2 $ kI * 2
p kF / 2 $ kF / 2
p kF * 2 $ kF * 2
p kN / 2 $ kN / 2
p kN * 2 $ kN * 2
p k  / 2 $ k / 2
p k  * 2 $ k * 2

p :: (Show a) = String - a - IO ()
p s = putStrLn.(s++).( = ++).show


-- the output - remember kI / 2 is not possible.
kI * 2 = 8
kF / 2 = 2.0
kF * 2 = 8.0
kN / 2 = 2.0
kN * 2 = 8
k  / 2 = 2.0
k  * 2 = 8.0

-- PS: If you delete the k / 2 line from the program, then k * 2 becomes 
simply 8 (not 8.0). It uses Int if possible, and Float if that's not 
available.

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