Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-27 Thread Andrew Pimlott
On Fri, Nov 18, 2005 at 11:37:40AM -0500, Paul Hudak wrote:
 This is a very late response to an old thread...

ditto :-)

  unwind :: Expr - Expr
  unwind (Add e1 e2) = Add (unwind e1) (unwind e2)
  unwind (Rec fe)= x where x = unwind (fe x)
  unwind e   = e

Since this discussion started around observing sharing in the
implementation, I wanted to see whether, by the time we convert your
cunning representation back into an infinite data structure, we have the
sharing we hoped to observe in the first place.

  fe2 e = Add (Const 1) e  -- recursive
  e2 = Rec fe2 -- top-level loop
  e2u = unwind e2   -- infinite

main = walk e4u where
  walk (Add e1 e2) = walk e2 

blows up, showing that we do not.  The problem with unwind seems to be
that the computation of the fixed point keeps calling unwind, which
keeps reconstructing the fixed point:

e2u = unwind e2
= x where x = unwind ((\e - Add (Const 1) e) x)
= Add (Const 1) (unwind x)
= Add (Const 1) (Add (Const 1) (unwind (unwind x)))
= ...

I then tried

unwind (Rec fe)= unwind (fix fe)
fix f = x where x = f x

even though I didn't think it would work: (fix fe) would create a
properly sharing structure, but unwind would unshare it:

e2u = unwind (x where x = ((\e - Add (Const 1) e) x))
 (  = Add (Const 1) x)
= Add (Const 1) (unwind (x where x = Add (Const 1) x))
= Add (Const 1) (Add (Const 1) (unwind (x where x = Add (Const 1) x)))
= ...

This does blow up in ghci, but not in ghc (6.4.1), even without
optimization.  I'm not quite sure why, but anyway I want a version that
exhibits sharing even in any reasonable implementation.

Your message gives the technique (in mapE); we only have to apply it to
unwind.  But there is a problem--your code has a bug!

  mapE :: (Int-Int) - Expr - Expr
  mapE f e = mapE' f e 0 where
