Re: fixed point

2003-10-27 Thread Paul Hudak
Thomas L. Bevan wrote:
 Is there a simple transformation that can be applied to all
 recursive functions to render them non-recursive with fix.
Suppose you have a LET expression with a set of (possibly mutually 
recursive) equations such as:

let f1 = e1
f2 = e2
...
fn = en
in e
The following is then equivalent to the above, assuming that g is not 
free in e or any of the ei:

let (f1,...,fn) = fix g
g ~(f1,...,fn) = (e1,...,en)
in e
Note that all recursion introduced by the top-most LET has been removed 
(or, if you will, concentrated into the one application of fix).  This 
transformation will work even if there is no recursion, and even if some 
of the fi are not functions (for example they could be recursively 
defined lazy data structures).

For example:

main1 =
  let rem = \a b - if a  b then a
else rem (a - b) b
  ones = 1 : ones
  x   = 42
  in (rem 42 9, take 3 ones, x)
is equivalent to:

main2 =
  let (rem,ones,x)= fix g
  g ~(rem,ones,x) = (\a b - if a  b then a
 else rem (a - b) b,
 1 : ones,
 42
)
  in (rem 42 7, take 3 ones, x)
and both yield the result (6,[1,1,1],42).

-Paul

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: fixed point

2003-10-27 Thread Josef Svenningsson
On Mon, 27 Oct 2003, Paul Hudak wrote:

 Thomas L. Bevan wrote:
   Is there a simple transformation that can be applied to all
   recursive functions to render them non-recursive with fix.

 Suppose you have a LET expression with a set of (possibly mutually
 recursive) equations such as:

 let f1 = e1
  f2 = e2
  ...
  fn = en
 in e

 The following is then equivalent to the above, assuming that g is not
 free in e or any of the ei:

 let (f1,...,fn) = fix g
  g ~(f1,...,fn) = (e1,...,en)
 in e

 Note that all recursion introduced by the top-most LET has been removed
 (or, if you will, concentrated into the one application of fix).  This
 transformation will work even if there is no recursion, and even if some
 of the fi are not functions (for example they could be recursively
 defined lazy data structures).

This is a very nice technique. As an exercise to the reader I suggest the
following program:

\being{code}
data Tree a = Branch a (Tree (a,a)) | Leaf

cross f (a,b) = (f a,f b)

main1 =
  let mapTree :: (a - b) - Tree a - Tree b
  mapTree = \f tree - case tree of
Branch a t - Branch (f a) (mapTree (cross f) t)
Leaf - Leaf
  in mapTree id (Branch 42 Leaf)
\end{code]

/Josef

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: fixed point

2003-10-27 Thread Paul Hudak
 Also, had a feeling the fix function was related to the Y
 combinator; it seems they're the same thing!
Yes, they're the same in effect, although historically fix is often 
defined recursively or taken as a primitive, whereas Y has its roots in 
the lambda calculus, where it is defined as:

  Y = \f.(\x.f(x x))(\x.f(x x))

