Re: [Haskell-cafe] Weird ghci behaviour?

2007-07-23 Thread Philip Armstrong


On Mon, Jul 23, 2007 at 11:46:41AM -0700, Dan Piponi wrote:

Ian said:

Can you please give a complete testcase for the problem you're seeing?


I took my test case and started deleting lines from it to simplify it.
And now I'm not seeing the problem at all and I can't reproduce it,
even though when I originally posted I was getting it repeatably. I'm
either hallucinating or it's a problem that comes up intermittently.
Maybe it's some kind of network time skew issue that has nothing to do
with ghc. If I catch it happening again I'll make sure to do more
investigation.


GHC 6.6 had some kind of memory allocation bug that led to all kind of
weird errors in GHCi. Maybe try 6.6.1 ?

Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] NDP documentation

2007-07-23 Thread Donald Bruce Stewart
bulat.ziganshin:
> Hello Andrew,
> 
> Monday, July 23, 2007, 11:50:32 PM, you wrote:
> 
> > Actually, I was just reading through all the Data Parallel Haskell and
> > Nested Data Parallelism documentation. It says in several places that 
> > "parallel array comprehensions are available since GHC 6.6, but they are
> > broken; please use the development versions; this will be fixed in GHC
> > 6.6.1".
> 
> parallel arrays (GHC.PArr) was implemented at least in ghc 6.4 and my
> program using it was worked fine with 6.4.*, 6.6 and 6.6.1 now. but i
> don't use comprehensions, only !: operator
> 

More documentation on the wiki:

http://haskell.org/haskellwiki/GHC/Data_Parallel_Haskell

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


Re: [Haskell-cafe] NDP documentation

2007-07-23 Thread Bulat Ziganshin
Hello Andrew,

Monday, July 23, 2007, 11:50:32 PM, you wrote:

> Actually, I was just reading through all the Data Parallel Haskell and
> Nested Data Parallelism documentation. It says in several places that 
> "parallel array comprehensions are available since GHC 6.6, but they are
> broken; please use the development versions; this will be fixed in GHC
> 6.6.1".

parallel arrays (GHC.PArr) was implemented at least in ghc 6.4 and my
program using it was worked fine with 6.4.*, 6.6 and 6.6.1 now. but i
don't use comprehensions, only !: operator

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Lazy in either argument?

2007-07-23 Thread Dan Weston
I am trying to get my feet wet with Haskell threads with the following 
problem, inspired by a recent post 
(http://www.haskell.org/pipermail/haskell-cafe/2007-July/029408.html) 
saying that:


> Since there's no way to have a function be lazy in both arguments, the
> implicit convention is to make functions strict in the first arguments
> and, if applicable, lazy in the last arguments. In other words, the
> convention is
>
>   True || _|_ = True   but not  _|_ || True = True
>
>   1 + _|_ = Succ _|_   but not  _|_ + 1 = Succ _|_
>
> Regards,
> apfelmus

Maybe not lazy in both arguments, but how about lazy in either argument?

The idea is to fork a thread for each of the two functions, (||) and 
flip (||), pick the winner, then kill off both threads. I can wrap this 
up in a pure function using unsafePerformIO (given the proof obligation 
that the results of both threads will always be equal where both are 
defined).


The code below seems to work, except for the following problems:

1) Commenting out the type annotation f :: Bool makes the program hang
2) If I replace f = f by f = undefined, I get an annoying print of 
"LazyOr: Prelude.undefined" before it returns the correct value.


Does anyone know why the type annotation is needed in #1, and/or how to 
suppress the error message in #2?


Dan Weston

---
import Control.Monad(when)
import Control.Concurrent(forkIO,killThread)
import Control.Concurrent.Chan(newChan,readChan,writeChan,isEmptyChan)
import Foreign(unsafePerformIO)

f :: Bool
f = f

main = putStrLn . show $ lazyBinaryOp (||) f True

lazyBinaryOp p x y = unsafePerformIO $ do
c  <- newChan
p2 <- forkIO (lazyBinaryOpThread c p x y)
p1 <- forkIO (lazyBinaryOpThread c p y x)
z  <- readChan c
killThread p1
killThread p2
return z

  where

lazyBinaryOpThread c p x y = do
  case (p x y) of True  -> writeChan c True
  False -> writeChan c False

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


Re: [Haskell-cafe] My Haskell ICFP '07 Programming Competition entry

2007-07-23 Thread Donald Bruce Stewart
aslatter:
> Hello,
> 
> I'd just like to call attention to a few recent blog posts containing
> myself and my friend Creighton's entry into the ICFP '07 programming
> competition.  Mainly because I'm looking to find someone who knows
> Haskell and the contest so they can tell me where my bug is :)
> 

There were quite a few Haskell teams this year. Those who were on IRC 
have listed their teams, team members, and final rankings, here:

http://haskell.org/haskellwiki/ICFP_Programming_Contest/Teams_2007

Feel free to add links to code, your team details and the like.

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


[Haskell-cafe] My Haskell ICFP '07 Programming Competition entry

2007-07-23 Thread Antoine Latter
Hello,

I'd just like to call attention to a few recent blog posts containing
myself and my friend Creighton's entry into the ICFP '07 programming
competition.  Mainly because I'm looking to find someone who knows
Haskell and the contest so they can tell me where my bug is :)

Also, if anyone wants to see a Haskell approach towards the contest's
DNA to RNA conversion, here you go.  It's not always idiomatic
HAskell, but that's what happens in a 72 hour contest.

Any feedback would be appreciated.  The bug (I believe) occurs
somewhere in the implementation of "matchpattern", which is in the
fourth URL.

Bellow are the URLs of the Haskell source code (with comments included
as blog posts).  We only got as far as the DNA to RNA conversion
algorithm.

-Antoine

http://panicsonic.blogspot.com/2007/07/icfp-07-post-mortem-i.html
http://panicsonic.blogspot.com/2007/07/icfp-07-post-mortem-ii.html
http://panicsonic.blogspot.com/2007/07/icfp-07-post-mortem-iii.html
http://panicsonic.blogspot.com/2007/07/icfp-07-post-mortem-iv.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Minim interpreter

2007-07-23 Thread Chaddaï Fouché

There was more than "some" bugs, and a lack of strictness that led to
a stack overflow for high values of x... So here is a better version
(not quite there still, but better).

--
Jedaï
{-# OPTIONS -fbang-patterns -funbox-strict-fields #-}
module Minim (Statement (..), Test (..), Program (..), Expr (..), eval) where 
import qualified Data.Map as M
import Data.Char

data Statement = 
Assign String Expr
| Inc String
| Dec String
| Cond Test Statement Statement
| Goto String
| Print Expr
| Nl
| Input String
deriving (Show)

data Test = 
Le Expr Expr
| Eq Expr Expr
| And Test Test
| Or Test Test
| Not Test
deriving (Show)

data Expr =
Str String
| Number !Int
| EVar String
deriving (Eq, Ord)

instance Show Expr where
show (Str s) = s
show (Number i) = show i
show (EVar s) = "Variable : " ++ s

newtype Program = Program ([Statement],[(String,[Statement])])
deriving (Show)
eval :: Program -> IO ()
eval (Program (xs, tags)) =
evalS xs tags M.empty

evalS :: [Statement] -> [(String, [Statement])] -> M.Map String Expr -> IO ()
evalS (s0:ss) tags !context =  
case s0 of
  Assign str expr -> evalS ss tags 
 $ M.insert str (evalE expr context) context
  Inc str -> evalS ss tags $ M.insertWith' inc_expr str undefined context
where
  inc_expr _ !(Number i) = Number $ i + 1
  inc_expr _ _ = error $ "You can't increment "
   ++ str ++ ", it isn't numeric.\n" 
  Dec str -> evalS ss tags $ M.insertWith' dec_expr str undefined context
where
  dec_expr _ !(Number i) = Number $ i - 1
  dec_expr _ _ = error $ "You can't increment "
 ++ str ++ ", it isn't numeric.\n"
  Cond test s1 s2 -> if evalT test context
 then evalS (s1:ss) tags context
 else evalS (s2:ss) tags context
  Goto str -> maybe 
  (error $ "No such tag : " ++ str)
  (\nss -> evalS nss tags context)
  $ lookup str tags
  Print expr -> do putStr (show $ evalE expr context)
   evalS ss tags context
  Nl -> do putStrLn ""
   evalS ss tags context
  Input str -> do input <- getLine
  let expr = if (not $ null input) && all isDigit input
 then Number $ read input
 else Str input
  evalS ss tags $ M.insert str expr context
evalS [] _ _ = return ()

evalE :: Expr -> M.Map String Expr -> Expr
evalE (EVar str) context = maybe 
   (error $ "There's no such variable : " ++ str) 
   id $ M.lookup str context
evalE e _ = e

evalT :: Test -> M.Map String Expr -> Bool
evalT t context = case t of
Eq e1 e2 -> evalE e1 context == evalE e2 context
Le e1 e2 -> evalE e1 context < evalE e2 context
And t1 t2 -> evalT t1 context && evalT t2 context
Or t1 t2 -> evalT t1 context || evalT t2 context
Not t1 -> not $ evalT t1 context
module MinimParser (parseFile) where
import Minim
import Text.ParserCombinators.Parsec hiding (spaces, parseTest, token)
import Text.ParserCombinators.Parsec.Expr
import Text.ParserCombinators.Parsec.Token hiding (symbol)
import Control.Monad

sp :: Parser ()
sp = skipMany $ char ' '

spaces :: Parser ()
spaces = skipMany1 $ char ' '

token :: Parser a -> Parser ()
token p = spaces >> p >> spaces

symbol :: Parser String
symbol = many1 letter

litVar :: Parser Expr
litVar = liftM EVar symbol

litString :: Parser Expr
litString = liftM Str $ between (char '"') (char '"') $ many (noneOf "\"")

litNumber :: Parser Expr
litNumber = return . Number . read =<< many digit

parseExpr :: Parser Expr
parseExpr = litVar <|> litString <|> litNumber

opTable = [ [infixOp "and" And AssocNone, infixOp "or" Or AssocNone],
[Prefix (string "not" >> spaces >> return Not)] ]

infixOp name op assoc = 
Infix (try $ token (string name) >> return op) assoc

parseTest :: Parser Test
parseTest = buildExpressionParser opTable simpleTest

simpleTest :: Parser Test
simpleTest =
between (char '(' >> sp) (sp >> char ')') parseTest <|>
do e1 <- parseExpr
   op <- between sp sp $ oneOf "=<>"
   e2 <- parseExpr
   return $ case op of
  '=' -> Eq e1 e2
  '<' -> Le e1 e2
  '>' -> Le e2 e1

printS :: Parser Statement
printS = liftM Print $ string "print" >> spaces >> parseExpr

inputS :: Parser Statement
inputS = liftM Input $ string "input" >> spaces >> symbol

assignS :: Parser Statement
assignS = do
  var <- symbol
  token $ string "is"
  expr <- parseExpr
  return $ Assign var expr

gotoS :: Parser Statement
gotoS = liftM Goto $ string "goto" >> spaces >> symbol

i

Re: [Haskell-cafe] Re: Code and Perf. Data for Prime Finders (was: Genuine Eratosthenes sieve)

2007-07-23 Thread Melissa O'Neill

Neil Mitchell wrote:
 -O3 is slower than -O2 and -O in ghc? If you want "fast code" then  
specify -O2, not -O3.


Oops. That ought to have been -O2.

But from what I can tell, -O3 is harmless (at least in this case).   
Both invocations generate identical executables, at least for these  
examples on my machine.


Melissa.

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


Re: [Haskell-cafe] Re: Code and Perf. Data for Prime Finders (was: Genuine Eratosthenes sieve)

2007-07-23 Thread Neil Mitchell

Hi


But for the current version of my code, there is still a bit of a
performance gap between our two methods.  Here are the stats I get
(ghc -O3, 2.4GHz x86):


Are you aware that -O3 is slower than -O2 and -O in ghc? If you want
"fast code" then specify -O2, not -O3.

Thanks

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


Re: [Haskell-cafe] Minim interpreter

2007-07-23 Thread Chaddaï Fouché

I wrote such an interpreter though the code is quite ugly due to my
lack of experience in the field as well as with Haskell... It took me
the better part of two hour but mainly because I didn't use Parsec
before this. I would of course be happy of any suggestion to amend it
but a plain rewriting might be best... (even by me ;-) )
There are probably some bugs (in part due to the fuzzy definition of
the language semantics and real syntax).
Here is the beast :
module Minim (the real work is done here)
##
module Minim (Statement (..), Test (..), Program (..), Expr (..), eval) where
import qualified Data.Map as M
import Data.Char

data Statement =
   Assign String Expr
   | Inc String
   | Dec String
   | Cond Test Statement Statement
   | Goto String
   | Print Expr
   | Nl
   | Input String
   deriving (Show)

data Test =
   Le Expr Expr
   | Ge Expr Expr
   | Eq Expr Expr
   | And Test Test
   | Or Test Test
   | Not Test
   deriving (Show)

data Expr =
   Str String
   | Number Int
   | EVar String
   deriving (Eq, Ord)

instance Show Expr where
   show (Str s) = s
   show (Number i) = show i
   show (EVar s) = "Variable : " ++ s

newtype Program = Program ([Statement],[(String,[Statement])])
   deriving (Show)
eval :: Program -> IO ()
eval (Program (xs, tags)) =
   evalS xs tags M.empty

evalS :: [Statement] -> [(String, [Statement])] -> M.Map String Expr -> IO ()
evalS (s0:ss) tags context =
   s0 `seq`
   case s0 of
 Assign str expr -> evalS ss tags
$ M.insert str (evalE expr context) context
 Inc str -> evalS ss tags
$ M.adjust inc_expr str context
where
  inc_expr (Number i) = Number $ i + 1
  inc_expr _ = error $ "You can't increment "
   ++ str ++ ", it isn't numeric.\n"
 Dec str -> evalS ss tags
$ M.adjust dec_expr str context
where
  dec_expr (Number i) = Number $ i - 1
  dec_expr _ = error $ "You can't increment "
   ++ str ++ ", it isn't numeric.\n"
 Cond test s1 s2 -> if evalT test context
