[Haskell-cafe] How lazy can "peek" be?

2005-08-24 Thread Juan Carlos Arevalo Baeza
  Hi! One of the nice things of laziness is that it allows us to 
express things concisely. For instance:


func a b =
   let ta = transmogrify a in
   case b of
   B1 -> doSomething
   B2 -> doSomethingElse ta
   B3 -> doAnotherThing ta

  It is clear why having this let-expression is a good thing. We can 
"transmogrify a" only once, and then use the "transmogrified a" only 
when (if) needed. In this case, one branch of the case expression 
doesn't need it, in which case we've effectively paid nothing for it, no 
matter how complex and time/resource-consuming "transmogrify" is.


  So far, so good.

  Now, I need to interoperate with external code using FFI. I have a 
function that gets called from outside, and gets its parameters as a 
pointer to a structure, so:


func p = do
   a <- peekByteOff p 0
   b <- peekByteOff p 4
   case b of
   B1 -> doSomething
   B2 -> doSomethingElse a
   B3 -> doAnotherThing a

  Now I see myself with a little dilemma. This code looks a lot like 
the first version, where instead of "transmogrifying", we just read the 
value from the structure through the use of the pointer. Reading the 
value from memory can't be very time consuming, but it has to cost 
something. If I don't want to pay for that cost, then I have to convert 
the code as in:


func p =
   b <- peekByteOff p 4
   case b of
   B1 -> doSomething
   B2 -> do { a <- peekByteOff p 0; doSomethingElse a }
   B3 -> do { a <- peekByteOff p 0; doAnotherThing a }

  Repetition, repetition, repetition. This does get tedious. Especially 
when the case expression has many branches, and there are many variables 
in the structure that might or might not be needed. So you see my 
dilemma. It's _very_ tempting to do something like:


func p = do
   let a = unsafePerformIO $ peekByteOff p 0
   b <- peekByteOff p 4
   case b of
   B1 -> doSomething
   B2 -> doSomethingElse a
   B3 -> doAnotherThing a

  I mean... the contents of "p" are never going to be modified, so this 
"feels" right on some level. But we're effectively breaking the pureness 
of the language. I mean... this function could be called twice with the 
same _pointer_ but different data stores in the structure, which can 
(and maybe will) cause problems depending on how evaluation proceeds.


  Is there a way to handle this nicely? I recently read about the Clean 
language. It seems like it allows (and relies) in an extension to the 
type system, that allows the program to specify uniqueness of values, so 
that two pointers values might be represented using the same bits, but 
they'd still be considered distinct values. But no such thing in 
Haskell. Maybe a good thing... trying to understand the whole 
explanation of uniqueness in Clean made my head spin. But still...


  Is it known what GHC, for instance, will do to this code when 
optimizing? Might it just do the right thing? Probably the C optimizer 
would take care of it. It feels to me that's my only hope.


  But it'd be great if the "haskell" part of the compiler could take 
care of it natively. This is something that I've been thinking about. I 
mean... the IO monad does seem to impose too much sometimes. Any IO 
action always is assumed to modify the "external world" (affect the 
execution of the actions that come after it), whether it does or not:


do
   peekByteOff p 0 -- totally useless, but it needs to be performed 
anyway before "returning"

   return ()

do
   a <- peekByteOff p 0
   b <- peekByteOff p 4 -- could be done before "a"

  Somehow, it feels like it'd be a good thing to be able to limit the 
scope of IO actions. Going too far would complicate it enormously:


do
   a <- readFile "file"
   b <- peekByteOff p 4 -- could be done in any order, really, but how 
would you express it... maybe "domains of influence", like "filesystem" 
and "memory"... not very clear.


do
   a <- peekByteOff p1 0
   pokeByteOff p2 0 1234 -- could be done in any order, as long as p1 
and p2 don't alias each other (yuck!)


  So I wouldn't want to go that far... yet :). A global thing might be 
an improvement. I'm aware it wouldn't be a monad anymore, but could it 
be something else?


  I hope this is all pointless :-).

JCAB

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


Re: [Haskell-cafe] Pattern match failure, then inconsistent function

2005-08-24 Thread Ross Paterson
On Mon, Aug 22, 2005 at 03:31:24PM +0100, Adam Wyner wrote:
> I am getting a "pattern match failure", and then subsequent functions
> which worked right work wrong.  I am using Hugs and Trex.  While most of
> the other functions work fine, the function "findCoordinatesUtil"
> generates an error, then misbehaves; it takes a record and searches a
> list of records to find other records in a specified relationship with
> the input function.
> [...]
> However, when I run the function on a larger list of records (here
> testList01), it generates an error message.
> 
> LexicalSemantics03> findCoordinatesUtil (giveActionFromLabel "Action33
> " testList01) testList01
> 
> Program error: pattern match failure: map_v780 (instEq_v20 instEq_v11
> Eq_== "neg-prop2") map_v780
> INTERNAL ERROR: Error in graph

This lokks like a memory management bug in Hugs, leaving the heap
corrupted so that further results are unreliable.  Please send in the full
program that triggers this, plus details of the Hugs version you're using.

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


Re: [Haskell-cafe] Hugs - evaluation statistics

2005-08-24 Thread Daniel Fischer
Am Mittwoch, 24. August 2005 16:55 schrieb Dusan Kolar:
> Hello,
>
>   Even if I know number of reductions should not be used
> to anything important I'm quite confused with values I get.
> Is garbage collection somehow affecting the number of
> reductions? I have always thought not, but... ;-)
>
>   Thx,
>
>Dusan
>

What is confusing you?
Different numbers of reductions for the same computation?
That would probably be due to the fact that named entities are stored and not 
re-evaluated.

Cheers,

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


[Haskell-cafe] Hugs - evaluation statistics

2005-08-24 Thread Dusan Kolar

Hello,

 Even if I know number of reductions should not be used
to anything important I'm quite confused with values I get.
Is garbage collection somehow affecting the number of
reductions? I have always thought not, but... ;-)

 Thx,

  Dusan

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


[Haskell-cafe] Re: Overlapping instances

2005-08-24 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>,
 "Frank" <[EMAIL PROTECTED]> wrote:

> I would like to state that a class Sup is exhaustively broken down in two
> subclasses Sub1 and Sub2 (meaning, for every instance of Sub1 and every
> instance of Sub2, the methods in Sup apply). 
> 
> I try to code this as:
> 
> instance Sub1 x => Sup x 
> instance Sub2 x => Sup x 
> 
> And get the (expected) error message
> ExhaustiveClass.hs:22:0:
> Duplicate instance declarations:
>   ExhaustiveClass.hs:22:0: instance (Sub1 x) => Sup x
>   ExhaustiveClass.hs:25:0: instance (Sub2 x) => Sup x
> (I have allowed overlapping instances, undecidable instances)
> 
> Is there another way of achieving this? 
> Any help appreciated!
> 
> Andrew
> 
> 
> 
> - complete code I tried with:
> class Sub1 a where
> op1 :: a -> a
> 
> class Sub2 a where
> op2 :: a -> a -> a
> 
> class Sup a where
> op3 :: a -> Bool
> 
> 
> instance Sub1 Int where
> op1 = id
> instance Sub2 Float where
> op2 x y = y
> 
> instance Sub1 x => Sup x where
> op3 _ = True
> 
> instance Sub2 x => Sup x where
> op3 _ = False

Try this:

class Sup a where
op3 :: a -> Bool
class (Sup a) => Sub1 a where
op1 :: a -> a
class (Sup a) => Sub2 a where
op2 :: a -> a -> a

instance Sup Int where
op3 _ = True
instance Sup Float where
op3 _ = False
instance Sub1 Int where
op1 = id
instance Sub2 Float where
op2 x y = y

-- 
Ashley Yakeley, Seattle WA

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