which, you will note, is not recursive, yet has the property that Y f = 
f (Y f), so that it is in fact a fixpoint generator.  (You might want to 
try proving this -- it's easy and illuminating.)

Unfortunately, this expression will not type-check in Haskell or ML
because of limitations of the Hindley-Milner type system :-(.  There are 
ways around this, but they involve introducing a data structure to avoid 
problems with infinite types.

  -Paul

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


I/O multiplexing (repost)

2003-10-27 Thread Peter Simons
[ I'm posting this article here again, because the general ]
[ mailing list seems to be closed to non-members, and I'm  ]
[ reading/posting through gmane.org. Pardon me, if you see ]
[ this on both lists, please.  -peter  ]

Hi,

I have a question concerning manual I/O multiplexing in Haskell, or
specifically with GHC. I have written an interface to the C library
ADNS, which performs asynchronous DNS queries. Everything is fine and
dandy, but now comes the hard part:

The function

foreign import ccall adns_beforepoll
:: State-- ADNS context
- Ptr Pollfd   -- space for 'n' Pollfd
- Ptr CInt -- n
- Ptr CInt -- max timeout
- Ptr (Timeval)-- current time
- IO CInt

generates an array of file descriptors, suitable for calling poll(2).
The function

foreign import ccall adns_afterpoll
:: State
- Ptr Pollfd
- CInt
- Ptr (Timeval)
- IO CInt

scans this array (after poll has been called), performs I/O on all
readable/writable sockets, and processes any packets that have been
received.

Obviously, the library wants me to call poll myself, though. But since
poll is not supported by Haskell's run-time system, the call would
block _all_ running threads in my process, not just the thread doing
the DNS resolving.

I have considered the following options to solve this:

 1. Run the DNS resolver in a forkOS thread.

 2. Declare all imported functions to be thread-safe (what they are)
and use forkIO.

 3. Call poll(2) without blocking, then conjure some magic to decide
when to call it again without busy polling.

 4. Register the file descriptors with GHC's internal poll event loop.

Option (1) seems to be straight-forward, but I don't want to rely on
the non-standard forkOS function unless I really have to. The same
goes for (4): This is probably a good solution, but it's not portable
among compilers. (3) works fine, but is unsatisfactory because the
resolver will have comparably large latency times. (I have been
processing DNS queries every, say, second.)

So option (2) seems quite attractive compared to the others ... But
the question is: Would that even work?

Any ideas, thoughts, recommendations?

Peter

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Cast from and to CChar

2003-10-27 Thread Marcin 'Qrczak' Kowalczyk
W licie z pon, 27-10-2003, godz. 20:47, Christian Buschmann pisze:

Prelude Foreign.C castCCharToChar $ castCharToCChar ''
 I would expect that this returns '', but it returns '\252'.

This is the same - instance Show Char displays non-ASCII characters
that way. You get the same effect if you just type ''.

-- 
   __( Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Cast from and to CChar

2003-10-27 Thread John Meacham
On Mon, Oct 27, 2003 at 08:47:41PM +0100, Christian Buschmann wrote:
 Hi!
 I've got following problem. If I enter in ghci following line:
   Prelude Foreign.C castCCharToChar $ castCharToCChar 'ü'
 I would expect that this returns 'ü', but it returns '\252'. Is this the 
 correct behaviour? Or am I doing something wrong? Or are there any 
 problems with language specific characters and CChar?

The problem is a CChar is (most likely) 8 bits while a Haskell Char is a
32 bit unicode value. the correct thing to do to talk unicode values
with C code can depend on what you are trying to do, if you know your
system is utf8 (many are) and don't mind being somewhat unportable, then
the easist thing to do is just hard code that in
http://repetae.net/john/computer/haskell/UTF8.hs will do it. (code
stolen from someone else)

if you want to use the proper locale  settings, then things get
trickier but this should do it for many apps but requires the ffi
http://repetae.net/john/computer/haskell/CWString.hsc

otherwise, you may need to write your own ffi code which uses 'iconv' to
do the proper character set conversion. This is a well known deficiency
in the haskell libraries at the moment...

John

-- 
---
John Meacham - California Institute of Technology, Alum. - [EMAIL PROTECTED]
---
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Polyvariadic Y in pure Haskell98

2003-10-27 Thread oleg

Paul Hudak wrote:

 Suppose you have a LET expression with a set of (possibly mutually 
 recursive) equations such as:

 let f1 = e1
  f2 = e2
  ...
  fn = en
 in e

 The following is then equivalent to the above, assuming that g is not 
 free in e or any of the ei:

 let (f1,...,fn) = fix g
  g ~(f1,...,fn) = (e1,...,en)
 in e


I'm afraid that is not entirely satisfactory: the above expression
uses ... . This implies that we need a meta-language operation --
ellipsis -- to express the mutually recursive fixpoint of several
expressions. In the following, we write the polyvariadic fixpoint
combinator in pure Haskell98, without any ellipsis construct.

The combinator is a translation from Scheme of a polyvariadic fixpoint
combinator. The latter is derived in a systematic simplification
way. It is different from a polyvariadic Y of Christian Queinnec and
of Mayer Goldberg.

Here's the polyvaridic Y implemented entirely in Scheme:
-- (define (Y* . fl)
--  (map (lambda (f) (f))
--   ((lambda (x) (x x))
-- (lambda (p)
--   (map 
-- (lambda (f)
--   (lambda ()
--(apply f
-- (map 
--   (lambda (ff)
-- (lambda y (apply (ff) y)))
--   (p p) 
-- fl)

Its translation to Haskell couldn't be any simpler due to the
non-strict nature of Haskell.

 fix':: [[a-b]-a-b] - [a-b]
 fix' fl = self_apply (\pp - map ($pp) fl)

 self_apply f = f g where g = f g

That's it.

Examples. The common odd-even example:

 test1 = (map iseven [0,1,2,3,4,5], map isodd [0,1,2,3,4,5])
   where
[iseven, isodd] = fix' [fe,fo]
fe [e,o] x = x == 0 || o (x-1)
fo [e,o] x = x /= 0  e (x-1)

A more involved example of three mutually-recursive functions:

test2 = map (\f - map f [0,1,2,3,4,5,6,7,8,9,10,11]) fs
  where
   fs= fix' [\[triple,triple1,triple2] x- x==0 || triple2 (x-1),
 \[triple,triple1,triple2] x- (x/=0)((x==1)|| triple (x-1)),
 \[triple,triple1,triple2] x- (x==2)||((x2) triple1 (x-1))]



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe