Re: doubly linked list

2000-04-28 Thread Peter Hancock

 "Jan" == Jan Kort [EMAIL PROTECTED] writes:

 Anyway, a doubly linked list could be defined like this:

That was very interesting.  It seems to generalise to put
back-pointers and other context info in a variety of data
structures. This seems a pretty performance-enhancing thing to do.

It is reminiscent of Richard Bird's paper on cyclic structures.

Peter




RE: doubly linked list

2000-04-28 Thread Chris Angus



 -Original Message-
 From: Peter Hancock [mailto:[EMAIL PROTECTED]]
 Sent: 28 April 2000 10:23
 To: [EMAIL PROTECTED]
 Cc: [EMAIL PROTECTED]
 Subject: Re: doubly linked list
 
 
  "Jan" == Jan Kort [EMAIL PROTECTED] writes:
 
  Anyway, a doubly linked list could be defined like this:
 
 That was very interesting.  It seems to generalise to put
 back-pointers and other context info in a variety of data
 structures. This seems a pretty performance-enhancing thing to do.
 
 It is reminiscent of Richard Bird's paper on cyclic structures.
 
 Peter
 

I quite like the idea too but the thought of updating such a structure gives
me a headache.
Saying that ... this might encourage greater use of higher order fns rather
than
explicit recursion.








RE: doubly linked list

2000-04-28 Thread Chris Angus

Would it not be better to tag a start point then we can manipulate this
easier
and move it back to a singly linked list etc.

data Db a = Dd (Db a) a (Db a) 
  | DStart (Db a) a (Db a)

instance Show a = Show (Db a) where
 show xs = show (enumerate xs)

instance Eq a = Eq (Db a) where
 xs == ys = enumerate xs == enumerate ys

enumerate xs = enumerate' (rewind xs)
 
enumerate' (DStart _ v r) = v : enumerate'' r
enumerate' (Dd _ v r) = v : enumerate'' r
enumerate'' (DStart _ v r) = []
enumerate'' (Dd _ v r) = v : enumerate'' r

mapD f = dlink .(map f) .enumerate 

dlink ll = 
  let (hd,lst)=dble' ll lst hd
  dble [x] prev foll = 
let h = Dd prev x foll in (h,h)
  dble (x:xq) prev foll =
let h=Dd prev x nxt
(nxt,lst) = dble xq h foll
in (h,lst)
  dble' [x] prev foll = 
let h = DStart prev x foll in (h,h)
  dble' (x:xq) prev foll =
let h=DStart prev x nxt
(nxt,lst) = dble xq h foll
in (h,lst)
  in hd

left  (Dd a _ _) = a
left  (DStart a _ _) = a
right (Dd _ _ a) = a
right (DStart _ _ a) = a
val   (Dd _ x _) = x
val   (DStart _ x _) = x

rewind (Dd a _ _) = rewind a
rewind a = a

