Re: [Haskell-cafe] Parsec bug, or...?

2009-10-14 Thread S. Doaitse Swierstra
I could not resist this. The code import Text.ParserCombinators.UU.Parsing pCommand [] = pure [] pCommand xxs@(x:xs) = ((:) $ pSym x * pCommand xs) `opt` xxs pCommands = amb . foldr (|) pFail . map pCommand $ [banana, chocolate, frito, fromage] t :: String - ([String], [Error Char Char

Re: [Haskell-cafe] Exponential complexity of type checking (Was: Type-level naturals multiplication)

2009-10-14 Thread Roel van Dijk
You can help ghci out a bit with type synonyms: type T a = (a, a) type T2 a = T (T a) type T4 a = T2 (T2 a) type T8 a = T4 (T4 a) type T16 a = T8 (T8 a) f0 :: a - T a f1 :: a - T2 a f2 :: a - T4 a f3 :: a - T8 a f4 :: a - T16 a f0 x = (x,x) f1 = f0 . f0 f2 = f1 . f1 f3 = f2 . f2 f4

Re: [Haskell-cafe] Exponential complexity of type checking (Was: Type-level naturals multiplication)

2009-10-14 Thread Dan Doel
On Wednesday 14 October 2009 5:25:10 am Roel van Dijk wrote: With newtypes I can probably abstract even more. (newtype X a b = X (a (a b)) In fact, with GHC extensions, you don't need newtypes: {-# LANGUAGE LiberalTypeSynonyms #-} type T a = (a,a) type X f a = f (f a) f0 :: a - T

Re: [Haskell-cafe] Exponential complexity of type checking (Was: Type-level naturals multiplication)

2009-10-14 Thread Roel van Dijk
On Wed, Oct 14, 2009 at 11:53 AM, Dan Doel dan.d...@gmail.com wrote: In fact, with GHC extensions, you don't need newtypes:  {-# LANGUAGE LiberalTypeSynonyms #-} Ah, I completely forgot about that language extension. Thanks! Yeah. Asking for the type of 'f4 . f4' doesn't seem to expand the

[Haskell-cafe] ANN: fp-southwales, the South Wales Functional Programming User Group

2009-10-14 Thread Andy Gimblett
Dear friends, It is my pleasure to announce the formation of fp-southwales, a user group for anybody interested in functional programming in the area of south Wales, UK. We're based out of Swansea University's Computer Science department, where there are a few of us using Haskell for our

Re: [Haskell-cafe] Exponential complexity of type checking (Was: Type-level naturals multiplication)

2009-10-14 Thread Dan Doel
On Wednesday 14 October 2009 6:15:11 am Roel van Dijk wrote: If you declare a type for f5 then ghci must check if that type is correct, which triggers the explosion. If you don't declare a type then it won't infer the type until necessary. Basically, ghci is lazy Well, that may be the

[Haskell-cafe] Fuzzy Logic / Linguistic Variables

2009-10-14 Thread Neal Alexander
So i was reading Programming Game AI by Example by Mat Buckland (http://www.ai-junkie.com/books/toc_pgaibe.html) and decided to rewrite his chapter on Fuzzy logic in haskell (from C++). My initial impression: its one of those scenarios where OOP grossly over complicates things Heres an

[Haskell-cafe] Reverse dependencies in Hackage

2009-10-14 Thread hask...@kudling.de
Nice, thank you for the great work. Browsing the reverse dependencies of popular packages like bytestring http://bifunctor.homelinux.net/~roel/cgi-bin/hackage-scripts/revdeps/bytestring-0.9.1.5 can be improved a bit. 1) Can you please sort the reverse dependent package names? That makes it

[Haskell-cafe] Re: Reverse dependencies in Hackage

2009-10-14 Thread Roel van Dijk
On Wed, Oct 14, 2009 at 3:24 PM, hask...@kudling.de hask...@kudling.de wrote: Nice, thank you for the great work. Browsing the reverse dependencies of popular packages like bytestring http://bifunctor.homelinux.net/~roel/cgi-bin/hackage-scripts/revdeps/bytestring-0.9.1.5 can be improved a

[Haskell-cafe] Re: Parsec bug, or...?

2009-10-14 Thread Christian Maeder
My fix would be to parse as many letters as possible many1 alpha (that's longest match) and then check the result with isPrefixOf for all your alternatives (and return the alternative that matches first). Cheers Christian Martijn van Steenbergen wrote: Brandon S. Allbery KF8NH wrote: My fix

Re: [Haskell-cafe] Setting environment variables on Windows

2009-10-14 Thread Sönke Hahn
On Friday 09 October 2009 07:07:21 pm Duncan Coutts wrote: On Fri, 2009-10-09 at 17:37 +0200, Sönke Hahn wrote: Hi! I need to set an environment variable from Haskell and i would like to do that cross-platform. There is System.Posix.Env.setEnv, which does exactly, what i want on Linux.

Re: [Haskell-cafe] Setting environment variables on Windows

2009-10-14 Thread Sönke Hahn
On Friday 09 October 2009 07:19:30 pm Peter Verswyvelen wrote: Mmm, that seems like a shortcoming. Well, you could just wrap the C functions yourself, like this (two possibilities, no error checking yet, quick hack): http://hpaste.org/fastcgi/hpaste.fcgi/view?id=10565#a10565 Note that

[Haskell-cafe] example of PortMidi use

2009-10-14 Thread Michael Mossey
Can someone give me an example of Sound.PortMidi use? I'm having trouble. This program has bugs---makes sound only intermittently, and seems to have set up some kind of loop that is sending midi messages continuously even after terminating the program: import Sound.PortMidi import Foreign.C

[Haskell-cafe] GHC devs

2009-10-14 Thread Andrew Coppin
Random question of the day: How many developers are working on GHC? I had always *assumed* that there was something like a hundred core developers, with a much larger number of people casually testing and occasionally submitting the odd patch or two. However, I watched a video of a talk the

[Haskell-cafe] Monotype error

2009-10-14 Thread Martijn van Steenbergen
Dear café, {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ImpredicativeTypes #-} type Void = forall a. a newtype Mono a = Mono { runMono :: [Void] } beep :: Mono a - Mono a beep (Mono vs) = Mono (map undefined vs) Compiling this with GHC results in: Monotype.hs:9:28: Cannot match a

Re: [Haskell-cafe] GHC devs

2009-10-14 Thread Roel van Dijk
I think the contributors page on GHC's wiki contains relevant information: http://hackage.haskell.org/trac/ghc/wiki/Contributors ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] GHC devs

2009-10-14 Thread Bulat Ziganshin
Hello Andrew, Wednesday, October 14, 2009, 10:28:45 PM, you wrote: I had always *assumed* that there was something like a hundred core developers only 10 and only in binary system :))) Simon Peyton-Jones works on front-end, i.e compiling Haskell down to simple core language, and Simon Marlow

[Haskell-cafe] Re:

2009-10-14 Thread Martin Sulzmann
On Wed, Oct 14, 2009 at 7:33 AM, o...@okmij.org wrote: Martin Sulzmann wrote: Undecidable instances means that there exists a program for which there's an infinite reduction sequence. I believe this may be too strong of a statement. There exists patently terminating type families that

Re: [Haskell-cafe] example of PortMidi use

2009-10-14 Thread Henning Thielemann
On Wed, 14 Oct 2009, Michael Mossey wrote: Can someone give me an example of Sound.PortMidi use? I'm having trouble. This program has bugs---makes sound only intermittently, and seems to have set up some kind of loop that is sending midi messages continuously even after terminating the

Re: [Haskell-cafe] GHC devs

2009-10-14 Thread Don Stewart
bulat.ziganshin: Hello Andrew, Wednesday, October 14, 2009, 10:28:45 PM, you wrote: I had always *assumed* that there was something like a hundred core developers only 10 and only in binary system :))) Simon Peyton-Jones works on front-end, i.e compiling Haskell down to simple

