RE: [Haskell-cafe] Re: Properties of optimizer rule application?

2008-01-17 Thread Simon Peyton-Jones

| Ok, this was a bad example. Try this one:
|project . project . foo
|  with the rules
|project (project x) = project x
|project (foo x) = projectFoo x
|
| Both rules can be applied to the expression, but you get one fusion more,
| if you use the first one first. Let me guess, in order to solve that, I
| should restrict the first rule to an earlier phase than the second rule.

As you point out, this set of rules is not confluent:
project (project foo)
can reduce to
---  project (projectFoo x)
or to
--- projectFoo x
depending on the order of application.

The conventional solution is not to apply the rules very carefully (which is 
extremely hard in general), but rather to complete the rules, by adding
project (projectFoo x) = projectFoo x

Now it doesn't matter which order you apply them in.

You can do this by hand, although it'd be quite a nice thing to automate it in 
GHC.


| To give a precise example: If I have a sequence of 'map's
|   map f0 . map f1 . ... . map fn
|  then there is some length where this is no longer collapsed to a single
| 'map'?

(a) GHC tries to do as much as possible in a single iteration of the simplifer; 
I think it uses an outermost-first strategy for this.

(b) For each phase it runs the simplifier until nothing changes, or a maximum 
of N times, where N is settable by a command-line-flag 
-fmax-simplifier-iterations.  After N it stops running that phase, even if the 
simplification has not terminated.

| However then I wonder, how it is possible to make the compiler to
| go into an infinite loop by the rule
|
|loop   forall x,y.  f x y = f y x

Yes, it's possible.  Remember (a) does as much as possible, which in your 
rule means rather a lot.


In this thread Roman and I have described stuff that isn't in the manual.  
Henning, would you feel like elaborating the Wiki page
http://haskell.org/haskellwiki/GHC/Using_rules
(which already has a lot of info) to reflect what you've learned?  That way 
it's preserved for others.

thanks

Simon

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


[Haskell-cafe] Re: announcing darcs 2.0.0pre2

2008-01-17 Thread Simon Marlow

David Roundy wrote:

On Thu, Jan 03, 2008 at 11:11:40AM +, Simon Marlow wrote:

Anyhow, could you retry this test with the above change in methodology,
and let me know if (a) the pull is still slow the first time and (b) if
it's much faster the second time (after the reverse unpull/pull)?
I think I've done it in both directions now, and it got faster, but still 
much slower than darcs1:


$ time darcs2 unpull --from-tag 2007-09-25 -a
Finished unpulling.
58.68s real   50.64s user   6.36s system   97% darcs2 unpull --from-tag 
2007-09-25 -a

$ time darcs2 pull -a ../ghc-darcs2
Pulling from ../ghc-darcs2...
Finished pulling and applying.
53.28s real   44.62s user   7.10s system   97% darcs2 pull -a ../ghc-darcs2

This is still an order of magnitude slower than darcs1 for the same 
operation.  (these times are now on the local filesystem, BTW)


I've recently found the problem leading to this slowdown (I believe) and
get about an order-of-magnitude improvement in the speed of a pull of 400
patches in the ghc repository.  It turned out to be an issue that scaled
with the size (width) of the repository, not with the number of patches
(which had been the obvious suspect), which was causing trouble when
applying to the pristine cache.

At this point, darcs-2 outperforms darcs-1 on most tests that I've tried,
so it'd be a good time to find some more performance problems, if you
can... and I don't doubt that there are more out there.


Certainly a lot faster, nice work!  Though it's still not as fast as 
darcs-1 here.  New figures:


$ time darcs2 unpull --from-tag 2007-09-25 -a
Finished unpulling.
18.83s real   15.27s user   1.53s system   89% darcs2 unpull --from-tag 
2007-09-25 -a

$ time darcs2 pull ../ghc-darcs2-other -a
Finished pulling and applying.
10.38s real   7.69s user   1.50s system   88% darcs2 pull ../ghc-darcs2-other -

I repeated the darcs-1 timings for comparison:

$ time darcs unpull --from-tag 2007-09-25 -a
Finished unpulling.
8.04s real   7.14s user   0.90s system   99% darcs unpull --from-tag 
2007-09-25 -a

$ time darcs pull ~/ghc-HEAD -a
Finished pulling and applying.
7.90s real   4.90s user   0.98s system   74% darcs pull ~/ghc-HEAD -a

In this case darcs-1 is pulling more patches (530 vs. 400), because I'm 
using the latest GHC HEAD repo.  Also the darcs-1 repository being pulled 
from is on a different, NFS mounted, filesystem, whereas the darcs-2 
timings were made using repos on the same local filesystem.  In all cases I 
tried things a few times to let caches etc. fill up.


Can you repeat these?

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


Re: [Haskell-cafe] First go at reactive programming

2008-01-17 Thread Levi Stephen

Hi,

Below is a version that was aimed at getting rid of the (Handle,IO 
(Request a)) tuples and as a result made it easier to remove the IO 
monad from some types, but I don't think it removed it completely from 
any methods.


module Main where

import Control.Applicative
import Control.Concurrent
import Control.Monad

import Data.Reactive

import Network.BSD
import Network.HTTP
import Network

import System.IO

import Text.XHtml.Strict

type RequestHandler = Request - Response

main = runHttpServer helloWorldHandler

helloWorldHandler :: RequestHandler
helloWorldHandler =  Response (2,0,0)  [] . prettyHtml . helloWorldDoc

helloWorldDoc :: Request - Html
helloWorldDoc rq = header  thetitle  Hello World
  +++ body(h1  Hello World +++ p  show rq)

runHttpServer :: RequestHandler - IO a
runHttpServer r = socketServer = runE . fmap (handleConnection r)

socketServer :: IO (Event Handle)
socketServer = withSocketsDo $ do
 (e,snk) - mkEventShow Server
 sock- listenOn (PortNumber 8080)
 forkIO $ forever $ acceptConnection sock $ snk
 return e

handleConnection :: Handle - RequestHandler - IO ()
handleConnection h r =
 handleToRequest h = responseSend h . runRequestHandler r

handleToRequest :: Handle - IO (Result Request)
handleToRequest = receiveHTTP

runRequestHandler :: RequestHandler - Result Request - Result Response
runRequestHandler r rq = rq `bindE` (Right . r)

responseSend :: Handle - Result Response - IO ()
responseSend h rsp = either print (respondHTTP h) rsp  close h