then evalS (s1:ss) tags context
else evalS (s2:ss) tags context
 Goto str -> maybe
 (error $ "No such tag : " ++ str)
 (\nss -> evalS nss tags context)
 $ lookup str tags
 Print expr -> do putStr (show $ evalE expr context)
  evalS ss tags context
 Nl -> do putStrLn ""
  evalS ss tags context
 Input str -> do input <- getLine
 let expr = if (not $ null input) && all isDigit input
then Number $ read input
else Str input
 evalS ss tags $ M.insert str expr context
evalS [] _ _ = return ()

evalE :: Expr -> M.Map String Expr -> Expr
evalE (EVar str) context =
   maybe
   (error $ "There's no such variable : " ++ str)
   id
   $ M.lookup str context
evalE e _ = e

evalT :: Test -> M.Map String Expr -> Bool
evalT t context =
   case t of
 Eq e1 e2 -> evalE e1 context == evalE e2 context
 Le e1 e2 -> evalE e1 context < evalE e2 context
 Ge e1 e2 -> evalE e1 context > evalE e2 context
 And t1 t2 -> evalT t1 context && evalT t2 context
 Or t1 t2 -> evalT t1 context || evalT t2 context
 Not t1 -> not $ evalT t1 context
##
module MinimParser
##
module MinimParser (parseFile) where
import Minim
import Text.ParserCombinators.Parsec hiding (spaces, parseTest)
import Text.ParserCombinators.Parsec.Expr
import Text.ParserCombinators.Parsec.Token hiding (symbol)
import Control.Monad

spaces :: Parser ()
spaces = skipMany1 $ char ' '

symbol :: Parser String
symbol = many1 letter

litVar :: Parser Expr
litVar = liftM EVar symbol

litString :: Parser Expr
litString = do char '"'
  s <- many (noneOf "\"")
  char '"'
  return $ Str s

litNumber :: Parser Expr
litNumber = return . Number . read =<< many digit

parseExpr :: Parser Expr
parseExpr = litVar <|> litString <|> litNumber

opTable = [ [Infix (string "and" >> return And) AssocNone,
Infix (string "or" >> return Or) AssocNone],
   [Prefix (string "not" >> return Not)]
 ]

parseTest :: Parser Test
parseTest = buildExpressionParser opTable simpleTest

simpleTest :: Parser Test
simpleTest =
   (do char '('
   spaces
   test <- parseTest
   spaces
   char ')'
   return test
   ) <|>
   do e1 <- parseExpr
  spaces
  op <- oneOf "=<>"
  spaces
  e2 <- parseExpr
  return $ case op of
 '=' -> Eq e1 e2
 '<' -> Le e1 e2
 '>' -> Ge e1 e2

printS :: Parser Statement
printS =
   do
 strin

[Haskell-cafe] Re: Code and Perf. Data for Prime Finders (was: Genuine Eratosthenes sieve)

2007-07-23 Thread Melissa O'Neill

Dave Bayer wrote:

Here is another prime sieve.


It's great to know people are still having fun with this stuff...   
I've added your implementation to the zipfile available at


   http://www.cs.hmc.edu/~oneill/code/haskell-primes.zip

(FWIW, I added specializations for Int and Integer and also  
primesToNth and primesToLimit).


It is about half the length of the fastest contributed code  
(ONeillPrimes)


I think you must be comparing it against an older version of my code  
(the zip file above now contains the most up to date version).  That  
older version actually contained two slightly different copies of the  
algorithm.  The more recent version doesn't.


FWIW, here are the statistics I see for lines of code (ignoring  
comments, blank lines, and compiler directives):


ONeillPrimes: 91 lines, 750 words, 4111 chars, 75628 bytes in .o file
BayerPrimes:  72 lines, 604 words, 2649 chars, 74420 bytes in .o file

So, I'd say the difference is at best 25% in source size and 2% in  
final binary size.


But in reality, a big chunk of my code is a general purpose heap/ 
priority-queue implementation.  If priority queue operations were  
provided as a standard part of Haskell in the same way that lists and  
BSTs are, the statistics would be:


ONeillPrimes: 47 lines, 331 words, 2039 chars



and nearly as fast


Your results are great!  It actually beats early versions of my  
method, before I made a couple of tweaks to improve performance.


But for the current version of my code, there is still a bit of a  
performance gap between our two methods.  Here are the stats I get  
(ghc -O3, 2.4GHz x86):


1*10^6 | 2*10^6 | 3*10^6 | 4*10^6 | 5*10^6 | 6*10^6
---+++++-
  ONeillPrimes1.36 |   3.08 |   4.98 |   6.98 |   9.05 |  11.21
  ONeillPrimes*   1.35 |   3.07 |   4.94 |   6.93 |   8.99 |  11.14
  BayerPrimes 2.18 |   4.49 |   8.99 |  11.18 |  16.60 |  25.77

The "*" version is one that uses ``calcPrimes()'' rather than  
``primes'' to provide its list of primes, and thereby avoids needless  
remembering of the whole list of primes and all the memory that entails.



 until it blows up on garbage collection:


I think that is the biggest issue with many of the other prime  
generators.  At a glance (just looking at RSS with Unix's top  
command), your space usage seems like its about double mine.  And  
when I use ``calcPrimes()'' rather than ``primes'' I barely need any  
space at all (O(sqrt(N)) at the point where I've calculated N  
primes.  The difference there is striking -- a couple of MB vs hundreds.


Anyway, fun stuff...

Melissa.

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


Re: Re[2]: [Haskell-cafe] i need wxHaskell compiled for ghc 6.6.1 on Windows

2007-07-23 Thread shelarcy
Hellow Bulat,

On Sun, 22 Jul 2007 23:20:44 +0900, Eric Kow <[EMAIL PROTECTED]> wrote:
>> > Please try the darcs version
>> >   darcs get http://darcs.haskell.org/wxhaskell
>>
>> thanks. should i follow building instructions from homepage/ directory
>> or there are another one?
>
> I don't remember if this is documented anywhere, sadly:
>
> It's
>
> ./configure
> make
> make install
> make wx
> make wx-install

This instruction isn't perfect when you want to build on Windows
with Visual Studio.


You must add --with-msc option to ./configure command,
if you want to use Visual Studio's dll.

http://wxhaskell.sourceforge.net/building-msc.html


If you want to use GLCanvas or ODBC support, you must modify
wxWidgets' include\wx\msw\setup.h file to enable Option.
To use GLCanvas, we must set "#define wxUSE_GLCANVAS   1"
ODBC support is simillar,

And ODBC support isn't work with Unicode support.
wxWidgets 2.4.2 doesn't support ODBC with Unicode. I think 2.6.4 or
greater can use ODBC support with Unicode. But I can't where is
bug now.


wxWidgets 2.4.2's project file is broken. I point out and attched patch
for this problem in previous mail, so you can build that with patch.

http://www.haskell.org/pipermail/haskell-cafe/2007-July/029438.html


I think wxc-2.6.3 project file depends on wxSTC.
So you must build wxSTC before building wxc on Windows,
if you want to build wxc with wxWidgets 2.6.3, or modifying
wxc-2.6.3 to support greater version (e.g. wxWidgets 2.6.4).

This problem comes from merging wxStyledTextCntrl support.
If we want to avoid it, we must add building option with STC support
or not in project file, or add wxc-withSTC-* project file.

http://sourceforge.net/mailarchive/forum.php?thread_name=d80c8a540701110913h3e28284aua137ef299f259ff6%40mail.gmail.com&forum_name=wxhaskell-users


Best Regards,

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


Re: Re[2]: [Haskell-cafe] i need wxHaskell compiled for ghc 6.6.1 on Windows

2007-07-23 Thread shelarcy
Hello Eric,

I found that wxc Visual Studio Project File for
wxWidgets-2.4.2 is broken now.
And I think that I forgot to notice some awkward point for Windows


So I put newer Windows binary on my project's file space.

http://sourceforge.net/project/showfiles.php?group_id=168626


On Sun, 22 Jul 2007 23:20:44 +0900, Eric Kow <[EMAIL PROTECTED]> wrote:
>> > Please try the darcs version
>> >   darcs get http://darcs.haskell.org/wxhaskell
>>
>> thanks. should i follow building instructions from homepage/ directory
>> or there are another one?

-- 
shelarcy 
http://page.freett.com/shelarcy/

fix_broken-2.4.dpatch
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Another analogy

2007-07-23 Thread Michael Vanier

I submit my own attempts for consideration:

http://www.cs.caltech.edu/~mvanier/hacking/rants/cars.html

Mike

Andrew Coppin wrote:
 From the guy who brought you "data in Haskell is like an undead quantum 
cat", I present the following:


"If programming languages were like vehicles, C would be a Ferrari, C++ 
would be a Porshe, Java would be a BWM and Haskell would be a hovercraft.


It doesn't even have WHEELS! There is no steering wheel, no gearbox, no 
clutch... it doesn't even have BRAKES!!!


It completely turns the rules upside down. I mean, it moves by PUSHING 
AIR. That's just crazy! It even STEERS by pushing air. It sounds so 
absurd, it couldn't possibly work...


...oh, but it DOES work. Very well, actually. In fact, a hovercraft can 
do some things that the others can't. It works on water. It can go 
sideways. It can REALLY turn on the spot."


Insert whitty replies here...

___
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] Another analogy