[Haskell-cafe] Why does replicateM (10^6) $ return 0 produce output in the IO monad, but overflow the maybe monad?

2009-10-14 Thread Thomas Hartman
-- Why does replicateM (10^6) $ return 0 produce output in the IO monad, but overflow the maybe monad? iterateNTimes i f x = foldr (.) id (replicate i f) $ x tntIO :: IO Int -- same as replicateM (10^6) $ return 0, same as sequence . replicate (10^6) $ return 0 tntIO = return . head =

Re: [Haskell-cafe] GHC core packages: same core?

2009-10-14 Thread Max Bolingbroke
Dimitry, I *believe* ext-core will match that document, but I'm not sure of the exact status. Tim Chevalier has done a lot of great work maintaining the external core stuff and I think he is actively using the extcore library, so *that* should almost certainly match GHC's output. It's great to

Re: [Haskell-cafe] GHC core packages: same core?

2009-10-14 Thread Lemmih
On Wed, Oct 14, 2009 at 10:28 PM, Max Bolingbroke batterseapo...@hotmail.com wrote: Dimitry, I *believe* ext-core will match that document, but I'm not sure of the exact status. Tim Chevalier has done a lot of great work maintaining the external core stuff and I think he is actively using the

Re: [Haskell-cafe] GHC devs

2009-10-14 Thread Andrew Coppin
Don Stewart wrote: bulat.ziganshin: Hello Andrew, Wednesday, October 14, 2009, 10:28:45 PM, you wrote: I had always *assumed* that there was something like a hundred core developers only 10 and only in binary system :))) About 1000 people have worked on libraries on

Re[2]: [Haskell-cafe] GHC devs

2009-10-14 Thread Bulat Ziganshin
Hello Andrew, Thursday, October 15, 2009, 12:54:37 AM, you wrote: Does anybody actually get paid to develop GHC? Or is this all people SPJ, SM and Ian are paid by MS Research. Other people involved in core development are mainly scientists (afaik) -- Best regards, Bulat

[Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Martijn van Steenbergen
Hello café, I've never written an Alternative instance for a newtype yet that doesn't look like this: instance Alternative T where empty = T empty T x | T y = T (x | y) Why does newtype deriving not work for Alternative? (It works fine for Monoid.) Thanks, Martijn.

Re: [Haskell-cafe] Sharing Subexpressions: Memoization of Fibonacci sequence

2009-10-14 Thread SimonK77
Hallo Daniel, can you explain the difference between a pattern binding and a function binding? I haven't heard about these two terms so far. And furthermore: Why does the memoization only happen with pattern binding? Best regards, Simon -- View this message in context:

Re: [Haskell-cafe] Monotype error

2009-10-14 Thread Roman Cheplyaka
* Martijn van Steenbergen mart...@van.steenbergen.nl [2009-10-14 20:35:06+0200] Dear café, {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ImpredicativeTypes #-} type Void = forall a. a newtype Mono a = Mono { runMono :: [Void] } beep :: Mono a - Mono a beep (Mono vs) = Mono (map undefined

Re: [Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Ryan Ingram
Works for me on GHC6.10.4: {-# LANGUAGE GeneralizedNewtypeDeriving #-} module NewtypeDerive where import Control.Applicative newtype Foo f a = Foo (f a) deriving (Functor, Applicative, Alternative) newtype Bar a = Bar [a] deriving (Functor, Applicative, Alternative) -- ryan On Wed, Oct 14,

Re: [Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Martijn van Steenbergen
You guys are right. I was being silly. Thanks. :-) Ryan Ingram wrote: Works for me on GHC6.10.4: ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Setting environment variables on Windows

2009-10-14 Thread Sönke Hahn
On Wednesday 14 October 2009 04:50:56 pm Sönke Hahn wrote: On Friday 09 October 2009 07:19:30 pm Peter Verswyvelen wrote: Mmm, that seems like a shortcoming. Well, you could just wrap the C functions yourself, like this (two possibilities, no error checking yet, quick hack):

Re: [Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Martijn van Steenbergen
It doesn't work for this one: newtype Split a = Split { runSplit :: [Either a (Char, Split a) ]} But my handwritten instance remains identical. Groetjes, Martijn. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Sharing Subexpressions: Memoization of Fibonacci sequence

2009-10-14 Thread Daniel Fischer
Am Mittwoch 14 Oktober 2009 23:30:05 schrieb SimonK77: Hallo Daniel, can you explain the difference between a pattern binding and a function binding? I haven't heard about these two terms so far. The formal specification is at http://haskell.org/onlinereport/decls.html#sect4.4.3 A function

Re: [Haskell-cafe] Fuzzy Logic / Linguistic Variables

2009-10-14 Thread Fernando Henrique Sanches
I didn't read the book, but your code seems very elegant, more than I even thought possible. I've never programmed with fuzzy logic before, but I can understand your code - it reads naturally. Fernando Henrique Sanches On Wed, Oct 14, 2009 at 9:59 AM, Neal Alexander relapse@gmx.com wrote:

Re: [Haskell-cafe] GHC devs

2009-10-14 Thread Don Stewart
bulat.ziganshin: Hello Andrew, Thursday, October 15, 2009, 12:54:37 AM, you wrote: Does anybody actually get paid to develop GHC? Or is this all people SPJ, SM and Ian are paid by MS Research. Other people involved in core development are mainly scientists (afaik) Besides MSR and the

Re: [Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Jake McArthur
Martijn van Steenbergen wrote: It doesn't work for this one: newtype Split a = Split { runSplit :: [Either a (Char, Split a) ]} But my handwritten instance remains identical. The instance has the form [], not the form [Either _ (Char, Split _)]. Since they don't match exactly, it won't