acceptConnection :: Socket - (Handle - IO ()) - IO ThreadId
acceptConnection s k = accept s = \(h,_,_) - forkIO $ k h

instance Stream Handle where
 readLine   h   = hGetLine h = \l - return $ Right $ l ++ \n
 readBlock  h n = replicateM n (hGetChar h) = return . Right
 writeBlock h s = mapM_ (hPutChar h) s = return . Right
 close  = hClose


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


Re: [Haskell-cafe] libmpd-haskell RFC

2008-01-17 Thread Roman Cheplyaka
* Ben Sinclair [EMAIL PROTECTED] [2008-01-16 22:02:40+1100]
   If anybody has already used libmpd-haskell (the darcs repo version)
 or would like to look over it I would appreciate their comments.
 
 Thanks,
 Ben
 
 http://turing.une.edu.au/~bsinclai/code/libmpd-haskell/

I'd like to use it in xmonad extension to control MPD, but since all
extensions live in one package (XMonadContrib), adding new dependencies
is discouraged, so I chose ad-hoc solution using netcat.

-- 
Roman I. Cheplyaka :: http://ro-che.info/
...being in love is totally punk rock...


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


[Haskell-cafe] ghc6.8: hiding uninstalled package?

2008-01-17 Thread Magnus Therning
This might seem like a silly question, but what's the reasoning behind the
following behaviour?

% ghc-pkg list dataenc
/usr/lib/ghc-6.8.2/package.conf:
% ghc --make -hide-package dataenc -isrc UT.hs
ghc-6.8.2: unknown package: dataenc

Hiding an uninstalled package doesn't seem to warrant failing compilation!

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


[Haskell-cafe] Filter by several predicates at once

2008-01-17 Thread Dougal Stanton
Are the functions

 passall, passany :: [a - Bool] - a - Bool
 passall ps v = and $ map ($v) ps
 passany ps v = or $ map ($v) ps

or something similar defined anywhere? Such that one can write

 filter (passany tests) [0..10]
 filter (passall tests) [0..10]

where

 tests = [5, odd]

Or is there a better way of filtering by several predicates for each
value without using

 filter p3 . filter p2 . filter p1

or

 filter (\v - p1 v  p2 v  p3 v) vs

Cheers,

D

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


Re: [Haskell-cafe] Filter by several predicates at once

2008-01-17 Thread Neil Mitchell
Hi

  passall, passany :: [a - Bool] - a - Bool
  passall ps v = and $ map ($v) ps
  passany ps v = or $ map ($v) ps

 or something similar defined anywhere? Such that one can write

Don't think so.

One thing I have often wanted is something like:

or1 a b x = a x || b x
or2 a b x y = a x y || b x y

Then you can do:

filter ((5) `or1` odd) [0..10]
filter ((5) `and1` odd) [0..10]

You can imagine that or1 could get a symbol such as ||#, and or2 could
perhaps be ||## (if # wasn't already really overloaded)

Thanks

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


[Haskell-cafe] Re: Compiling Blobs

2008-01-17 Thread Miguel Vilaça
Peter Verswyvelen wrote:
 I'm trying to build http://www.cs.york.ac.uk/fp/darcs/Blobs using GHC
 6.8.2. It looks like a good Haskell program to learn from.

 So far I managed to modify the source code so it makes use of the new
 HaXML libraries, and after a lot of hacking I could build and link to
 wxHaskell, but my app crashes (I do get a window however, woohoo)

 Maybe someone else managed already?

 Thanks,
 Peter


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
   
Hi Peter,
I have Blobs compiling and running in my machine.
Its an Kubuntu Gutsy with GHC 6.6.1 and HaXml 1.19.SOMETHING (I'm using
a repository version but not yet the current one)
This implies some minor changes that I've as local patches, that I can
send to you as soon as I find how to get a file per patch from the
repository.

The big issue is always to be able to get wxHaskell compiled and working
properly.
I'm currently using a recent (1 or 2 weeks old) version of wxHaskell
from its official repository  (darcs get
http://darcs.haskell.org/wxhaskell) and wxGTK 2.6.3

You can find more information in INblobs (INblobs is done on top of
Bblobs) webpage : http://haskell.di.uminho.pt/jmvilaca/INblobs/
or in the wxHaskell mailing list [EMAIL PROTECTED]

What versions of wxWidgets are you using and in which platform?

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


Re: [Haskell-cafe] Filter by several predicates at once

2008-01-17 Thread Isaac Dupree

Neil Mitchell wrote:

Hi


passall, passany :: [a - Bool] - a - Bool
passall ps v = and $ map ($v) ps
passany ps v = or $ map ($v) ps

or something similar defined anywhere? Such that one can write


nearly; using Prelude:
passall ps v = all ($v) ps
passany ps v = any ($v) ps


One thing I have often wanted is something like:

or1 a b x = a x || b x
or2 a b x y = a x y || b x y


yep, there's the idea of putting Bools in a typeclass that allows you to 
(||) functions-returning-Bool-class-instance for example, which I 
haven't used much but seems like a good idea (though potentially 
confusing, especially if the Prelude-Bool-specific names are reused)


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


Re: [Haskell-cafe] Filter by several predicates at once

2008-01-17 Thread Dougal Stanton
On 17/01/2008, Stuart Cook [EMAIL PROTECTED] wrote:
 On Jan 18, 2008 1:46 AM, Isaac Dupree [EMAIL PROTECTED] wrote:

  nearly; using Prelude:
  passall ps v = all ($v) ps
  passany ps v = any ($v) ps

Yes, thanks Isaac. That should have been obvious, argh...


   passall = swing all
   passany = swing any

 Whether that's any better than the pointwise version is up to you.

I think in this case I will use the explicit version, because I
wouldn't remember how swing worked. What is the motivation for the
name? ;-) (Do I want to hear the answer...?)

D

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


Re: [Haskell-cafe] Haskell and GUI

2008-01-17 Thread Wolfgang Jeltsch
Am Dienstag, 15. Januar 2008 20:42 schrieb Conal Elliott:
 If you can get wxHaskell installed  working, you could try Phooey and/or
 TV.  Both are described on the Haskell wiki and available via darcs and
 Hackage.

And they have the interesting property of being a functional approach to GUI 
programming (similar to FranTk).  Most of the other Haskell GUI toolkits are 
imperative in nature.