2007-07-23 Thread Andrew Wagner

Yeah, but to learn how to start the hovercraft, you have to take a
6-week training class.

On 7/23/07, Hugh Perkins <[EMAIL PROTECTED]> wrote:

On 7/23/07, Jonathan Cast <[EMAIL PROTECTED]> wrote:
> >
> > Fine you guys can have Haskell as the hovercraft, not one of those big
ones
> > mind,
>
> How do you get that Haskell has to be small?  It seems a great big
language to
> me.
>

 Well, partly to be controversial, partly because one of those small
zippy 'glade hovers would be just so much fun!  You're saying you'd rather
play around with a big commercial hovercraft like they use across the
Channel?

Let the commercial boys use F# or O'Caml, we can zip around on the 'glade
hover :-)

Oh, and by the way, the 'glade hover in our case is modular and comes with
100% user serviceable parts!


___
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


[Haskell-cafe] Re: Code and Perf. Data for Prime Finders (was: Genuine Eratosthenes sieve)

2007-07-23 Thread Dave Bayer
It appears that at least on gmane, my posts to this thread ended up as
singletons, breaking the thread. Here are the posts:

http://article.gmane.org/gmane.comp.lang.haskell.cafe/26426
http://article.gmane.org/gmane.comp.lang.haskell.cafe/26466


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


[Haskell-cafe] Re: Frustrating experience of a wannabe contributor

2007-07-23 Thread Dave Bayer
Simon Michael  joyful.com> writes:

> 
> Hi Andreas - very good problem report, thanks.
> 
> I have just cleaned up the archive links at 
> http://www.haskell.org/haskellwiki/Mailing_lists a bit. I added the 
> ever-excellent gmane and an overview of all archives.

Ok, this list was crushing my OS X Mail program (not the
coldest beer in the fridge) so I went to a hybrid approach
of reading on gmane, and using NetNewsWire to track the
news feed from gmane.

As a result, I don't have original mail messages to reply
to. I nevertheless want to use my Mail program to
originate posts, in order to cc: interested parties
directly as appears to be the custom, and in hopes that at
least some recipients won't have xs@(x,xt) in Haskell
source code rewritten as xs  (x,xt).

When I send a message "Re: thread" it appears to break the
thread, showing up as a singleton in gmane's thread list.

It appears that I am caught between a rock and a hard
place.

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


Re: [Haskell-cafe] filterFirst

2007-07-23 Thread Dan Weston
If you find it tedious to pass parameters that never change, remember 
that you can access symbols defined in the enclosing environment 
(closure), freeing you from "passing it on" each time:


filterAlpha :: (a -> Bool) -> [a] -> [a]
filterAlpha f = filterAlpha'
  where filterAlpha' [] = []