mapE' f (Const i)   n = Const (f i)
mapE' f (Add e1 e2) n = Add (mapE' f e1 n) (mapE' f e2 n)
mapE' f (Rec fe)n = Rec (absLoop n (mapE' f (fe (Loop n)) (n+1)))
mapE' f (Loop i)n = Loop i
 
  absLoop :: Int - Expr - Fix Expr
  absLoop n e = \e' -
 let abs (Loop n') | n==n' = e'
 abs (Add e1 e2)   = Add (abs e1) (abs e2)
 abs e = e
 in abs e

  e4 = Rec (\e1- Add (Const 1)
  (Rec (\e2- Add e1 e2))) -- nested loop
  e7 = mapE succ e4
  e8 = Rec (\e1- Add (Const 2)
  (Rec (\e2- Add e1 e2)))
  b4 = e7==e8   -- returns True!

Notice that absLoop does not look inside Rec.  But there could be a Loop
(with the right n) there!  e7 is actually

Rec (\e1- Add (Const 2)
   (Rec (\e2- Add (Loop 0) e2)))

We might also cast a suspicious eye at (==), which spuriously returned
True!

Really, we want absLoop to eliminate all the Loops it can find.  But it
can't, because it only knows the replacement expression for one Loop.
It would be simpler for the Loop just to contain the expression.  To
enable that, I added a constructor Stop that is like Loop, except it
takes an Expr instead of an Int.  I use this constructor for my sharing
unwind as well; Loop is only needed for (==).  (It would probably be
even better to add an annotation type argument to Expr; this could
enable stricter typechecking that would have caught the bug.)

Complete code:

 {-# OPTIONS -fglasgow-exts #-}
 
 data Expr = Const Int
   | Add Expr Expr
   | Rec (Fix Expr)-- implicit loop
   | Loop ID   -- not exported
   | Stop Expr
 
 type Fix a = a - a
 type ID= Int
 
 instance Eq Expr where
   e1 == e2  =
 let eq (Const x) (Const y)   n  =  x == y
 eq (Loop i1) (Loop i2)   n  =  i1 == i2
 eq (Add e1 e2) (Add e1' e2') n  =  eq e1 e1' n  eq e2 e2' n
 eq (Rec fe1) (Rec fe2)   n  =  eq (fe1 (Loop n))
   (fe2 (Loop n)) (n+1)
 eq _ _   n  =  False
 in  eq e1 e2 0
 
 unwind :: Expr - Expr
 unwind e = absStop (unwind' e) where
   unwind' (Add e1 e2) = Add (unwind' e1) (unwind' e2)
   unwind' (Rec fe)= Stop e where e = absStop (unwind' (fe (Stop e)))
   unwind' e   = e
 
 mapE :: (Int-Int) - Expr - Expr
 mapE f e = mapE' e where
   mapE' (Const i)   = Const (f i)
   mapE' (Add e1 e2) = Add (mapE' e1) (mapE' e2)
   mapE' (Rec fe)= Rec (\e - absStop (mapE' (fe (Stop e
   mapE' e@(Stop _)  = e

Replacement for absLoop that removes all Stops, unlike absLoop which
only removed the Loops that its caller owned.

 absStop (Stop e)  = e
 absStop (Add e1 e2)   = Add (absStop e1) (absStop e2)
 absStop e = e

The mapE examples still work ...

 e4 = Rec (\e1- Add (Const 1)
 (Rec (\e2- Add e1 e2))) -- nested loop
 e4u = unwind e4   -- infinite
 e7 = mapE succ e4
 e8 

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-27 Thread jerzy . karczmarczuk

Andrew Pimlott:
//about my highly spiritual essay on lazy computing of PI//: 


In addition to being clever and terribly funny, the conclusion
foreshadows (inspired?) later work on Enron [1].


Come on, it is improbable that Master Simon ever read my essay... 


No,... no comparison.
His work on contracts and the usage of FP for this funny branch of
math which serves to generate (and to destroy...) *real* money, is
based on a very serious formal research.
(So serious that when Simon PJ presented that, people looked at him
so attentively and concentrated, that I saw true physical pain on
their faces, and I wondered whether it would be a bad idea to call
some ambulances...) 

Jerzy Karczmarczuk 



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


[Haskell-cafe] STM, IO and event loops

2005-11-27 Thread Joel Reymont

Folks,

I'm trying to build an event-driven system that includes multiple  
event channels. I would have one channel for network events and  
another one for events sent by other threads. I would like to use STM  
and `orElse` to poll the various event channels.


Is there a reasonably safe way to do this with STM and IO?

The network side of things currently times out after a given number  
of seconds if no input is available but can also throw exceptions.  
I'm having a hard time figuring out how to wrap this in STM.


There's another alternative that I can think of...

My poker bots are launched in separate threads but do not talk to  
each other right now. They just receive events from the network. I  
would like a poker bot to tell others to stop playing and exit, for  
example. I guess I could build poker bots with an event loop that  
reads from a TChan but... I would then need twice as many threads  
since each bot has a socket associated with it and one thread per bot  
would need to read from the socket and push events into the TChan.


Are there any facilities in Haskell that can poll a set of 10k  
descriptors and retrieve input from the first available?


I don't know if I should be concerned with launching 20k threads vs.  
10k threads but it seems that disassociating bots from the network  
has some positive effects. I could compose packets by hand in the  
interpreter and feed them to the TChan by hand to test individual  
bots, for example.


Any advice is appreciated!

Thanks, Joel

--
http://wagerlabs.com/





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


Re[2]: [Haskell-cafe] Monads in Scala, XSLT, Unix shell pipes was Re: Monads in ...

2005-11-27 Thread Bulat Ziganshin
Hello Greg,

Saturday, November 26, 2005, 8:25:38 PM, you wrote:

GW Maybe this is a different topic, but exploring concurrency in Haskell
GW is definitely on my to do list, but this is really a bit of a puzzle.
GW One thing I've been thinking lately is that in functional programming
GW the process is really the wrong abstraction (computation is reduction,
GW not a sequence of steps performed in temporal order). But what is
GW concurrency if their are no processes to run concurrently? I've beren
GW thinking about action systems and non-determinism, but am unsure how
GW the pieces really fit together.

for pure functional computations concurrency is just one of
IMPLEMENTATION mechanisms, and it doesn't appear in abstractions
DEFINITIONS 



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: Dataflow and Comonads was Re: [Haskell-cafe] Monads in Scala, ...

2005-11-27 Thread Bulat Ziganshin
Hello Bill,

Sunday, November 27, 2005, 1:25:59 AM, you wrote:

BW The one downside I found to using dataflow was that most software people
BW seem to be uncomfortable with the lack of identifiable processes doing
BW significant bits of work.  I guess if they they're not floundering
BW around in mutual exclusion, semaphores, deadlock detection and all the
BW other manifestations of unmanaged complexity, they don't feel they've
BW *accomplished* anything (BTW I grew up on Dijkstra, Hoare and Hanson, so
BW I can get away with saying this :-).  Interestingly enough, and perhaps
BW obvious in retrospect, I often found hardware designers to be very
BW comfortable with dataflow computations.

dataflow computers was known at least from 60's as possible
alternative to Neumann architecture with its bottleneck of only one
operation executed each time. they are very natural for chip designers
because real internal processor structure is dataflow, and for
external users (assembler programmers) Neumann architecture is
emulated



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Monads in Scala, XSLT, Unix shell pipes was Re: Monads in ...

2005-11-27 Thread jerzy . karczmarczuk
Bulat Ziganshin: 


for pure functional computations concurrency is just one of
IMPLEMENTATION mechanisms, and it doesn't appear in abstractions
DEFINITIONS 


Well, there are formal aspects of the specification of concurrency as well.
Do you claim that no language has the right to demand *abstractly*  that
evaluating
runtwo (proc1) (proc2) 

mean: launch the two concurrently and process further the first outcome? 

Jerzy Karczmarczuk 


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


Re: [Haskell-cafe] STM, IO and event loops

2005-11-27 Thread Bulat Ziganshin
Hello Joel,

Sunday, November 27, 2005, 2:12:23 PM, you wrote:

JR My poker bots are launched in separate threads but do not talk to
JR each other right now. They just receive events from the network. I  
JR would like a poker bot to tell others to stop playing and exit, for  
JR example.

use async exceptions to do it

JR 10k threads but it seems that disassociating bots from the network
JR has some positive effects. I could compose packets by hand in the  
JR interpreter and feed them to the TChan by hand to test individual  
JR bots, for example.

as Tomasz already suggested, your bots must be parametrized by
action which gets next item, not by Chan/... itself.

current implementation:

bot chan = ... x-readChan chan

must be:

bot reading = ... x-reading
...
top_level = ... chan - newChan
forkIO $ bot (readChan chan)
forkIO $ another_procedure (writeChan chan)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell-cafe] Monads in Scala, XSLT, Unix shell pipes was Re: Monads in ...

2005-11-27 Thread Bulat Ziganshin
Hello jerzy,

Sunday, November 27, 2005, 3:49:07 PM, you wrote:

 for pure functional computations concurrency is just one of
 IMPLEMENTATION mechanisms, and it doesn't appear in abstractions
 DEFINITIONS 

jkiuf Well, there are formal aspects of the specification of concurrency as 
well.
jkiuf Do you claim that no language has the right to demand *abstractly*  that
jkiuf evaluating
jkiuf runtwo (proc1) (proc2) 

jkiuf mean: launch the two concurrently and process further the first outcome? 

for SPECIFICATION of pure functional computation? ;)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: Re[2]: [Haskell-cafe] Monads in Scala, XSLT, Unix shell pipes was Re: Monads in ...

2005-11-27 Thread Greg Woodhouse
--- Bulat Ziganshin [EMAIL PROTECTED] wrote:

 Hello Greg,
 
 for pure functional computations concurrency is just one of
 IMPLEMENTATION mechanisms, and it doesn't appear in abstractions
 DEFINITIONS 
 

I suppose it depends a bit on the question you're asking. A
multiprocessor, considered as a whole, might be a platform upon which
you wish to implement a functional language. And in a certain sense,
what you do with those processors is an implementation issue. But what
I'm after is compositionality. I have in mind message based physically
distributed systems, where individual components can be thought of as
having well-defined semantics from which the semantics of the system as
a whole can be defined. It's not at all clear (to me, anyway) how to do
this. In a physically distributed system, it seems natural to think of
the other processors, together with the bus(es) or network interfaces
as providing part of the environment, and this leads naturally to the
idea of using a theoretical tool like monads or continuations to model
one of these components -- but that doesn't (obviously, at least)
lead to compositional semantics becsuse of the obvious asymmetry.

By way of background, a project I had been working on (untitl the
project was cancelled) was something I dubbed an interface compiler.
I had developed a number of HL7 interfaces in a traditional imperative
language (HL7, or Health Level 7, is an application protocol used in
healthcare). These interfaces were virtually identical in most
respects, so I set out to build a generic engine that would abstract
away from the details of each interface. I was successful and easily
re-implemented the interfaces I had already written using the new
engine. But a little reflection lead me to conclude that this template
driven approach was really higher order programming in disguise
(another factor leading to my renewed interest in functional
programming). Okay, that's fine as far as it goes, but it suffers from
a severe limitation: the computational model is a single network node
communicvating with its environment. There is no obvious way (in
functional terms, at least) to go from the semantics of the subsystems
running on each node to the semantics of the system as a whole. An idea
that I've considered, but not really attempted to elaborate, is to
generate code for the whole system *as a unit*. In retrospect, I see
that this is essentially an attempt to move to the setting you
describe, in which concurrency is simply a design issue.

I have not yet read Misra's monograph (I hope I got that right -- I'm
visiting family and away from my library), but I'm attracted to the
idea that concurrency should not be a design issue and, by
extension(?), that the process is not fundamental. (After all, is it
not an artifact of the operating system?) This strikes a chord with me,
because computation in functional languages is a matter of reduction,
not sequential execution of statements (commands, really). I've been
attracted to reactive systems because they, too, seem to provide a path
to moving beyond the process abstraction, and because I've been working
on TCP/IP based applications for years, and find it all quite
fascinating. But, in a fundamental sense, reactive systems seem to
represent a step in the *opposite* direction. After all, the
appropriate program logic here seems to be temporal logic -- hardly
natural from a functional perspective!

I should apologize (no longer in advance) for the stream of
consciousness nature of this post. Think of it as an attempt to pull
together a few seemingly (or maybe not so seemingly) unrelated threads
from my earlier posts.


===
Gregory Woodhouse  [EMAIL PROTECTED]


Interaction is the mind-body problem of computing.

--Philip Wadler











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


[Haskell-cafe] Shortening if-then-else

2005-11-27 Thread tpledger
Arjan van IJzendoorn wrote:
 |  Is there a shorter way to write the if-then-else part
below?
 | if (cmdType cmd) /= (CmdSitError Server)
 |then return $ Just seat_num
 |else return Nothing
 |
 | return $ if cmdType cmd /= CmdSitError Serv
 |  then Just seat_num else Nothing


There's a subtle change in semantics when we move the 'if'
inside the 'return'.

The original code requires the condition to be evaluated as
part of the do-expression's monad's structure, but the
translated code defers it.

'return $! if ...' would be closer to the original.

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


Re: Re[2]: [Haskell-cafe] Monads in Scala, XSLT, Unix shell pipes was Re: Monads in ...

2005-11-27 Thread Bill Wood
(I'm going to do a lazy permute on your stream of consciousness; hope it
terminates :-).

I think the Rubicon here is the step from one to many -- one
function/procedure to many, one thread to many, one processor to
many, ... .  Our favorite pure functions are like the Hoare triples and
Dijkstra weakest preconditions of the formal methods folks in that the
latter abstract from the body of a procedure to the input-output
relation it computes; both the function and the abstracted procedure are
atomic and outside of time.  After all, aren't referential
transparency and copy rule all about replacing a function body with
its results?  Well, as soon as there are two or more
functions/procedures in the same environment, the prospect of
interaction and interference arises, and our nice, clean,
*comprehensible* atemporal semantics get replaced by temporal logic,
path expressions, trace specifications, what have you.  Some notion of
process is inevitable, since now each computation must be treated as an
activity over time in order to relate events that occur doing the
execution of one computation with the events of another.

Functional programming gives us the possibility of using algebra to
simplify the task of reasoning about single programs.  Of course,
non-functional procedures can also be reasoned about algebraically,
since a procedure P(args) that hammers on state can be adequately
described by a pure function f_P :: Args - State - State.  The problem
is, of course, that the state can be large.

But the functional paradigm offers some hope for containing the
complexity in the world of many as it does in the world of one. I think
combining formalisms like Hoare's CSP or Milner's CCS with computations
gives us the possibility of doing algebra on the temporal event
sequences corresponding to their interactions; the hope is that this is
simpler than doing proofs in dynamic or temporal logic.  Using
functional programs simplifies the algebraic task by reducing the size
of the set of events over which the algebra operates -- you consider
only the explicitly shared parameters and results, not the implicitly
shared memory that can couple non-functional procedures.

It is conceivable that you can get your compositionality here as well.
Suppose we package computations with input-output parameter
specifications and CSP-like specifications of the pattern of event
sequences produced when the computation executes.  It may be possible to
reason about the interactions of the event sequences of groups of
packages, determine the event sequences over non-hidden events provided
by the composite system, etc.

As far as Bulat's comment goes, I'm mostly in agreement.  My dataflow
view was really driven by the intuition that a functional program can be
described by a network of subfunctions linking outputs to inputs; cross
your eyes a little and voila!  A dataflow network.  And if we're smart
enough to make a compiler do that, why bother the programmer?  But
you're not talking about analyzing a function into a
parallel/concurrent/distributed implementation; rather, you're
interested in synthesizing a temporal process out of interacting
computations.

The temporal aspect won't go away.  And that's the problem.

 -- Bill Wood


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