And now my shameless plug:  If you can get Gtk2Hs installed and working, you 
could try Grapefruit which is also a functional library.  In addition to 
GUIs, it also supports animated graphics.  At the moment, it’s main downside 
is that it supports only a small set of widgets (buttons, labels, edit fields 
and boxes).  See http://haskell.org/haskellwiki/Grapefruit.

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


[Haskell-cafe] Hamming's Problem

2008-01-17 Thread Jose Luis Reyes F .
Hi,

 

In exercise 2 of http://www.walenz.org/Dijkstra/page0145.html we need to
write a function that holds

 

(1)The value 1 is in the sequence

(2)If x and y are in the sequence, so is f(x,y), where f has the
properties

a.   f(x,y)  x

b.  (y1  y2) = (f(x,y1)f(x,y2))

 

This is a solution for this problem, but an inefficient one

 

hammingff :: [Integer]

hammingff = 1 : merge [ h x y | x - hammingff, y - hammingff ] [ h x y | y
- hammingff, x - hammingff ]

 

h x y = 2*x+3*y

 

merge :: (Ord a) = [a] - [a] - [a]

merge [] xs = xs

merge ys [] = ys

merge (x:xs) (y:ys) = case compare x y of

LT - x : merge xs (y:ys)

GT - y : merge (x:xs) ys

EQ - x : merge xs ys

 

 

anybody  has a better solution?.

 

Thanks

Jose

 

 

 

 

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


Re: [Haskell-cafe] Filter by several predicates at once

2008-01-17 Thread Stuart Cook
On Jan 18, 2008 1:46 AM, Isaac Dupree [EMAIL PROTECTED] wrote:
 Neil Mitchell wrote:
  Hi
 
  passall, passany :: [a - Bool] - a - Bool
  passall ps v = and $ map ($v) ps
  passany ps v = or $ map ($v) ps
  or something similar defined anywhere? Such that one can write

 nearly; using Prelude:
 passall ps v = all ($v) ps
 passany ps v = any ($v) ps

See also http://haskell.org/haskellwiki/Pointfree#Swing, which would
let you define

  passall = swing all
  passany = swing any

Whether that's any better than the pointwise version is up to you.


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


Re: [Haskell-cafe] libmpd-haskell RFC

2008-01-17 Thread Don Stewart
roma:
 * Ben Sinclair [EMAIL PROTECTED] [2008-01-16 22:02:40+1100]
If anybody has already used libmpd-haskell (the darcs repo version)
  or would like to look over it I would appreciate their comments.
  
  Thanks,
  Ben
  
  http://turing.une.edu.au/~bsinclai/code/libmpd-haskell/
 
 I'd like to use it in xmonad extension to control MPD, but since all
 extensions live in one package (XMonadContrib), adding new dependencies
 is discouraged, so I chose ad-hoc solution using netcat.
 

We could have multiple extension packages (i.e. xmonadcontrib-network)
for things that touch the network.

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


[Haskell-cafe] Re: Data constructors versus types

2008-01-17 Thread Achim Schneider
Richard A. O'Keefe [EMAIL PROTECTED] wrote:

 I have no idea what get/cc might be, unless it is a mistake for
 call/cc, but that's Scheme, not Lisp.

Erm... yes. I guess it's the part of call/cc that gets the continuation
before calling it.

Actually, I shouldn't be talking about stuff that was used before I was
even planned...


-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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


[Haskell-cafe] Re: Data constructors versus types

2008-01-17 Thread Achim Schneider
Anton van Straaten [EMAIL PROTECTED] wrote:

 [EMAIL PROTECTED] wrote:
  On 2008.01.17 00:58:19 +0100, [EMAIL PROTECTED]
  scribbled 0.9K characters:
  Achim Schneider writes:
  Lisp is actually not really meant to be compiled, but
  interpreted. 
 ...
  Would you mind stopping to spread dubious truths?
 ...
  I don't think it's a dubious truth. 
 
 It's about as accurate as saying Television is actually not really 
 meant to be color, but black and white.

Yes, that about fits... the chroma data still has only half the
resolution of luminosity.

In fact, it wasn't even meant to be a programming language, just a
calculus.

But still, I should have written was meant not is meant.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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


Re: [Haskell-cafe] ghc6.8: hiding uninstalled package?

2008-01-17 Thread Albert Y. C. Lai

Magnus Therning wrote:
This might seem like a silly question, but what's the reasoning behind 
the following behaviour?


% ghc-pkg list dataenc
/usr/lib/ghc-6.8.2/package.conf:
% ghc --make -hide-package dataenc -isrc UT.hs
ghc-6.8.2 : unknown package: dataenc

Hiding an uninstalled package doesn't seem to warrant failing compilation!


I cannot find it, therefore I cannot hide it? XD

The following is fairly widely accepted behaviour:

$ rm phd-thsies
rm: cannot remove `phd-thsies': No such file or directory

If a file is absent and you want it absent, is that an error?

(Now you might get into a long thread debating whether deletion is 
analogous to hiding...)


If I want to hide or delete something, and the computer can't find that 
something, it may be because I have a typo. If the computer remains 
silent about it, I fail to hide or delete the true thing. I want to 
delete phd-thesis, but I typed phd-thsies, and I appreciate the error 
report. If I fail to delete phd-thesis, at worst more people read it and 
be enlightened :) but if I fail to hide a package and I don't know about 
it, the ensuing problems will be much more mysterious.


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


Re: [Haskell-cafe] libmpd-haskell RFC

2008-01-17 Thread Roman Cheplyaka
* Don Stewart [EMAIL PROTECTED] [2008-01-17 08:56:14-0800]
 roma:
  * Ben Sinclair [EMAIL PROTECTED] [2008-01-16 22:02:40+1100]
 If anybody has already used libmpd-haskell (the darcs repo version)
   or would like to look over it I would appreciate their comments.
   
   Thanks,
   Ben
   
   http://turing.une.edu.au/~bsinclai/code/libmpd-haskell/
  
  I'd like to use it in xmonad extension to control MPD, but since all
  extensions live in one package (XMonadContrib), adding new dependencies
  is discouraged, so I chose ad-hoc solution using netcat.
  
 
 We could have multiple extension packages (i.e. xmonadcontrib-network)
 for things that touch the network.

It doesn't really matter -- I hardly imagine amarok user who would agree
to fetchbuild libmpd-haskell in order to use some other network-related
extension.

-- 
Roman I. Cheplyaka :: http://ro-che.info/
...being in love is totally punk rock...


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


Re: [Haskell-cafe] Hamming's Problem

2008-01-17 Thread Calvin Smith
The author of Pugs (Perl6 implemented in Haskell) gives a nice solution
to the problem of generating the Hamming numbers in the following interview:

http://www.perl.com/pub/a/2005/09/08/autrijus-tang.html?page=last
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Compiling Blobs

2008-01-17 Thread Peter Verswyvelen
Sorry guys, this email also got in my personal email box, I did not
mention to send this to the cafe. And with this message this is double
spam, duh.

On Thu, 2008-01-17 at 20:10 +0100, Peter Verswyvelen wrote:
 Hi Miguel!
 
 Thanks for the reply!
 
 Yes, I also took the latest darcs version of wxHaskell, HaXml 1.19.2,
 and polyparse.
 
 I had to do some minor tweaks to the Blobs source code (mainly
 Text.Parse stuff, no big deal really).
 
 I used wxGTK 2.6.4, --with-opengl and --disable-sharing (otherwise I got
 link errors when linking Blobs).
 
 However I'm using GHC 6.8.2 on Fedora 8. BTW what do you think is the
 best distro for doing Haskell development?
 
 Now I just switched from Windows to Linux, so this is all very very new
 to me. However I do like the Linux way of settings things up, so I'm
 planning to dig a bit deeper in the Linux world. Not easy because I know
 a lot about Windows development, so giving that up is hard.
 
 I'll take a look at the website you mentioned.
 
 The fact to you have it running gives me confidance it is possible :)
 
 Cheers,
 Peter
 
 
 On Thu, 2008-01-17 at 14:51 +, Miguel Vilaça wrote:
  Peter Verswyvelen wrote:
   I'm trying to build http://www.cs.york.ac.uk/fp/darcs/Blobs using GHC
   6.8.2. It looks like a good Haskell program to learn from.
  
   So far I managed to modify the source code so it makes use of the new
   HaXML libraries, and after a lot of hacking I could build and link to
   wxHaskell, but my app crashes (I do get a window however, woohoo)
  
   Maybe someone else managed already?
  
   Thanks,
   Peter
  
  
   ___
   Haskell-Cafe mailing list
   Haskell-Cafe@haskell.org
   http://www.haskell.org/mailman/listinfo/haskell-cafe
 
  Hi Peter,
  I have Blobs compiling and running in my machine.
  Its an Kubuntu Gutsy with GHC 6.6.1 and HaXml 1.19.SOMETHING (I'm using
  a repository version but not yet the current one)
  This implies some minor changes that I've as local patches, that I can
  send to you as soon as I find how to get a file per patch from the
  repository.
  
  The big issue is always to be able to get wxHaskell compiled and working
  properly.
  I'm currently using a recent (1 or 2 weeks old) version of wxHaskell
  from its official repository  (darcs get
  http://darcs.haskell.org/wxhaskell) and wxGTK 2.6.3
  
  You can find more information in INblobs (INblobs is done on top of
  Bblobs) webpage : http://haskell.di.uminho.pt/jmvilaca/INblobs/
  or in the wxHaskell mailing list [EMAIL PROTECTED]
  
  What versions of wxWidgets are you using and in which platform?
  
  best
  Miguel Vilaca
  
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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


Re: [Haskell-cafe] Re: Data constructors versus types

2008-01-17 Thread Peter Verswyvelen
 It's about as accurate as saying Television is actually not really 
 meant to be color, but black and white.

Funny, but that is actually correct, since both NTSC and PAL did a lot
of tricks to carry color information using the same infrastructure as
black and white TVs :) Of course that will soon be over when we all go
digital, then we have jaggies and blockies because of
over-compression :) Okay, ff topic.

Cheers,
Peter


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


[Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-17 Thread Dominic Steinitz
Adam Langley agl at imperialviolet.org writes:

 
 BitGet is just an API RFC at the moment, so I'm just describing it
 here - not trying to justify it.
 
 In BitGet there's getAsWord[8|16|32|64] which take a number of bits ($n$) and
 returns the next $n$ bits in the bottom of a Word$x$. Thus, getAsWord8 is what
 you call getBits and, if you had a 48 bit number, you could use getAsWord64 
 and
 the bottom 48-bits of the resulting Word64 would be what you want.
 
 Equally, asking for more than $x$ bits when calling getAsWord$x$ is a mistake,
 however I don't check for it in the interest of speed.
 
 There are also get[Left|Right]ByteString which return the next $n$ bits in a
 ByteString of Word8's. The padding is either at the end of the last byte (left
 aligned) or at the beginning of the first byte (right aligned).
 

Ok so I should be doing something like this. I'm not clear what happens if you
are reading from a socket and not all the input has arrived but I'll think 
about that over the weekend.

Another thought: could e.g. getRightByteString be in the IO monad and then I
don't have to run the Get(?) monad? Or is that a really stupid question?

Dominic.

import qualified Data.ByteString as B
import Data.Word
import IO

import qualified Data.Binary.Strict.BitGet as BG

test =
   do h - openFile foobarbaz ReadMode
  b - B.hGetContents h
  let ebms = test2 b 
  case ebms of
 Left s- return s
 Right bms - return (concat ((map (show . B.unpack) bms)))

test1 =
   do bm1 - BG.getRightByteString 2
  bm2 - BG.getRightByteString 2
  return [bm1,bm2]
  
test2 bs = BG.runBitGet bs test1
  
  





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


[Haskell-cafe] Re: Compiling Blobs

2008-01-17 Thread Peter Verswyvelen
Hi Miguel!

Thanks for the reply!

Yes, I also took the latest darcs version of wxHaskell, HaXml 1.19.2,
and polyparse.

I had to do some minor tweaks to the Blobs source code (mainly
Text.Parse stuff, no big deal really).

I used wxGTK 2.6.4, --with-opengl and --disable-sharing (otherwise I got
link errors when linking Blobs).

However I'm using GHC 6.8.2 on Fedora 8. BTW what do you think is the
best distro for doing Haskell development?

Now I just switched from Windows to Linux, so this is all very very new
to me. However I do like the Linux way of settings things up, so I'm
planning to dig a bit deeper in the Linux world. Not easy because I know
a lot about Windows development, so giving that up is hard.

I'll take a look at the website you mentioned.

The fact to you have it running gives me confidance it is possible :)

Cheers,
Peter


On Thu, 2008-01-17 at 14:51 +, Miguel Vilaça wrote:
 Peter Verswyvelen wrote:
  I'm trying to build http://www.cs.york.ac.uk/fp/darcs/Blobs using GHC
  6.8.2. It looks like a good Haskell program to learn from.
 
  So far I managed to modify the source code so it makes use of the new
  HaXML libraries, and after a lot of hacking I could build and link to
  wxHaskell, but my app crashes (I do get a window however, woohoo)
 
  Maybe someone else managed already?
 
  Thanks,
  Peter
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe

 Hi Peter,
 I have Blobs compiling and running in my machine.
 Its an Kubuntu Gutsy with GHC 6.6.1 and HaXml 1.19.SOMETHING (I'm using
 a repository version but not yet the current one)
 This implies some minor changes that I've as local patches, that I can
 send to you as soon as I find how to get a file per patch from the
 repository.
 
 The big issue is always to be able to get wxHaskell compiled and working
 properly.
 I'm currently using a recent (1 or 2 weeks old) version of wxHaskell
 from its official repository  (darcs get
 http://darcs.haskell.org/wxhaskell) and wxGTK 2.6.3
 
 You can find more information in INblobs (INblobs is done on top of
 Bblobs) webpage : http://haskell.di.uminho.pt/jmvilaca/INblobs/
 or in the wxHaskell mailing list [EMAIL PROTECTED]
 
 What versions of wxWidgets are you using and in which platform?
 
 best
 Miguel Vilaca
 

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


Re: [Haskell-cafe] libmpd-haskell RFC

2008-01-17 Thread Clifford Beshers
A comment on documentation.  I find it very frustrating when libraries are
described as an interface to X, where X is often an acronym that has
multiple definitions on the web.  Lots of clicking got me to 'Music Player
Demon', but no further description or links.  Just a little more
information, say in a top-level README and/or the Haddock docs would be
greatly appreciated.

2008/1/16 Ben Sinclair [EMAIL PROTECTED]:

 Hello all,
  If anybody has already used libmpd-haskell (the darcs repo version)
 or would like to look over it I would appreciate their comments.

 Thanks,
 Ben

 http://turing.une.edu.au/~bsinclai/code/libmpd-haskell/http://turing.une.edu.au/%7Ebsinclai/code/libmpd-haskell/

 -BEGIN PGP SIGNATURE-
 Version: GnuPG v1.4.6 (GNU/Linux)

 iD8DBQFHjeRPDo+byWtWM/kRApQhAJ9eMVQR+Bd5hgmsXSF9rRvVCS8ZxACg15rl
 FuRALK8V7ArBSxR9FvTYUr4=
 =d97o
 -END PGP SIGNATURE-

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


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


Re: [Haskell-cafe] ghc6.8: hiding uninstalled package?

2008-01-17 Thread Magnus Therning
On 1/17/08, Albert Y. C. Lai [EMAIL PROTECTED] wrote:

 Magnus Therning wrote:
  This might seem like a silly question, but what's the reasoning behind
  the following behaviour?
 
  % ghc-pkg list dataenc
  /usr/lib/ghc-6.8.2/package.conf:
  % ghc --make -hide-package dataenc -isrc UT.hs
  ghc-6.8.2 : unknown package: dataenc
 
  Hiding an uninstalled package doesn't seem to warrant failing
 compilation!

 I cannot find it, therefore I cannot hide it? XD

 The following is fairly widely accepted behaviour:

 $ rm phd-thsies
 rm: cannot remove `phd-thsies': No such file or directory

 If a file is absent and you want it absent, is that an error?

 (Now you might get into a long thread debating whether deletion is
 analogous to hiding...)

 If I want to hide or delete something, and the computer can't find that
 something, it may be because I have a typo. If the computer remains
 silent about it, I fail to hide or delete the true thing. I want to
 delete phd-thesis, but I typed phd-thsies, and I appreciate the error
 report. If I fail to delete phd-thesis, at worst more people read it and
 be enlightened :) but if I fail to hide a package and I don't know about
 it, the ensuing problems will be much more mysterious.