filterAlpha' (x:xs)
  | f x = x : (filterAlpha' xs)
  | otherwise   = (filterAlpha' xs)

As far as the primed version filterAlpha' is concerned, f is a global 
symbol. The argument list is just used for values that vary.


This will be your friend if the parameter list starts to stack up with 
more and more "reference" or "environment" inputs. It is also easier to 
see that f never changes if it is defined in only one spot.


Later, when you study monads you will notice the same pattern in the 
Reader monad, where the technique is even more valuable.


Dan Weston

Alexteslin wrote:


filterAlpha :: (a -> Bool) -> [a] -> [a]
filterAlpha f [] = []
filterAlpha f (x:xs)
|f x   = x : filterAlpha f xs-- corrected
|otherwise = filterAlpha f xs-- corrected



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


[Haskell-cafe] Re: partitions of a multiset

2007-07-23 Thread DavidA
Here's the approach I would try.
1. Use Data.List.group to group your multiset, eg [1,1,2] -> [[1,1],[2]]
2. Now apply your partitions function to each of the groups
[[1,1],[2]] -> [ [([1,1],[]), ([1],[1]), ([],[1,1])], [([2],[]), ([],[2])] ]
(Actually of course, you can probably write a simpler function to do this)
3. Then you just need a function which can list all possible ways of combining 
the partial partitions (so it's a kind of Cartesian product).

I leave you the pleasure of writing the code.


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


[Haskell-cafe] Re: Code and Perf. Data for Prime Finders (was: Genuine Eratosthenes sieve)

2007-07-23 Thread Dave Bayer

As an exercise, trying to understand the beautiful paper

Stream Fusion
From Lists to Streams to Nothing at All
Duncan Coutts, Roman Leshchinskiy and Don Stewart
http://www.cse.unsw.edu.au/~dons/papers/CLS07.html
http://www.cse.unsw.edu.au/~dons/streams.html

I recoded my prime sieve using a pared down version of their Stream  
datatype; this is the simplest version I could write that  achieves a  
significant speedup.


My reaction to their paper was, if streams are better internally than  
lists, why not code directly in streams? Lists enjoy a serious  
notational advantage in Haskell, but one could imagine a language  
where the list notation was reserved for stream semantics.


My sieve was spending half its time in "merge", so I made only the  
changes necessary to convert "merge" to use streams. My streams are  
infinite, and "merge" can be written to not use Skip, so Step goes away.


Even though "nextx" and "nexty" only have one case now, using case  
statements is significantly faster than using let or where clauses.  
I'm imagining that I read about this somewhere, but if I did, it  
didn't sink in until I was tuning this code. I don't know if this is  
related to fusion optimization, or a general effect.


The timings are


[Integer] -O2  1*10^6   2*10^6   3*10^6   4*10^6   5*10^6
-
ONeillPrimes |  3.338 |  7.320 | 11.911 | 18.225 | 21.785
StreamPrimes |  3.867 |  8.405 | 13.656 | 21.542 | 37.640
BayerPrimes  |  3.960 |  8.940 | 18.528 | 33.221 | 38.568


Here is the code:


{-# OPTIONS_GHC -fglasgow-exts #-}

module StreamPrimes (primes) where

-- stream code

data Stream a = forall s. Stream (s -> (a,s)) s
data AStream a = A a (AStream a) | B (Stream a)

stream :: [a] -> Stream a
stream xs = Stream next xs
  where
next [] = undefined
next (x:xt) = (x,xt)

astream :: [a] -> AStream a
astream [] = undefined
astream (x:xt) = A x $ B $ stream xt

merge :: Ord a => Stream a -> Stream a -> Stream a
merge (Stream nextx vs) (Stream nexty ws) =
Stream next (vt,ws,Left v)
where
(v,vt) = nextx vs
next (xs,ys,Left x) =
case nexty ys of
(y,yt) ->
if   x < y
then (x,(xs,yt,Right y))
else (y,(xs,yt,Left x))
next (xs,ys,Right y) =
case nextx xs of
(x,xt) ->
if   x < y
then (x,(xt,ys,Right y))
else (y,(xt,ys,Left x))

mergeA :: Ord a => AStream a -> AStream a -> AStream a
mergeA (A x xt) ys = A x (mergeA xt ys)
mergeA (B xs)   ys = mergeB xs ys

mergeB :: Ord a => Stream a -> AStream a -> AStream a
mergeB s@(Stream next xs) ys@(A y yt) =
case next xs of
(x,xt) ->
if x < y
then A x (mergeB (Stream next xt) ys)
else A y (mergeB s yt)
mergeB xs (B ys) = B $ merge xs ys

-- Code for venturi :: Ord a => [[a]] -> [a]

root :: Ord a => AStream a -> [AStream a] -> [a]
root (A x xt) yss= x : (root xt yss)
root (B xs) (ys:yst) = root (mergeB xs ys) yst
root _ _ = undefined

pair :: Ord a => [AStream a] -> [AStream a]
pair (x:y:xt) = mergeA x y : (pair xt)
pair _ = undefined

group :: Ord a => [AStream a] -> [AStream a]
group (x:xt) = x : (group $ pair xt)
group _ = undefined

venturi :: Ord a => [[a]] -> [a]
venturi (x:xt) = root (astream x) $ group $ map astream xt
venturi _ = undefined

-- Code for primes :: Integral a => [a]

diff  :: Ord a => [a] -> [a] -> [a]
diff xs@(x:xt) ys@(y:yt) = case compare x y of
LT -> x : (diff  xt ys)
EQ -> (diff  xt yt)
GT -> (diff  xs yt)
diff _ _ = undefined

trim :: Integral a => a -> [a] -> [a]
trim p = let f m x = mod x m /= 0 in filter (f p)

seed :: Integral a => [a]
seed = [2,3,5,7,11,13,17]

wheel :: Integral a => [a]
wheel = drop 1 [ m*j + k | j <- [0..], k <- ws ]
where m  = foldr1 (*) seed
  ws = foldr trim [1..m] seed

multiples :: Integral a => [a] -> [[a]]
multiples ws = map fst $ tail $ iterate g ([], ws)
where g (_,ps@(p:pt)) = ([ m*p | m <- ps ], trim p pt)
  g _ = undefined

primes :: Integral a => [a]
primes = seed ++ (diff wheel $ venturi $ multiples wheel)



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


[Haskell-cafe] NDP documentation

2007-07-23 Thread Andrew Coppin
Actually, I was just reading through all the Data Parallel Haskell and 
Nested Data Parallelism documentation. It says in several places that 
"parallel array comprehensions are available since GHC 6.6, but they are 
broken; please use the development versions; this will be fixed in GHC 
6.6.1".


Can anybody clarify - was this actually fixed? (And shouldn't somebody 
update the Wiki?)


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


Re: [Haskell-cafe] filterFirst

2007-07-23 Thread Alexteslin



apfelmus wrote:
> 
> Alexteslin wrote:
>> filterAlpha :: (a -> Bool) -> [a] -> [a]
>> filterAlpha f [] = []
>> filterAlpha f (x:xs)
>>  |f x= x : filterAlpha xs
>>  |otherwise  = filterAlpha xs
>> 
>> 
>> and i am getting this error message:
>> 
>> Type error in application
>> Expression :filterAlpha xs
>> Type: [b]
>> Dous not match : a -> Bool
> 
>   filterAlpha :: (a -> Bool) -> [a] -> [a]
>   filterAlpha f [] = []
>   filterAlpha f (x:xs)
>  | f x   = x : filterAlpha f xs
>  | otherwise = filterAlpha f xs
> 
> filterAlpha  has two parameters. The first parameter is a function (a ->
> Bool), the second is a list [a]. The error message complains that  xs ,
> which you actidentially gave as first parameter, is a list [a] and not a
> function (a -> Bool).
> 
> Regards,
> apfelmus
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 

Oh silly me.  I defined firstFirst now, thank you.

-- 
View this message in context: 
http://www.nabble.com/filterFirst-tf4131377.html#a11751421
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Another analogy

2007-07-23 Thread Hugh Perkins

On 7/23/07, Jonathan Cast <[EMAIL PROTECTED]> wrote:


>
> Fine you guys can have Haskell as the hovercraft, not one of those big
ones
> mind,

How do you get that Haskell has to be small?  It seems a great big
language to
me.



Well, partly to be controversial, partly because one of those small
zippy 'glade hovers would be just so much fun!  You're saying you'd rather
play around with a big commercial hovercraft like they use across the
Channel?

Let the commercial boys use F# or O'Caml, we can zip around on the 'glade
hover :-)

Oh, and by the way, the 'glade hover in our case is modular and comes with
100% user serviceable parts!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Another analogy

2007-07-23 Thread Jonathan Cast
On Monday 23 July 2007, Hugh Perkins wrote:
> C would be an engine.  You have to add the wheels.  If you use anything but
> a 75.0% mix of gasoline to oil, it explodes.
>
> Fine you guys can have Haskell as the hovercraft, not one of those big ones
> mind,

How do you get that Haskell has to be small?  It seems a great big language to 
me.

> one of those Florida glades ones, like in Lassie, with one guy 
> sitting on it, weaving between the aligators.
>
> Java is a hot air balloon.  Kindof obvious really ;-)
>
> C# is the F1 ferrari.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Another analogy

2007-07-23 Thread Hugh Perkins

C would be an engine.  You have to add the wheels.  If you use anything but
a 75.0% mix of gasoline to oil, it explodes.

Fine you guys can have Haskell as the hovercraft, not one of those big ones
mind, one of those Florida glades ones, like in Lassie, with one guy sitting
on it, weaving between the aligators.

Java is a hot air balloon.  Kindof obvious really ;-)

C# is the F1 ferrari.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Another analogy

2007-07-23 Thread Brent Yorgey

On 7/23/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:


From the guy who brought you "data in Haskell is like an undead quantum
cat", I present the following:

"If programming languages were like vehicles, C would be a Ferrari, C++
would be a Porshe, Java would be a BWM and Haskell would be a hovercraft.

It doesn't even have WHEELS! There is no steering wheel, no gearbox, no
clutch... it doesn't even have BRAKES!!!

It completely turns the rules upside down. I mean, it moves by PUSHING
AIR. That's just crazy! It even STEERS by pushing air. It sounds so
absurd, it couldn't possibly work...

...oh, but it DOES work. Very well, actually. In fact, a hovercraft can
do some things that the others can't. It works on water. It can go
sideways. It can REALLY turn on the spot."

Insert whitty replies here...




nice. =)  Except C wouldn't be a Ferarri, it would be just the chassis of a
Ferrari with a metal seat bolted on.

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


Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Request forfeedback