ffwd (Dd _ _ a) = ffwd a
ffwd a = a



 -Original Message-
 From: Jerzy Karczmarczuk [mailto:[EMAIL PROTECTED]]
 Sent: 28 April 2000 11:12
 Cc: [EMAIL PROTECTED]
 Subject: Re: doubly linked list
 
 
  Jan Brosius wrote:
 
  I wonder if it is possible to simulate a doubly linked list in
  Haskell.
 
 ... and the number of answers was impressive...
 
 Want some more?
 This is a short for *making* true double
 lists, and as an extra bonus it is circular. Slightly longer than
 the solution of Jan Kort, no empty lists.
 
 A data record with three fields, the central is the value, other
 are pointers.
 
  data Db a = Dd (Db a) a (Db a) deriving Show
 -- (don't try to derive Eq...)
 
 
 dlink constructs a circular list out of a standard list. Cannot
 be empty. The internal fct. dble is the main iterator, which 
 constructs
 a dlist and links it at both ends to prev and foll.
 
  dlink ll = 
   let (hd,lst)=dble ll lst hd
   dble [x] prev foll = 
 let h = Dd prev x foll in (h,h)
   dble (x:xq) prev foll =
 let h=Dd prev x nxt
 (nxt,lst) = dble xq h foll
 in (h,lst)
   in hd
 
 You might add some navigation utilities, e.g.
 
  left  (Dd a _ _) = a
  right (Dd _ _ a) = a
  val   (Dd _ x _) = x
 
 etc. At least you don't need Monads nor Zippers. Keith Wansbrough
 proposes his article. I don't know it, when you find it please
 send me the references. But there are previous works, see the
 article published in Software 19(2), (1989) by Lloyd Allison,
 "Circular programs and self-referential structures".
 
 
 Jerzy Karczmarczuk
 Caen, France
 
 PS. Oh, I see now that the KW article has been found...
 Well, I send you my solution anyway.
 




Re: doubly linked list

2000-04-28 Thread Jerzy Karczmarczuk

Chris Angus:
 
 Would it not be better to tag a start point then we can manipulate this
 easier
 and move it back to a singly linked list etc.
 
 data Db a = Dd (Db a) a (Db a)
   | DStart (Db a) a (Db a)
 
 ...

Well, I am sufficiently old to confess that one of my favourite OO
languages, and the one where I found doubly-linked lists for the first
time was ...

Yes, Simula-67.

Actually *they did* that. A "node" had two sub-classes, the link and the
head, and the link chain was doubly attached to the head. This structure
has been havily used for the maintenance of the co-routine bedlam
exploited in simulation programs.

The idea of double lists was to permit a fast two-directional
navigation,
and the ease of insertion/deletion.

But in Haskell, where the beasts are not mutable:

... Actually, has anybody really used them for practical purposes?

Jerzy Karczmarczuk
Caen, France




Re: doubly linked list

2000-04-28 Thread Marc van Dongen

Jerzy Karczmarczuk ([EMAIL PROTECTED]) wrote:

: But in Haskell, where the beasts are not mutable:
: 
: ... Actually, has anybody really used them for practical purposes?

I have used doubly linked lists in Haskell about four
years ago to implement a queue from which objects could
be added at front/back and deleted anywhere.

A mutable array was used to see if objects were in the queue.
If they were then (Just Ix) to them would be returned
and if they weren't Nothing. The index could then be used
to find the possible previous and next elements in the queue
and change their representations. I cheated a bit because I used
the fact that the possible indices were know in advance so that
I could use an array to represent the member in the queue as
well. It worked well.

I've appended (what I think are the most important) code-fragments
at the end. I don't know if I would do it the same way again; this
was years ago.

Regards,


Marc van Dongen

 initQueue :: Ix i = (LinkedList s i v) - [(i,v)] - ST s (Maybe i,Maybe i)
 initQueue _ []
   = return (Nothing,Nothing)
 initQueue marks ((i,v):ivs)
   = writeArray marks i (Nothing,Nothing,Just v) 
 a2q marks i i ivs

 addToQueue :: Ix i =
   (LinkedList s i v)
  - (Maybe i)
  - (Maybe i)
  - [(i,v)]
  - ST s (Maybe i,Maybe i)
 addToQueue marks fst lst  []
   = return (fst,lst)
 addToQueue marks Nothing_  ijrs
   = initQueue marks ijrs
 addToQueue marks (Just fst) (Just lst) ijrs
   = a2q marks fst lst ijrs

 a2q :: Ix i =
   (LinkedList s i v)
   - i
   - i
   - [(i,v)]
   - ST s (Maybe i,Maybe i)
 a2q _ fst lst []
   = return (Just fst,Just lst)
 a2q marks fst lst ((i,v):ivs)
   = readArray marks i = \(_,_,mbv) -
 case mbv of
   Nothing - readArray marks lst  = \(jpred,_,jv) -
  writeArray marks lst (jpred,Just i,jv)   
  writeArray marks i (Just lst,Nothing,Just v) 
  a2q marks fst i ivs
   _   - a2q marks fst lst ivs

 delFromQueue :: Ix i =
   (LinkedList s i v)
   - (Maybe i)
   - (Maybe i)
   - [i]
   - ST s (Maybe i,Maybe i)
 delFromQueue _  jfstjlst[]
   = return (jfst,jlst)
 delFromQueue marks  jfst@(Just fst) jlst@(Just lst) (i:is)
   = readArray marks i  = 
\(jpred,jsucc,_) -
 writeArray marks i (Nothing,Nothing,Nothing)   
 case jpred of
   Nothing  - case jsucc of
 Nothing  - return (Nothing,Nothing)
 (Just s) - readArray marks s  = \(_,s',r') -
 writeArray marks s (Nothing,s',r') 
 delFromQueue marks jsucc jlst is
   (Just p) - case jsucc of
 Nothing  - readArray marks p  = \(p',_,r') -
 writeArray marks p (p',Nothing,r') 
 delFromQueue marks jfst jpred is
 (Just s) - readArray marks p  = \(p',_,r') -
 writeArray marks p (p',jsucc,r')   
 readArray marks s  = \(_,s',r') -
 writeArray marks s (jpred,s',r')   
 delFromQueue marks jfst jlst is




Re: doubly linked list

2000-04-28 Thread Peter Hancock

 "Jerzy" == Jerzy Karczmarczuk [EMAIL PROTECTED] writes:

 The idea of double lists was to permit a fast two-directional
 navigation,
 and the ease of insertion/deletion.

 But in Haskell, where the beasts are not mutable:

 ... Actually, has anybody really used them for practical purposes?

I think that if you want mutable double lists you would use a
representation with before/after lists.  Perhaps when you no longer
need mutable access (ie just "tape" operations) you can switch
to a representation with backthreading.

I suppose if there are parliaments of crows there may as well
be bedlams of coroutines.  
--
Peter





RE: updating file

2000-04-28 Thread Jan Skibinski


Erik:
 
 You have discovered the essence of monads, ie the difference between the bad
 and ugly world of side-effecting computations and the nice and clean world
 of pure functions. And even using my favourite example (*)!

Let's put it in other words: I knew the difference,
I was just not careful enough. What I often do when
in a midst of debugging is to move a local definition
temporarily to the left margin, just for debugging.
This time I got badly bitten.   

I thought that this was such a spectacular example
that I decided to share it with the world :-). 
 
 
 You say the currentSecond has type Int, so it is a pure value. However, when
 you assume that, you can prove that True equals False. It is not without
 reason that unsafePerformIO is called *unsafe*PerformIO!

Well, I said the same in my post.

 
 You said, "To my distress the clock stopped after the first call to
 `currentSecond'". Well, it is not the clock that stopped, but Haskell that
 assumes that it only has to look at the clock once to compute currentSecond,
 and thereafter immediately return that value everytime currentSecond is
 needed. 

"To my distress the clock stopped .." supposed to be a joke. 
 

Friendly,
Jan






Fw: doubly linked list

2000-04-28 Thread Jan Brosius





  Jerzy Karczmarczuk wrote:

 
  Yes, Simula-67.
 
  Actually *they did* that. A "node" had two sub-classes, the link and the
  head, and the link chain was doubly attached to the head. This structure
  has been havily used for the maintenance of the co-routine bedlam
  exploited in simulation programs.
 
  The idea of double lists was to permit a fast two-directional
  navigation,
  and the ease of insertion/deletion.
 
  But in Haskell, where the beasts are not mutable:
 
  ... Actually, has anybody really used them for practical purposes?
 
  Jerzy Karczmarczuk
  Caen, France
 
 

 Well I want to see the simulation of  a mutable  doubly linked list too.

 The author of  Lout writes in his documentation that after much searching
he
 was compelled

 to use doubly linked C lists.

 In Ocaml there was recently an online English version about using pointers
 in Ocaml

 (if people would like to do this) . I have got yesterday the solution of
 implementing

 doubly linked lists, it was rather short.


 I also wonder how one could simulate objects with mutable state in Haskell.

 Another question : is there any way to interrogate the typechecker from
 within a Haskell program?
 Could this be put on the wishlist?


 Friendly
Jan Brosius







Re: updating file

2000-04-28 Thread Jan Skibinski



On Fri, 28 Apr 2000, Fergus Henderson wrote:

  
  This is all fine and dandy if `currentSecond' is within `where'
  clause, because it will be always evaluated afresh.
 
 It might happen to work with current Haskell implementations,
 but I don't think there's any guarantee of that.

Thanks Fergus for pointing this out. I was playing
by ear: "Does it work in Hugs?" 

I rarely use (if ever) "unsafePerformIO" in any of my code,
but this time the application demanded such a heavy usage
of time stamps that a "lightweight" method of IO unwrapping
seemed to be quite handy. It turned out not to be :-)

Jan







ANN: C-Haskell by anonymous CVS

2000-04-28 Thread Manuel M. T. Chakravarty

For those who prefer the thrill of the latest features over
the safety of a tested release: C-Haskell is now available
via anonymous CVS.  Details at

  http://www.cse.unsw.edu.au/~chak/haskell/c2hs/#cvs

Cheers,
Manuel




Re: doubly linked lists

2000-04-28 Thread Chris Okasaki

The implementation that uses laziness to get
true backpointers seems to have caught everybody's
imagination.  Several people have hinted at
the big weakness of this implementation, but lest
any beginners reading this thread be misled, let me 
just state that weakness explicitly -- it takes O(n) 
time to make even the simplest change to such a list.*

What it boils down to is that this implementation
is only useful when the list is mostly static
(that is, not updated very often).  And, in
many situations where the list *is* mostly static,
an array might be a better choice.

Chris


* Laziness can sometimes save you from paying this
  entire O(n) cost up front, but if you are going
  to end up eventually looking at the entire list,
  you'll eventually pay the entire cost.  Furthermore,
  this O(n) cost cannot be amortized across multiple
  updates -- every update pays an additional O(n).




When is it safe to cheat?

2000-04-28 Thread Jan Skibinski



Facing a risk of being stomped all over again
without reason, I nevertheless post this question
to get to the bottom of things:

When can I safely cheat haskell compiler/interpreter
by pretending that I perform pure computations,
when in fact they are not? Here is a real example,
from my Md5Digest module which works fine in Hugs:

digest :: String - String
digest string
= unsafePerformIO (
marshall_string_ string   = \x1 -
prim_Md5Digest_digest x1  = \x2 -
unmarshall_string_ x2 = \x3 -
return x3
  )


From my naive perspective it should look to Hugs
as a pure function - due to input argument.

If this is correct then

currentSecond dummyInput
= cheat expression involving dummyInput and unsafePerformIO
 
from my previous example should be, by extension, also
safe to use. Correct? Or are there some lurking
surprises that I am not aware of?

Not that I like cheating though :-)

Jan

 






Call for 10 minute slots: Workshop on Generic Programming 2000

2000-04-28 Thread Johan Jeuring

   Workshop on Generic Programming

 http://www.cs.uu.nl/~johanj/wgp2000/wgp2000cfp.html

 6th July 2000

   Ponte de Lima , Portugal



Call for proposals for 10 minutes slots

The one day Workshop on Generic Programming (see the web page above for a
description of the field) will follow on the Mathematics of Program
Construction conference, http://seide.di.uminho.pt/~mpc2000/.  Besides
longer talks on contributed papers, there will be some 10 minutes slots
available for new, controversial, interesting or provocative ideas. 

Submit your proposal for such a 10 minute slot on at most half a page 
to [EMAIL PROTECTED], on or before May 31, 2000.


Johan Jeuring
 Department of Computer Science
  Utrecht University
 P.O.Box 80.089
   NL-3508 TB Utrecht
The Netherlands
  email: [EMAIL PROTECTED]
 url: http://www.cs.uu.nl/~johanj/







RE: When is it safe to cheat?

2000-04-28 Thread Erik Meijer

Hi Jan,

   When can I safely cheat haskell compiler/interpreter
   by pretending that I perform pure computations,
   when in fact they are not?

If the computation is not pure, you cannot pretend it is.

 Here is a real example,
   from my Md5Digest module which works fine in Hugs:

   digest :: String - String
   digest string
 = unsafePerformIO (
 marshall_string_ string   = \x1 -
 prim_Md5Digest_digest x1  = \x2 -
   unmarshall_string_ x2 = \x3 -
 return x3
   )

I gues that for digest it holds that

  s1 == s2
  ==
  digest s1 == digest s2

The only reason that the underlying function is impure is that is allocates
memory to marshall its argument and then calls a C function. These
side-effects don't influence the result of computing digest (it would be
different if prim_Md5Digest_digest would take into account the actual
address of its argument, or the time of day, the current Microsoft
stockprice, ...

   currentSecond dummyInput
   = cheat expression involving dummyInput and unsafePerformIO

This function however *should* return a different answer each time it is
called, otherwise you will get distressed again that the clock stopped yet
again. Some people pay lots of money to stop the time (they get a face-lift,
take mega doses of vitamins, go jogging, or put their corpse in a freezer
after they die). Perhaps we can sell them FP!

Erik





When is it safe to cheat?

2000-04-28 Thread Frank Atanassow

Jan Skibinski writes:
   When can I safely cheat haskell compiler/interpreter
   by pretending that I perform pure computations,
   when in fact they are not? Here is a real example,
   from my Md5Digest module which works fine in Hugs:

I don't understand what is impure about the MD5 example, but the time example
is clearly state-dependant. I think the bottom line is that unsafePerformIO
has no semantics beside the fact that it _forgets_ the effectful semantics of
the inner expression, and since we don't have an operational semantics for
Haskell, you can in principle expect any "bad" use of unsafePerformIO to fail.

For example, even if you try to suspend the evaluation by guarding the
expression with a (), as Nigel explained, a smart compiler could recognize
that a function of type () - a is denotationally equivalent to a constant
of type a.

So what you are really doing in these cases is trying to outsmart the
compiler('s designers), which is IMO a pointless exercise. (Think: "the
compiler as a black box".)

-- 
Frank Atanassow, Dept. of Computer Science, Utrecht University
Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
Tel +31 (030) 253-1012, Fax +31 (030) 251-3791





Re: When is it safe to cheat?

2000-04-28 Thread Lennart Augustsson

Jan Skibinski wrote:

 digest :: String - String
 digest string
 = unsafePerformIO (
 marshall_string_ string   = \x1 -
 prim_Md5Digest_digest x1  = \x2 -
 unmarshall_string_ x2 = \x3 -
 return x3
   )

 From my naive perspective it should look to Hugs
 as a pure function - due to input argument.

 If this is correct then

 currentSecond dummyInput
 = cheat expression involving dummyInput and unsafePerformIO

 from my previous example should be, by extension, also
 safe to use. Correct? Or are there some lurking
 surprises that I am not aware of?

There's a big difference between digest and currentSecond.  The first is really
a mathematical function, the second is not.  I.e., given the same argument to
digest you expect the same result.  This is not the case with currentSecond.
So, currentSecond is not safe to the kind of compiler optimizations that a good
Haskell compiler can do.
You can't make a working currentSecond if you don't involve IO in the type,
that's just the way it is.


--

-- Lennart







Re: When is it safe to cheat?

2000-04-28 Thread Fergus Henderson

On 28-Apr-2000, Jan Skibinski [EMAIL PROTECTED] wrote:
 
   When can I safely cheat haskell compiler/interpreter
   by pretending that I perform pure computations,
   when in fact they are not?

That depends on what degree of safety and portability you want.
If you want the greatest degree of both of those, then currently
the only safe answer is "never".  The Haskell 98 Report does not
standardize `unsafePerformIO', and so there are no guarantees
about whether future implementations will have such a function,
or what it would do, or when it would be safe.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.




Re: When is it safe to cheat?

2000-04-28 Thread Fergus Henderson

On 28-Apr-2000, Frank Atanassow [EMAIL PROTECTED] wrote:
 Jan Skibinski writes:
  When can I safely cheat haskell compiler/interpreter
  by pretending that I perform pure computations,
  when in fact they are not? Here is a real example,
  from my Md5Digest module which works fine in Hugs:
 
 I don't understand what is impure about the MD5 example, but the time example
 is clearly state-dependant. I think the bottom line is that unsafePerformIO
 has no semantics beside the fact that it _forgets_ the effectful semantics of
 the inner expression,

I think you should stop a bit earlier, and just say that the bottom line
is that unsafePerformIO has no semantics, period.  It's certainly not
guaranteed that `unsafePerformIO' will "forget" the effects of the
inner expression.  It might, of course, but then again it might not.

 and since we don't have an operational semantics for
 Haskell, you can in principle expect any "bad" use of unsafePerformIO to fail.

Yes, and you can in principle expect that any use of unsafePerformIO
might be "bad" for some future implementation.

 For example, even if you try to suspend the evaluation by guarding the
 expression with a (), as Nigel explained, a smart compiler could recognize
 that a function of type () - a is denotationally equivalent to a constant
 of type a.

Actually that is not true in general, since the `()' type has two values,
namely `()' and bottom.  But in specific circumstances a compiler could
perform optimizations like that.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.




Re: When is it safe to cheat?

2000-04-28 Thread Fergus Henderson

On 28-Apr-2000, Erik Meijer [EMAIL PROTECTED] wrote:
 Hi Jan,
 
  When can I safely cheat haskell compiler/interpreter
  by pretending that I perform pure computations,
  when in fact they are not?
 
 If the computation is not pure, you cannot pretend it is.

Indeed.  And if the computation were pure, then why would it have `IO'
in its type in the first place? ;-)

  Here is a real example,
  from my Md5Digest module which works fine in Hugs:
 
  digest :: String - String
  digest string
  = unsafePerformIO (
  marshall_string_ string   = \x1 -
  prim_Md5Digest_digest x1  = \x2 -
  unmarshall_string_ x2 = \x3 -
  return x3
)
 
 I gues that for digest it holds that
 
   s1 == s2
   ==
   digest s1 == digest s2
 
 The only reason that the underlying function is impure is that is allocates
 memory to marshall its argument and then calls a C function. These
 side-effects don't influence the result of computing digest

I'm not familiar with Jan's Md5Digest module, or the various functions
that it calls.  But I remain unconvinced that your argument above
need hold in general.  Certainly there is nothing in the Haskell 98 Report
that guarantees it, and last time I looked there was nothing in the
ghc manual that guarantees it either.

A Haskell implementation is free to assume that something of type
`String' has no side effects at all (not just no side effects that
alter the return value), and it may perform optimizations that rely on
this.  If you break that invariant, then the compiler may break your
program.

No doubt it works with the current version of ghc, but who knows what
optimizations some future version of ghc may have?

If implementations are to provide `unsafePerformIO', then really
they ought to document when it can safely be used.  Current
implementations don't do an adequate job of that, AFAIK.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.




Re: When is it safe to cheat?

2000-04-28 Thread Jan Skibinski



On Sat, 29 Apr 2000, Fergus Henderson wrote:

 On 28-Apr-2000, Jan Skibinski [EMAIL PROTECTED] wrote:
  
  When can I safely cheat haskell compiler/interpreter
  by pretending that I perform pure computations,
  when in fact they are not?
 
 That depends on what degree of safety and portability you want.
 If you want the greatest degree of both of those, then currently
 the only safe answer is "never".  The Haskell 98 Report does not
 standardize `unsafePerformIO', and so there are no guarantees
 about whether future implementations will have such a function,
 or what it would do, or when it would be safe.


That's the best answer I got. It should be framed.

If my implementation currently cheats a bit but
it works in Hugs, that's my responsibility and
my possible future headaches. Period.

 
Lennart wrote:

 So, currentSecond is not safe to the kind of compiler optimizations
 that a good Haskell compiler can do.
 You can't make a working currentSecond if you don't involve IO in the
 type, that's just the way it is.

Just out of curiosity: Is your compiler clever enough
to do just what you said? Another words, would this
attached code fail to produce random nonce string (
the idea apparently criticized by Erik, but I do not care
where this came from. It works fine in Hugs-98,
February 2000 release). Humor me please :-)

nonce :: Int - String
nonce size
= take size (filter isAlpha
   (randoms $ mkStdGen (fst $ unsafePerformIO timeFrom1970)))


timeFrom1970 :: IO (Int, Int)
-- you can simulate it somehow, but
-- source code is available to all
-- at www.numeric-quest.com/haskell/bridge/



Erik, Frank and Nigel:

I appreciate your answers too. Please try to understand
that I am searching for clear answers about the limits
of usage of "unsafePerformIO". I do not try to
"outsmart compilers".

I often do just that in my other life - rocking a boat
a little. Really! When I take a dinghy for my
first sail, when the weather is warm, wind gusty,
no baggage and children on boat then I drive her
to her limits to gain some confidence of what can
I do with her.

Jan Skibinski







Changing - to :=

2000-04-28 Thread Mike Jones

All,

Is there a way to define (:=) to be (-) in the context of a do? This would
then allow:

result = do
initialize
vi1 := Vi.create
Vi.setValue vi1 5.5
Vi.enable vi1
vi2 := Vi.create
Vi.setValue vi2 6.0
cond1 (isnt (Vi.enabled vi2)) (Vi.setValue vi2 0.0)
s := Vi.value vi2
return s

The goal is to make the language look Pascal like for those who will use it.

Mike





Re: Changing - to :=

2000-04-28 Thread Thimble Smith

On Fri, Apr 28, 2000 at 07:08:22PM -0700, Mike Jones wrote:
 Is there a way to define (:=) to be (-) in the context of a do?

 The goal is to make the language look Pascal like for those who will use it.

I'd say that goal is ill-concieved.  If you are trying to help
people learn functional programming, then this will only confuse
them.  - in Haskell does not work the same as := in Pascal.  It
is not assignment in the Pascal sense, and it's no good to make
people think that it is.

Tim




silly question on \n

2000-04-28 Thread Sitzman

Hey all.. Gosh, this feels embarrassing to ask.. but how do I get a string
to print out with a carriage return in it? (like using \n in c++)...

I want 
 listBooks :: [Book] - [String]
 listBooks [] = []
 listBooks (Book lang year last first title:bs)
   =
(lang++","++year++","++last++","++first++","++title++"\n"):listBooks bs

But instead it actually prints the \n! Doh ;-)  I tried using single
quotes instead of doubles and it didnt help... Thx much ;-)

-Andrew S.





RE: Changing - to :=

2000-04-28 Thread Mike Jones

Tim,

I am aware that it is not an assignment, but rather a binding to a value.
However, my intent is to model a system that has both declarative and
imperative constructs, then build it in another language. If I can use :=, I
can make it look more like the final system, which is good for
demonstrations to those who know nothing about functional programming, and
in fact don't even know that lambda calculus exists. Furthermore, they have
no desire to know, because they believe that Microsoft tools make the world
go around.

I know, I know, it sucks, but hey, I have to eat. At least they don't care
how I build my prototypes, which means Haskel, and Eiffel.

Thanks for the help.

Mike

-Original Message-
From: Thimble Smith [mailto:[EMAIL PROTECTED]]
Sent: Friday, April 28, 2000 7:26 PM
To: Mike Jones
Cc: [EMAIL PROTECTED]
Subject: Re: Changing - to :=


On Fri, Apr 28, 2000 at 07:08:22PM -0700, Mike Jones wrote:
 Is there a way to define (:=) to be (-) in the context of a do?

 The goal is to make the language look Pascal like for those who will use
it.

I'd say that goal is ill-concieved.  If you are trying to help
people learn functional programming, then this will only confuse
them.  - in Haskell does not work the same as := in Pascal.  It
is not assignment in the Pascal sense, and it's no good to make
people think that it is.

Tim