Fair enough.  I stumbled on this behaviour because I was writing a makefile
for my unit/quickcheck tests.  I need to make sure that the correct module
is used, hence I need to hide it if it's installed.  I ended up with the
following in order to work around the issue:

ifeq (,$(shell ghc-pkg list dataenc | grep dataenc))
GHCOPTS = -fhpc -isrc
else
GHCOPTS = -fhpc -hide-package dataenc -isrc
endif

% : %.hs
ghc --make $(GHCOPTS) $

Is there a better way to do it?

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


Re[2]: [Haskell-cafe] Filter by several predicates at once

2008-01-17 Thread Bulat Ziganshin
Hello Isaac,

Thursday, January 17, 2008, 5:46:20 PM, you wrote:

 yep, there's the idea of putting Bools in a typeclass that allows you to
 (||) functions-returning-Bool-class-instance for example, which I 
 haven't used much but seems like a good idea (though potentially 
 confusing, especially if the Prelude-Bool-specific names are reused)

-- Datatypes having default values
classDefaults a  where defaultValue :: a
instance Defaults () where defaultValue = ()
instance Defaults Bool   where defaultValue = False
instance Defaults [a]where defaultValue = []
instance Defaults (a-a)   where defaultValue = id
instance Defaults (Maybe a)where defaultValue = Nothing
instance Defaults (a-IO a)where defaultValue = return
instance Defaults a = Defaults (IO a) where defaultValue = return defaultValue
instance Num a = Defaults a   where defaultValue = 0

-- Datatypes that can be checked for default value
classTestDefaultValue awhere isDefaultValue :: a - Bool
instance TestDefaultValue Bool where isDefaultValue = not
instance TestDefaultValue [a]  where isDefaultValue = null
instance Num a = TestDefaultValue a where isDefaultValue = (==0)

infixr 3  
infixr 2  |||

a ||| b | isDefaultValue a = b
| otherwise= a

a  b | isDefaultValue a = defaultValue
| otherwise= b



my code contains countless examples of using these funcs:

1. here it is used to conditionally include options in cmdline:
  [rar, x, arcname]++
  (isAddDir  [-ad])++
  (arcdir  files  [-ap++arcdir])++...

2. here it is used to get list of files where current directory may be
specified as :
   files - dirList (dirName ||| .)

3. here it is used to show file basename or full path if basename is empty:
putStr (takeBaseName file  |||  file)

4. here it's used for conditional code execution:
   do opt_debug command  testMalloc
  ...