2007-07-23 Thread Jonathan Cast
On Monday 23 July 2007, Rene de Visser wrote:
> >> Simon PJ and I are implementing view patterns, a way of pattern matching
> >> against abstract datatypes, in GHC.  Our design is described here:
> >>
> >> http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns
> >>
> >> If you have any comments or suggestions about this design, we'd love to
> >> hear them.  You can respond to this list (and we can take it to
> >> haskell-cafe if the thread gets long) or, if you prefer, directly to me.
>
> I find the => operator excessive.

I want to voice my complete agreement.  At least -> is already a binding 
operator in GHC, with semantics analogous to those being introduced; since 
when is => a binding operator?  Thus far, neither => nor <= has been used for 
anything of the sort, so it's an entirely new entry in the semantic space --- 
and => /is/ already a keyword in GHC, which makes it worse.



Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Another analogy

2007-07-23 Thread Jonathan Cast
On Monday 23 July 2007, Andrew Coppin wrote:
>  From the guy who brought you "data in Haskell is like an undead quantum
> cat", I present the following:
>
> "If programming languages were like vehicles, C would be a Ferrari, C++
> would be a Porshe, Java would be a BWM and Haskell would be a hovercraft.
>
> It doesn't even have WHEELS! There is no steering wheel, no gearbox, no
> clutch... it doesn't even have BRAKES!!!
>
> It completely turns the rules upside down. I mean, it moves by PUSHING
> AIR. That's just crazy! It even STEERS by pushing air. It sounds so
> absurd, it couldn't possibly work...
>
> ...oh, but it DOES work. Very well, actually. In fact, a hovercraft can
> do some things that the others can't. It works on water. It can go
> sideways. It can REALLY turn on the spot."

I'm definitely keeping this around somewhere.  Thanks.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Another analogy

2007-07-23 Thread Andrew Coppin
From the guy who brought you "data in Haskell is like an undead quantum 
cat", I present the following:


"If programming languages were like vehicles, C would be a Ferrari, C++ 
would be a Porshe, Java would be a BWM and Haskell would be a hovercraft.


It doesn't even have WHEELS! There is no steering wheel, no gearbox, no 
clutch... it doesn't even have BRAKES!!!


It completely turns the rules upside down. I mean, it moves by PUSHING 
AIR. That's just crazy! It even STEERS by pushing air. It sounds so 
absurd, it couldn't possibly work...


...oh, but it DOES work. Very well, actually. In fact, a hovercraft can 
do some things that the others can't. It works on water. It can go 
sideways. It can REALLY turn on the spot."


Insert whitty replies here...

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


Re: [Haskell-cafe] Weird ghci behaviour?

2007-07-23 Thread Dan Piponi

Ian said:


Can you please give a complete testcase for the problem you're seeing?


I took my test case and started deleting lines from it to simplify it.
And now I'm not seeing the problem at all and I can't reproduce it,
even though when I originally posted I was getting it repeatably. I'm
either hallucinating or it's a problem that comes up intermittently.
Maybe it's some kind of network time skew issue that has nothing to do
with ghc. If I catch it happening again I'll make sure to do more
investigation.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] View patterns in GHC: Request forfeedback

2007-07-23 Thread Rene de Visser
>> Simon PJ and I are implementing view patterns, a way of pattern matching
>> against abstract datatypes, in GHC.  Our design is described here:
>>
>> http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns
>>
>> If you have any comments or suggestions about this design, we'd love to
>> hear them.  You can respond to this list (and we can take it to
>> haskell-cafe if the thread gets long) or, if you prefer, directly to me.
>
I find the => operator excessive. GHC Haskell seems to be growing too 
rapidly syntax wise in my opinion.
The important features of code are correctness, maintainability and 
readibility (IMHO), and I think => is working against these.

=> uses up more syntax. Buys very little. Equivalent to "-> Just _ " or "-> 
Just x " as far as I can see.
I would prefer to type the extra 6 characters rather than having the hidden 
Maybe.
It is also one more thing to learn. One more confusing type error when you 
mix them up.

Rene.





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


Re: [Haskell-cafe] filterFirst

2007-07-23 Thread Jonathan Cast
On Monday 23 July 2007, Alexteslin wrote:
> Hi,
> first I like to thank all of you guys - it really helps!
>
> I am still on a same chapter with higher order functions and this function
> is also confusing.
> But before i even define this function i am getting the type error - i
> don't know why? So i wrote the simpler one like:
>
> filterAlpha :: (a -> Bool) -> [a] -> [a]
> filterAlpha f [] = []
> filterAlpha f (x:xs)
>   |f x= x : filterAlpha xs
>   |otherwise  = filterAlpha xs
>
> and i am getting this error message:
>
> Type error in application
> Expression :filterAlpha xs
> Type: [b]
> Dous not match : a -> Bool
>
> To even my very little knowledge i think that this should work. What am i
> doing wrong?

You're passing only one argument to filterApha, when it takes two.  Haskell 
can't figure out which arguments you want to stay the same on every recursive 
call, and which ones you want to vary, so you have to supply every argument 
every time.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: filterFirst

2007-07-23 Thread apfelmus
Alexteslin wrote:
> filterAlpha :: (a -> Bool) -> [a] -> [a]
> filterAlpha f [] = []
> filterAlpha f (x:xs)
>   |f x= x : filterAlpha xs
>   |otherwise  = filterAlpha xs
> 
> 
> and i am getting this error message:
> 
> Type error in application
> Expression :filterAlpha xs
> Type: [b]
> Dous not match : a -> Bool

  filterAlpha :: (a -> Bool) -> [a] -> [a]
  filterAlpha f [] = []
  filterAlpha f (x:xs)
 | f x   = x : filterAlpha f xs
 | otherwise = filterAlpha f xs

filterAlpha  has two parameters. The first parameter is a function (a ->
Bool), the second is a list [a]. The error message complains that  xs ,
which you actidentially gave as first parameter, is a list [a] and not a
function (a -> Bool).

Regards,
apfelmus

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


[Haskell-cafe] filterFirst

2007-07-23 Thread Alexteslin

Hi,
first I like to thank all of you guys - it really helps!

I am still on a same chapter with higher order functions and this function
is also confusing.
But before i even define this function i am getting the type error - i don't
know why? So i wrote the simpler one like:

filterAlpha :: (a -> Bool) -> [a] -> [a]
filterAlpha f [] = []
filterAlpha f (x:xs)
|f x= x : filterAlpha xs
|otherwise  = filterAlpha xs


and i am getting this error message:

Type error in application
Expression :filterAlpha xs
Type: [b]
Dous not match : a -> Bool

To even my very little knowledge i think that this should work. What am i
doing wrong?

Thanks again  
-- 
View this message in context: 
http://www.nabble.com/filterFirst-tf4131377.html#a11749336
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] In-place modification

2007-07-23 Thread Andrew Coppin

Sebastian Sylvan wrote:

On 10/07/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:

Hint: If you can get readable/maintainable Haskell to run on more than
one core "automatically", you're onto something pretty special. ;-)


Soon, have a little patience :-)

See for example:
http://research.microsoft.com/~simonpj/papers/ndp/NdpSlides.pdf
http://research.microsoft.com/~tharris/papers/2007-fdip.pdf


Mmm... it'll be damn good if any of this ever actually happens. But 
until then... heh. ;-)


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


[Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-23 Thread apfelmus
Simon Marlow wrote:
> Dan Licata wrote:
>> Simon PJ and I are implementing view patterns, a way of pattern matching
>> against abstract datatypes, in GHC.  Our design is described here:
>>
>> http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns
>>
>> If you have any comments or suggestions about this design, we'd love to
>> hear them.  You can respond to this list (and we can take it to
>> haskell-cafe if the thread gets long) or, if you prefer, directly to me.
> 
> At the risk of being a spoil-sport, I have a somewhat negative take on
> view patterns.  Not because I think they're particularly bad, but
> because I don't think they're significantly useful enough to warrant
> adding to the language, at least if we also have pattern guards.
> 
> All of the examples on the wiki page can be written in the same number
> of lines, sometimes with fewer characters, using pattern guards or some
> other existing Haskell idiom (e.g. the bit parsing example is much more
> nicely expressed using a bit-parsing monad).  I believe adding yet
> another idiom will be detrimental: too much choice is bad.

I agree that only few examples from the wiki page are that compelling.
Nevertheless, I like view patterns since they can be put to really good use

  http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns#UsesofViews

Views are especially useful for Data.Graph. Also, I favor views instead
of pattern guards.

However, I don't like the current proposal, mainly because it doesn't
have the "Transparent ordinary Patterns"-feature. Also, I consider
definitions like

   foldr f z [] = z
   foldr f z (x : foldr f z -> xs) =  x `f` xs

abuse.

>   Data.Set, Data.IntSet, Data.Map, Data.IntMap
>   Data.Graph, Data.Sequence, Data.Bytestring, Data.Array,
>   Data.HashTable, Data.Ratio(Rational)
> 
> So I don't think there's an overwhelming amount of stuff that would
> change if we had view patterns.  In GHC itself most of our data
> structures are already abstract too.

While the implementation of the abstract data structures themselves is
unlikely to change, views make it much easier to use them. I think it
would be a big win to have ByteStrings or Data.Sequence pattern matched
like ordinary lists and I think that Data.Graph will blossom with proper
view patterns.

Regards,
apfelmus

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


[Haskell-cafe] partitions of a multiset

2007-07-23 Thread Brent Yorgey

Hi all,

I've written some code to generate set partitions:

import Control.Arrow
import Data.List

-- pSet' S generates the power set of S, with each subset paired
--   with its complement.
--   e.g. pSet' [1,2] = [([1,2],[]),([1],[2]),([2],[1]),([],[1,2])].
pSet' :: [a]   -> [([a],[a])]
pSet'[] = [([],[])]
pSet'(x:xs) = mp first ++ mp second where
   mp which = map (which (x:)) psRest
   psRest = pSet' xs

-- partitions S generates a list of partitions of S.
-- e.g. partitions [1,2,3] =
[[[1,2,3]],[[1,2],[3]],[[1,3],[2]],[[1],[2,3]],[[1],[2],[3]]].
partitions :: [a] -> [[[a]]]
partitions [] = [[]]
partitions (x:xs) = (pSet' xs) >>= ((x:) *** partitions >>> uncurry (map .
(:)))

However, this version of partitions generates duplicates when given a
multiset, for example:

*Combinatorics> partitions [1,1,2]
[[[1,1,2]],[[1,1],[2]],[[1,2],[1]],[[1],[1,2]],[[1],[1],[2]]]

The partition [[1,2],[1]] is generated twice (order doesn't matter).  I'd
like to write a version of partitions which generates duplicate-free output
even for input multisets, but haven't come up with a good method yet.  Any
ideas?

-Brent

PS Yes, this is for Project Euler. =)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-23 Thread Jon Harrop
On Monday 23 July 2007 16:57:08 Simon Marlow wrote:
> Dan Licata wrote:
> > Simon PJ and I are implementing view patterns, a way of pattern matching
> > against abstract datatypes, in GHC.  Our design is described here:
> >
> > http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns
> >
> > If you have any comments or suggestions about this design, we'd love to
> > hear them.  You can respond to this list (and we can take it to
> > haskell-cafe if the thread gets long) or, if you prefer, directly to me.
>
> At the risk of being a spoil-sport, I have a somewhat negative take on view
> patterns...

F# already has active patterns and there are OCaml macros implementing views. 
I have used F#'s active patterns extensively and find them to be extremely 
useful. I can only assume that they will remain similarly useful in Haskell.

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-23 Thread Simon Marlow

Dan Licata wrote:


Simon PJ and I are implementing view patterns, a way of pattern matching
against abstract datatypes, in GHC.  Our design is described here:

http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns

If you have any comments or suggestions about this design, we'd love to
hear them.  You can respond to this list (and we can take it to
haskell-cafe if the thread gets long) or, if you prefer, directly to me.


At the risk of being a spoil-sport, I have a somewhat negative take on view 
patterns.  Not because I think they're particularly bad, but because I 
don't think they're significantly useful enough to warrant adding to the 
language, at least if we also have pattern guards.


All of the examples on the wiki page can be written in the same number of 
lines, sometimes with fewer characters, using pattern guards or some other 
existing Haskell idiom (e.g. the bit parsing example is much more nicely 
expressed using a bit-parsing monad).  I believe adding yet another idiom 
will be detrimental: too much choice is bad.


To my eyes, mixing bound and binding occurrences of variables in patterns 
in an arbitrarily nested way is sure to lead to confusion.  The existing 
idioms all have a one-level deep notion of bound/binding scope, and in 
order to get more nesting you have to start naming things: this is good, 
IMO.  Not that I think we should omit a language feature because it *could* 
be used to write obfuscated code; no, in this case I think nesting more 
than one level deep will *always* lead to obfuscated code.


The use of the right-arrow is confusing, especially on the left of a case 
alternative or in a lambda expression.


The main argument in favour of view patterns is:

> it's possible that people would start routinely hiding the data
> representation and exporting view functions instead, which would be an
> excellent thing.

My impression is that most of the time a data structure has a clever 
internal representation that you don't want to expose anyway.  This is 
supported by the data structures we have in the base package, all these are 
abstract:


  Data.Set, Data.IntSet, Data.Map, Data.IntMap
  Data.Graph, Data.Sequence, Data.Bytestring, Data.Array,
  Data.HashTable, Data.Ratio(Rational)

and most export view-like things (e.g. Data.Set.toList).

The modules I found that export non-abstract types that should really be 
abstract:


  Data.Complex, Data.Tree

So I don't think there's an overwhelming amount of stuff that would change 
if we had view patterns.  In GHC itself most of our data structures are 
already abstract too.


The View class is nice, even with just pattern guards.  I'd be in favour of 
 making it standard and actively encouraging its use.


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


Re: [Haskell-cafe] Equational Reasoning goes wrong

2007-07-23 Thread J.N. Oliveira

Janis Voigtlaender wrote:


()
http://portal.acm.org/citation.cfm?doid=227699.227716


This paper cites works by L. Kott, but not his PhD thesis "Des 
substitutions dans les systemes d'equations algebriques sur le magma" 
(Univ. Paris VII, 1979) which is (as far as I can remember) among the 
earliest efforts to characterize fixpoint stability with respect to 
substitution.


J. Oliveira
www.di.uminho.pt/~jno
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Optimising UTF8-CString -> String marshaling, plus comments on withCStringLen/peekCStringLen

2007-07-23 Thread Bayley, Alistair
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of Stefan O'Rear
> 
> fromUTF8Ptr unboxes fine for me with HEAD and 6.6.1.
> 
> > - the chr function tests that its Int argument is less than 1114111,
> >   before constructing the Char. It'd be nice to avoid this test.
> 
> You want unsafeChr from the (undocumented) GHC.Base module.
> http://darcs.haskell.org/ghc-6.6/packages/base/GHC/Base.lhs for
> reference (but don't copy the file, it's already an 
> importable module).

>  ISTR seeing a bug report about this a while back, we know it's dumb.
> You could probably use x < 0xF8 instead.

FWIW,

I've optimised this to a point where I'm happy with it, and you can see
the results here:
  http://darcs.haskell.org/takusen/Foreign/C/UTF8.hs

I was using ghc-6.6 back in June, and an upgrade to 6.6.1 fixed some of
the issues for me (e.g. unboxing Ptrs, bang-patterns differ from seq).

I sent a test case to Simon PJ about the duplicated code in the
simplifier output, but I can't tell if it's been added as a trac ticket.

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Equational Reasoning goes wrong

2007-07-23 Thread Jon Fairbairn
"Neil Mitchell" <[EMAIL PROTECTED]> writes:

> Hi
> 
> Haskell is known for its power at equational reasoning - being able to
> treat a program like a set of theorems. For example:
> 
> break g = span (not . g)
> 
> Which means we can replace:
> 
> f = span (not . g)
> 
> with:
> 
> f = break g
> 
> by doing the opposite of inlining, and we still have a valid program.
> 
> However, if we use the rule that "anywhere we encounter span (not . g)
> we can replace it with break g" then we can redefine break as:
> 
> break g = break g
> 
> Clearly this went wrong! Is the folding back rule true in general,
> only in specific cases, or only modulo termination?

To add another viewpoint on what goes wrong: I think you're
being seduced by syntax. When you say that you can replace
"span (not . g)" with "break g", you require that the break
you defined above be in scope. You wouldn't consider

> bother = \break -> break . span (not . g)

to be a suitable candidate for replacement without doing an
alpha conversion first. Now because the definitions in a
haskell programme are all mutually recursive, there's really
a big Y (fix) round the whole lot. Simplifying it a bit, you
could say that unsugaring the definition

> break g = span (not . g)

gives you

> break g := fix (\break -> span (not . g))

(where ":=" denotes non-recursive definition). Now it's
clear that you can't apply your equation in there, because
the break you want to use isn't in scope.

-- 
Jón Fairbairn [EMAIL PROTECTED]

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


[Haskell-cafe] Re: Practise fingerspelling with Haskell! (Code cleanup request)

2007-07-23 Thread apfelmus
Mirko Rahn wrote:
> apfelmus wrote:
>
>> Note that using Peano-numbers can achieve the same effect of stopping
>> the length calculation as soon as more than one character is different.
>>
>>   data Nat = Zero | Succ Nat deriving (Eq, Ord)
>>
>>   instance Num Nat where
>> (Succ x) + y  = Succ (x+y)
>>  Zero+ y  = y
> 
> Very nice (and quite fast), thanks for sharing this.
> 
> One point: Writing down the equations for (+) by looking at the left
> argument first, you introduce an additional constraint to the user
> program, since if we have
> 
> lenL [] = 0
> lenL (x:xs) = 1 + lenL xs
> 
> lenR [] = 0
> lenR (x:xs) = lenR xs + 1
> 
> then
> 
> *FingerSpell> (lenL (repeat ()) :: Nat) < 10
> False
> *FingerSpell> (lenR (repeat ()) :: Nat) < 10
> *** Exception: stack overflow
> 
> So you can change a program that returns a proper value to one that
> loops by replacing lenL with lenR. Such problems are very difficult to
> track down, even if the library documentation states it very clearly.

It's the same with (||) or (&&):

  any  p = foldr (||) False . map p
  any' p = foldr (flip (||)) False . map p

Here, any' id  will choke on

  x = True : repeat False

but  any id  works just fine.

Since there's no way to have a function be lazy in both arguments, the
implicit convention is to make functions strict in the first arguments
and, if applicable, lazy in the last arguments. In other words, the
convention is

  True || _|_ = True   but not  _|_ || True = True

  1 + _|_ = Succ _|_   but not  _|_ + 1 = Succ _|_

Regards,
apfelmus

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


Re: Re[2]: [Haskell-cafe] i need wxHaskell compiled for ghc 6.6.1 on Windows

2007-07-23 Thread Neil Mitchell

Hi


> - native appearance

I think that's pretty good these days, the native theme on Windows has
been getting better and better from Gtk+ 2.6 to the current 2.10


wxHaskell used to be 10 times better than Gtk, now its about twice as
good. The Gtk developers are seriously addressing some of the
mistakes, and the work is going in the direction, so my hope is that
it will hit nearly perfect one day.

Duncan even volunteered to file the bug report etc. on any bugs I spot
and screenshot.

Thanks

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


RE: [Haskell-cafe] Optimising UTF8-CString -> String marshaling, plus comments on withCStringLen/peekCStringLen

2007-07-23 Thread Bayley, Alistair
Weird... I sent this over a month ago, and was a bit puzzled as to why
it didn't appear on the list. Has it been waiting for a moderator to
release?

> -Original Message-
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of Alistair Bayley
> Sent: 04 June 2007 09:44
> To: haskell-cafe
> Cc: Duncan Coutts
> Subject: Re: [Haskell-cafe] Optimising UTF8-CString -> String 
> marshaling,plus comments on withCStringLen/peekCStringLen
> 
> Hello cafe,
> 
> (Following up on my own optimisation question, and Duncan's advice
> to look at http://darcs.haskell.org/ghc/compiler/utils/Encoding.hs)
> 
> > If you want to look at some existing optimised UTF8 
> encoding/decoding
> > code then take a look at the code used in GHC:
> >
> > http://darcs.haskell.org/ghc/compiler/utils/Encoding.hs
> >
> > Duncan
> 
> I took a look at the UTF8 decoder in GHC. This inspired me to write
> one that also used unboxed types directly. Pleasingly, it goes like
> a cut cat, and uses far less space than the naive version, but it's
> not portable, which is a bummer.
...
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe