[Haskell] sweet bananas, lenses, and other miscellaneous brackets

2005-09-25 Thread Vivian McPhail



Hi,

Just as we can define infix operators as syntactic sugar, 
could we not also have a similar mechanism for programmable fancy 
brackets?

There could be a keyword for the bracket declaration and a 
function definition, in this way ana- and catamorphisms, Template Haskell-like 
syntax, and set notationcould become a regular feature of the language. I 
am more interested in the general idea than the syntax of this specific 
example:

\begin{code}
bracket (( _ )) :: a - Ana a
bracket (| _ |) :: a -Cata a
bracket [ _ | _|]::Char - b 
-Splice --or whatever
bracket {[ _, .. ]} :: [a] - SList a

((( _ ))) :: a - Ana a
(( x )) = Ana x

((| _ |)) :: a - Cata a
(| x |) = Cata x

([ _ | _ |]) :: Char - b - Splice
[ c | t |] = case c of
b 
- doC t
d 
- doD t -- or whatever

-- the idea of this bracket is to create a user-defined 
list-type structure
-- {[ "the" , "lambda" , "calculus" 
]}
--would have the value
--(SCons "the" (SCons "lambda" (SCons 
"calculus" SEmpty)))
({[ _ , .. ]} :: [a] - SList a
{[ [] ]} =sempty
{[ x:xs ]} = scons x {[ xs ]}

\end{code}

Any thoughts?

Vivian



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


Re: [Haskell] Paper: The essence of dataflow programming

2005-09-25 Thread David Menendez
Tarmo Uustalu writes:

| We would like to announce our new paper
| 
| The essence of dataflow programming
| 
| http://cs.ioc.ee/~tarmo/papers/essence.pdf
| 
| which describes a novel comonadic foundation of dataflow computing,
| incl. semantics of dataflow languages a la Lucid or Lustre. The
| central point is that comonads structure the context-dependence in
| dataflow paradigms in much the same way as monads organize
| effects. The paper was specifically written for functional
| programmers (as opposed to semanticists).

This is really cool!

For those who haven't read the above paper yet, it describes how to
structure an interpreter for a dataflow language using comonads, similar
to the way you can structure an interpreter for an impure language using
monads. Inspired, I've tried my hand at implementing some of the example
dataflow functions directly in Haskell. 

This message is literate Haskell code. It uses the arrow syntax in a few
places; these are just examples, so you may comment them out if you do
not have a recent-enough GHCi or an arrow syntax preprocessor.

 {-# OPTIONS -farrows #-}
 module Dataflow where
 import Prelude hiding (sum)
 import Control.Arrow

FIrst, a class for comonads:

 class Functor d = Comonad d where
 extract :: d a - a
 coextend :: (d a - b) - d a - d b

(In the paper, these are counit and cobind.)

We'll also define the injection combinator from Kieburtz's paper[1]:

 (.) :: Functor d = d a - b - d b
 d . a = fmap (const a) d

As a simple example, the environment comonad:

 instance Functor ((,) e) where
 fmap f (e,a) = (e, f a)
 
 instance Comonad ((,) e) where
 extract (e,a) = a
 coextend f d@(e,a) = (e, f d)

This is closely related to the reader monad (in fact they are adjoint).

Given a comonad d, we can also create an arrow Cokleisli d:

 newtype Cokleisli d a b = Cokleisli { runCokleisli :: d a - b }

 instance Comonad d = Arrow (Cokleisli d) where
 arr f = Cokleisli (f . extract)
 
 Cokleisli f  Cokleisli g = Cokleisli (g . coextend f)
 
 first (Cokleisli f) = Cokleisli $ 
  \d - (f (fmap fst d), snd (extract d))

Here is something I did not expect to find: you can *apply* cokleisli
arrows.

 instance Comonad d = ArrowApply (Cokleisli d) where
 app = Cokleisli $ 
  \d - runCokleisli (fst (extract d)) (fmap snd d)

 instance Comonad d = ArrowChoice (Cokleisli d) where
 left = leftApp

Now, I haven't proven that this implementation of app satisfies the
relevant laws, but assuming it does, it raises some questions. Most of
the papers dealing with arrows state that instances of ArrowApply are
equivalent to monads, but cokleisli arrows allow you to do dataflow
programming, which cannot be done with monads. That may or may not be a
contradiction.

One point to consider is that the type Cokleisli d a b (or d a - b)
is isomorphic to Reader (d a) b (or d a - b), and Reader (d a) is
a monad.

Thus:

 instance Functor (Cokleisli d a) where
 fmap f (Cokleisli k) = Cokleisli (f . k)

 instance Monad (Cokleisli d a) where
 return a = Cokleisli (const a)
 
 Cokleisli k = f = Cokleisli $ \d - runCokleisli (f (k d)) d

I don't know whether this is significant or useful.


To describe synchronous dataflow languages (where values can depend on
the past, but not the future), Uustalu and Vene employ the non-empty
list comonad, which I will call History.

 data History a = First a | History a : a
 infixl 4 :
 
 runHistory :: (History a - b) - [a] - [b]
 runHistory f [] = []
 runHistory f (a:as) = run (First a) as
 where
 run az [] = [f az]
 run az (a:as) = f az : run (az : a) as
 
 instance Functor History where
 fmap f (First a) = First (f a)
 fmap f (as : a) = fmap f as : f a
 
 instance Comonad History where
 extract (First a) = a
 extract (as : a) = a
 
 coextend f d@(First a) = First (f d)
 coextend f d@(as : a) = coextend f as : f d

We'll also need a combinator fby, which is short for followed by. In
a dataflow language, you might write:

pos = 0 fby (pos + 1)

Which means that pos is initially zero, and its next value is always the
current value plus one. The fby combinator is easy to define,

 fby :: a - History a - a
 a0 `fby` First a = a0
 a0 `fby` (az : a) = extract az

but defining pos requires recursion.

Thanks to Yampa[2], we know how this sort of thing looks when written in
arrow notation:

 type Hist = Cokleisli History
 
 posA :: Hist a Integer
 posA = proc _ - do
 rec
 x - delay 0 - x + 1
 returnA - x

We can define 'delay' using 'fby'.

 delay :: a - Hist a a
 delay a0 = Cokleisli $ \d - a0 `fby` d

Now we just need a instance for ArrowLoop. This was tricky, but I
eventually managed to reverse-engineer the ArrowLoop instance for
Kleisli arrows and come up with a counterpart.

I rely on two combinators. The first, czip, is from the paper and
expresses the ability to merge two 

GHC-6.4.1 on FreeBSD-amd64 still not ported

2005-09-25 Thread Wilhelm B. Kloke
Though I have reported some sort of success on this in the last days,
I was too early. The ghc-inplace does not work on the target system.
It compiled because I have been too lax in following the instructions.
Here is the report, where the crossport fails on the i386host system:

tar czf ghc-6.4.1-x86_64-unknown-freebsd-hc.tar.gz `cat hc-files-to-go`
tar: ghc-6.4.1/ghc/rts/PrimOps.hc: Cannot stat: No such file or directory
tar: ghc-6.4.1/ghc/rts/StgStartup.hc: Cannot stat: No such file or directory
tar: ghc-6.4.1/ghc/rts/StgStdThunks.hc: Cannot stat: No such file or directory
tar: ghc-6.4.1/ghc/rts/Updates.hc: Cannot stat: No such file or directory
tar: ghc-6.4.1/ghc/rts/Apply.hc: Cannot stat: No such file or directory
tar: ghc-6.4.1/ghc/rts/Exception.hc: Cannot stat: No such file or directory
tar: ghc-6.4.1/ghc/rts/HeapStackCheck.hc: Cannot stat: No such file or directory
tar: ghc-6.4.1/ghc/rts/StgMiscClosures.hc: Cannot stat: No such file or 
directory
tar: ghc-6.4.1/libraries/haskell-src/Language/Haskell/Parser.hs: Cannot stat: 
No such file or directory
gmake: *** [hc-file-bundle] Fehler 1

bash-2.05b$ (cd ghc/rts; gmake PrimOps.o )
../../ghc/compiler/ghc-inplace -H16m -O -H32m -keep-hc-files -static -I. 
-#include Prelude.h -#include Rts.h -#include RtsFlags.h -#include RtsUtils.h 
-#include StgRun.h -#include Schedule.h -#include Printer.h -#include Sanity.h 
-#include STM.h -#include Storage.h -#include SchedAPI.h -#include Timer.h 
-#include Itimer.h -#include ProfHeap.h -#include LdvProfile.h -#include 
Profiling.h -#include Apply.h -fvia-C -dcmm-lint -c PrimOps.cmm -o PrimOps.o
In file included from PrimOps.cmm:28:
/home/wb/Haskell/fptools-i386amd64/ghc-6.4.1/ghc/includes/Cmm.h:288:2: #error 
mp_limb_t != StgWord: assumptions in PrimOps.cmm are now false
gmake: *** [PrimOps.o] Fehler 1

Similar messages for attemps to make other of the failing .hc files.
Perhaps crossporting from a 64bit system is easier. I presume that
once a working ghc is available, life is much easier, as Fedora
Linux-64 does not report problems.
-- 
Dipl.-Math. Wilhelm Bernhard Kloke
Institut fuer Arbeitsphysiologie an der Universitaet Dortmund
Ardeystrasse 67, D-44139 Dortmund, Tel. 0231-1084-257

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


[Haskell-cafe] map in IO

2005-09-25 Thread Tom Hawkins
What is the best way to perform a map inside IO?  I defined the 
following function, but this must be common enough to warrant something 
in the standard library.  What am I missing?


-Tom

mapIO :: (a - IO b) - [a] - IO [b]
mapIO _ [] = return []
mapIO f (x:xs) = do y - f x
ys - mapIO f xs
return (y : ys)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] map in IO

2005-09-25 Thread J. Garrett Morris
the similar function:

mapM :: Monad m = (a - m b) - [a] - m [b]

should do the trick for you, and is in the prelude.

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