5. here it is used to additionally print amount of bad sectors if it's non-zero:
   putStrLn$ show recoverable_sectors++ recoverable errors ++
(bad_sectors   and ++show bad_sectors++ bad sectors)

6. here it's used to create tempfile in current directory unless
temporary directory was explicitly specified in --tempdir option
   let filename = (opt_tempdir command ||| .) / $$temp$$

7. here it is use to apply additional reorder step to sorted list only
if --reorder option was specified
  sorted_diskfiles - (opt_reorder command  reorder) (sort_files command 
diskfiles)

(reorder has type [String] - IO [String])


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: Data constructors versus types

2008-01-17 Thread jerzy . karczmarczuk
Achim Schneider continues to comment the Lisp history: 


In fact, it wasn't even meant to be a programming language, just a
calculus.


There is  comprehensive German article (in English), by Herbert Stoyan,
on this historical issue: 

http://www8.informatik.uni-erlangen.de/html/lisp/histlit1.html 


Stoyan reminds a - currently - not so obvious truth, that something like
functional paradigmatics was not so popular at that time, the second half
of fifties, beginning of sixties. People reasoned rather in terms of
algorithms, and McCarthy was no exception. 


Let's cite Stoyan: To come back to functional programming, it is an
 important fact that McCarthy as mathematician was familiar with
 some formal mathematical languages but did not have a deep,
 intimate understanding of all their details. McCarthy himself has
 stressed this fact (23). His aim was to use the mathematical
 formalismus as languages and not as calculi. This is the root of
 the historical fact that he never took the Lambda-Calculus conversion
 rules as a sound basis for LISP implementation. 


So, I believe it is not so briliant an idea to confound the Church calculus
with Lisp! 

We have also the text of the Master himself, available on-line: 

http://www-formal.stanford.edu/jmc/history/lisp/lisp.html 


The chapter on the prehistory:
http://www-formal.stanford.edu/jmc/history/lisp/node2.html#SECTION000200 
00
begins: 


   My desire for an algebraic list processing language for artificial
   intelligence work on the IBM 704 computer arose in the summer of
   1956 during the Dartmouth Summer Research Project on Artificial
   Intelligence which was the first organized study of AI. During
   this meeting, Newell, Shaw and Simon described IPL 2, a list
   processing language for Rand Corporation's JOHNNIAC... 


So, sorry, but McCarthy since the very beginning thought about making
a usable computer language, not a calculus. When discussing the evolution
of FLPL, the *third* point mentions Church for the first time: 


  c. To use functions as arguments, one needs a notation for
   functions, and it seemed natural to use the -notation of
   Church (1941). I didn't understand the rest of his book,
   so I wasn't tempted to try to implement his more general
   mechanism for defining functions. Church used higher order
   functionals instead of using conditional expressions. ... 

See also the article of Paul Graham: 


http://lib.store.yahoo.net/lib/paulgraham/jmc.ps
=== 


Before somebody once more accuses me of pedantry, or says publicly
here that I am aggressive towards people: 


You know that spreading half-truths, and also plain rubbish on Internet
is extremely easy. Wherever you look, you find plenty of occasions to
err, it suffices to put yourself in a mode of a dead person from the
movie The sixth sense of M. Night Shyamalan, with Bruce Willis, and
Haley Joel Osment. The boy says to the other main personage (unaware of
his own condition) that dead people see only what they WANT to see... 


And somehow the false information spreads easier than the true one. THIS
list, which, independently of the freedom to chat about anything, is still
targeted at serious comp. sci. problems, and I think that the fact
that somebody is young and inexperienced, is not a justification to make
false claims, just because this and that had XXX years less than myself in
order to read some easily available texts. Of course, anybody may say
dubious truths, I am ashamed of myself, but from time to time I explode.
Sorry about this. 



Jerzy Karczmarczuk 



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


Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-17 Thread Adam Langley
On Jan 17, 2008 11:05 AM, Dominic Steinitz
[EMAIL PROTECTED] wrote:

 I'm not clear what happens if you
 are reading from a socket and not all the input has arrived but I'll think
 about that over the weekend.

At the moment, BitGet deals with strict ByteStrings only. One could use it
within a standard Get monad by getting a strict ByteString from the lazy input.
I believe that lazy ByteStrings got fixed a while back so that reading from a
socket doesn't block reading a whole block. (i.e. if you trickle data, byte by
byte, to a socket a lazy ByteString should return a spine of 1 byte strict
ByteStrings.)

A fully lazy BitGet would also be possible, of course, I've just not written it
yet ;)

 Adam Langley agl at imperialviolet.org writes:
 Another thought: could e.g. getRightByteString be in the IO monad and then I
 don't have to run the Get(?) monad? Or is that a really stupid question?

If it were in the IO monad, I guess that you're suggesting that it read from a
handle? If that were the case, the remainder of the last byte would have to be
discarded because one can only read whole bytes from a Handle and there's no
mechanism for pushing back into it.

It's certainly possible to do, but I think a quick wrapper around a BitGet
would be the way to do it. If it's particually desirable I can add it, although
I'll admit that it seems a bit odd and I'm wondering what your use case is.

Cheers


AGL

--
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Compiling Blobs

2008-01-17 Thread Isaac Dupree

Peter Verswyvelen wrote:

However I'm using GHC 6.8.2 on Fedora 8. BTW what do you think is the
best distro for doing Haskell development?


they all suck if you want to be able to try/use the latest stuff, in my 
experience; just install a GHC and cabal stuff in your home directory 
(you can install more than one GHC-version there if you want to test 
things with multiple versions...).  There's a semi-good reason for this: 
distros don't like to package broken things, and usually something 
breaks with each different version of GHC, but not necessarily something 
you're relying on, and as you're doing Haskell development you may be 
able to help fix it.


so that is, you compile (configure) things with --prefix=$HOME (or 
--prefix=$HOME/unix or so if you don't like your home-directory being 
cluttered with names like bin, lib etc.).  and when using cabal you 
also, if it's a system-wide-installed ghc, need to give --user when 
configuring.  And then you add whatever-you-put-for-prefix/bin to your 
path, e.g. in ~/.bashrc adding

PATH=$HOME/bin:$PATH
so that the programs (ghc, happy, alex, xmonad, whatever) will be found 
if you want to run them.


Did I leave anything important out?


now, there might be a distro system that actually worked well for this. 
Maybe in a couple years and once cabal-install is reasonably stable, 
some unconventional distro like GoboLinux or NixOS might meet my 
standards :-)


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


Re: [Haskell-cafe] Re: Data constructors versus types

2008-01-17 Thread Anton van Straaten

[EMAIL PROTECTED] wrote:

 [McCarthy's] aim was to use the mathematical
 formalismus as languages and not as calculi. This is the root of
 the historical fact that he never took the Lambda-Calculus conversion
 rules as a sound basis for LISP implementation.
So, I believe it is not so briliant an idea to confound the Church calculus
with Lisp!


It's difficult to extricate the two, as Lisp  McCarthy's experience 
shows.  The decision to use lambda notation without the accompanying 
semantics would have been fine if Lisp had not also had first-class 
functions.  But with first-class functions, and without lexical scoping 
semantics, Lisp suffered from scoping bugs which were only resolved once 
Lisp's 'lambda' was changed to follow Church's semantics, as Sussman and 
Steele originally did for Scheme.


When CL adopted lexical scoping, it was seen as a choice, but it wasn't 
really much of a choice.  The choice was between continuing with a 
fundamentally buggy language and working around those bugs somehow, or 
fixing it by adopting Church's lexical scoping rules.



Wherever you look, you find plenty of occasions to
err, it suffices to put yourself in a mode of a dead person from the
movie The sixth sense of M. Night Shyamalan, with Bruce Willis, and
Haley Joel Osment. 


I see dead languages...

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


[Haskell-cafe] Reflection.Emit in Haskell

2008-01-17 Thread Cetin Sert
As a .NET (C#/F#) programmer learning Haskell, I would love to know the best 
online sources about run-time compilation etc. like Reflection.Emit in .NET. I 
am making heavy use of this .NET API to compile customized 
(regular-expressions-) FSAs at run-time and want to learn how I might achieve 
the same in Haskell. Book or online article references specific to this issue 
will be highly appreciated ^_^

 

Best Regards,

Cetin Sert

INF 521, 4-6-2

69120 Heidelberg

Germany

 

http://www.corsis.de

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


[Haskell-cafe] Re: Data constructors versus types

2008-01-17 Thread Achim Schneider
[EMAIL PROTECTED] wrote:

 [...]

I heard it somewhere trustworthy. Instinctively, I would guess
somewhere into the direction of Graham, but I'm not sure at all.

On the other hand, you can be absolutely sure that I didn't get it off
the next warez-board nor from Bill Gates. 

The Story, afaicr, went along the lines of Professor writes something
for a cool paper about some calculus, student gets hold of it,
implements it and completely baffles the professor, he didn't ever dare
to think about letting that one run on a computer.

It might be one of those apples that didn't fall off trees while
Newton had his idea about gravity, but then it's a complete, nice
story with a nice morale on its own. 

After all, lisp's history isn't as important for me than its semantics,
and everything I read about it was kind of accidental, it just wasn't
uninteresting enough to skip.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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


[Haskell-cafe] shootout using 6.6?

2008-01-17 Thread Greg Fitzgerald
http://shootout.alioth.debian.org/gp4/haskell.php

Anyone know if the Language Shootout is actually using GHC 6.6 or is that a
typo?

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


Re: [Haskell-cafe] shootout using 6.6?

2008-01-17 Thread Don Stewart
garious:
[1]http://shootout.alioth.debian.org/gp4/haskell.php
 
Anyone know if the Language Shootout is actually using GHC 6.6 or is that
a typo?

It's using 6.6 till the gentoo 6.8 package is more widely distributed.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] STM in F#

2008-01-17 Thread Don Stewart
http://cs.hubfs.net/blogs/hell_is_other_languages/archive/2008/01/16/4565.aspx

I imagine this can only ease the process of learning Haskell, and
broaden the base of possible Haskellers, as more people on using .NET
stuff become familiar with modern typed FP.

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


Re: [Haskell-cafe] STM in F#

2008-01-17 Thread Jonathan Cast

On 17 Jan 2008, at 7:02 PM, Don Stewart wrote:

http://cs.hubfs.net/blogs/hell_is_other_languages/archive/ 
2008/01/16/4565.aspx


I imagine this can only ease the process of learning Haskell, and
broaden the base of possible Haskellers, as more people on using .NET
stuff become familiar with modern typed FP.


Indeed, these days I think the main advantage of Haskell is not the  
feature set (the same features can be used nicely in Perl (well,  
nicely for Perl), or not-so-nicely in Python), but rather, the fact  
that Haskell is *designed* for such things, so it's syntax makes  
things that are verbose in Perl or Python natural.


jcc

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


Re: [Haskell-cafe] Reflection.Emit in Haskell

2008-01-17 Thread Martin Lütke

Cetin Sert schrieb:


As a .NET (C#/F#) programmer learning Haskell, I would love to know 
the best online sources about run-time compilation etc. like 
Reflection.Emit in .NET. I am making heavy use of this .NET API to 
compile customized (regular-expressions-) FSAs at run-time and want to 
learn how I might achieve the same in Haskell. Book or online article 
references specific to this issue will be highly appreciated ^_^


I am not familiar with C# but I think what you looking for is the GHC 
api which allows you to compile haskell expressions at runtime. Look for 
metaplug on hackage 
(http://hackage.haskell.org/cgi-bin/hackage-scripts/package/metaplug-0.1.1).
In its source you ll find an example on how to use the api. You may of 
course use metaplug itself. I must warn you though that the GHC api is 
not the best documented and maintained. Currently (ghc 6.8.1) f.i. it 
seems that reloading modules is broken.
The most official docu is here:  
http://www.haskell.org/haskellwiki/GHC/As_a_library.


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


Re: [Haskell-cafe] ANNOUNCE: HStringTemplate -- An Elegant, Functional, Nifty Templating Engine for Haskell

2008-01-17 Thread Sterling Clover

Graham,
  I'm sort of playing fast and loose with referential transparency  
here, as I actually am with stringTemplateFileGroup as well. They  
both use unsafeIO to do what they want, and in corner cases could  
give silly, though not dangerous results (i.e., in the sense of being  
hazardous to your program, these calls are substantially less  
worrisome than head). stringTemplateFileGroup could conceivably be in  
IO, if it was strict in reading all the files in the directory it was  
passed, but cacheSTGroup would force every access to a group to take  
place in IO, which would make the library somewhat of a pain to work  
with. My semi-justification for this is that its referentially- 
transparent-enough for most use cases, in that just about the only  
thing one would be doing with a StringTemplate result would be  
outputting it again in some form anyway. In my experience, being able  
to hot-edit templates for a live app is a key benefit of a  
templating system, and forcing everything into IO to get that seems  
like an undue burden on end-users.


On the other hand, I'm also open to implementing an IO API that's  
safe and renaming the current functions to something somewhat  
scarier, or moving both them and their IO equivs to distinct modules  
so that end users could choose which to import. A number of options  
seem reasonable here.


--Sterl.

(btw, I fixed the typo you emailed me about in the repo, and also  
made a few other changes I documented at http:// 
fmapfixreturn.wordpress.com/)


On Jan 16, 2008, at 8:19 PM, Graham Fawcett wrote:


On Jan 14, 2008 2:47 AM, Sterling Clover [EMAIL PROTECTED] wrote:

HStringTemplate is a port of Terrence Parr's lovely StringTemplate
(http://www.stringtemplate.org) engine to Haskell.


This is very cool.

Your docs describe a function, cacheSTGroup:

cacheSTGroup :: Int - STGen a - STGen a
Given an integral amount of seconds and a group, returns a group
cached for that span of time. Does not cache misses.

How does this work without breaking referential transparency?
Shouldn't it be in the IO monad if it is time-dependent?

Graham


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


Re: [Haskell-cafe] Reflection.Emit in Haskell

2008-01-17 Thread Peter Verswyvelen

That would be possible, but wouldn't Template Haskell also be an option?

Peter

Martin Lütke wrote:

Cetin Sert schrieb:


As a .NET (C#/F#) programmer learning Haskell, I would love to know 
the best online sources about run-time compilation etc. like 
Reflection.Emit in .NET. I am making heavy use of this .NET API to 
compile customized (regular-expressions-) FSAs at run-time and want 
to learn how I might achieve the same in Haskell. Book or online 
article references specific to this issue will be highly appreciated ^_^


I am not familiar with C# but I think what you looking for is the GHC 
api which allows you to compile haskell expressions at runtime. Look 
for metaplug on hackage 
(http://hackage.haskell.org/cgi-bin/hackage-scripts/package/metaplug-0.1.1).
In its source you ll find an example on how to use the api. You may of 
course use metaplug itself. I must warn you though that the GHC api is 
not the best documented and maintained. Currently (ghc 6.8.1) f.i. it 
seems that reloading modules is broken.
The most official docu is here:  
http://www.haskell.org/haskellwiki/GHC/As_a_library.


regards,
Martin


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


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


Re: [Haskell-cafe] STM in F#

2008-01-17 Thread Peter Verswyvelen

Reminds me of a song, I'm dreaming of a ... dotnet Haskell...

I find it such a petty no real work seems to be done on that. Okay, the 
performance might not be optimal. Okay, you might have two huge 
frameworks that overlap. Okay, using the .NET stuff would mean some kind 
of automatic IO monadic wrapper generator, but surely with the .NET 
reflection support, this would be possible. But look at the advantages...


Of course Haskell is a research language, and avoid success at all 
cost is the goal. But unfortunately, IMHO Haskell does make a lot of 
sense, so...


Ah well, I should stop nagging about this :-)

Jonathan Cast wrote:

On 17 Jan 2008, at 7:02 PM, Don Stewart wrote:

http://cs.hubfs.net/blogs/hell_is_other_languages/archive/2008/01/16/4565.aspx 



I imagine this can only ease the process of learning Haskell, and
broaden the base of possible Haskellers, as more people on using .NET
stuff become familiar with modern typed FP.


Indeed, these days I think the main advantage of Haskell is not the 
feature set (the same features can be used nicely in Perl (well, 
nicely for Perl), or not-so-nicely in Python), but rather, the fact 
that Haskell is *designed* for such things, so it's syntax makes 
things that are verbose in Perl or Python natural.


jcc

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




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


Re: [Haskell-cafe] STM in F#

2008-01-17 Thread Derek Elkins
On Fri, 2008-01-18 at 07:32 +0100, Peter Verswyvelen wrote:
 Reminds me of a song, I'm dreaming of a ... dotnet Haskell...
 
 I find it such a petty no real work seems to be done on that. 

No one is stopping you.

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


Re: [Haskell-cafe] Reflection.Emit in Haskell

2008-01-17 Thread Bulat Ziganshin
Hello Cetin,

Friday, January 18, 2008, 12:52:27 AM, you wrote:
 As a .NET (C#/F#) programmer learning Haskell, I would love to know
 the best online sources about run-time compilation etc. like

hs-plugins (unix-only afair), and GHC-as-a-library

 Reflection.Emit in .NET. I am making heavy use of this .NET API to
 compile customized (regular-expressions-) FSAs at run-time and want
 to learn how I might achieve the same in Haskell. Book or online
 article references specific to this issue will be highly appreciated ^_^

it was Runtime_Compilation page on old Haskell wiki, written by Andrew
Bromage and me. in short, some form of run-time compilation works
without actual compiling code. in particular, RegEx package compiles
regexps on the fly. my own program includes very simple variant of
run-time compiled regexps:

-- Compiled regexpExample
data RegExpr = RE_End --  
 | RE_Anything--  *
 | RE_AnyStr  RegExpr --  '*':bc*
 | RE_FromEnd RegExpr --  '*':bc
 | RE_AnyChar RegExpr --  '?':bc
 | RE_CharChar RegExpr--  'a':bc

-- |Compile string representation of regexpr into RegExpr
compile_RE s  =  case s of
   - RE_End
  *- RE_Anything
  '*':cs | cs `contains` '*' - RE_AnyStr   (compile_RE  cs)
 | otherwise - RE_FromEnd  (compile_RE$ reverse s)
  '?':cs - RE_AnyChar  (compile_RE  cs)
  c  :cs - RE_Char   c (compile_RE  cs)

-- |Check match of string s with regexpr re
match_RE re s  =  case re of
  RE_End- null s
  RE_Anything   - True
  RE_AnyStr   r - any (match_RE r) (tails s)
  RE_FromEnd  r - match_RE r (reverse s)
  RE_AnyChar  r - case s of
- False
 _:xs - match_RE r xs
  RE_Char   c r - case s of
- False
 x:xs - x==c  match_RE r xs

-- |Check match of string s with regexpr re, represented as string
match re {-s-}  =  match_RE (compile_RE re) {-s-}


actually, you will not find anything unusual here. the code for
matching with RegExpr is just constructed at runtime (as tree of
closures) which makes matching quite efficient


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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