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 Int])
t input = parse ( (,) $ pCommands * pEnd)  (listToStr input)

gives the following results:

*Main t 
([banana,chocolate,frito,fromage],[])
*Main t b
([banana],[])
*Main t fr
([frito,fromage],[])
*Main t x
([banana,chocolate,frito,fromage],[
The token 'x'was not consumed by the parsing process.])
*Main t frox
([fromage],[
The token 'x'was not consumed by the parsing process.])
*Main t frx
([frito,fromage],[
The token 'x'was not consumed by the parsing process.])
*Main

I think it is less clumsy and far less confusing than the Parsec code.  
Note that the function amb tells that its parameter parser can be  
ambiguous


 Doaitse



On 13 okt 2009, at 17:10, Uwe Hollerbach wrote:

On 10/12/09, Martijn van Steenbergen mart...@van.steenbergen.nl  
wrote:

Brandon S. Allbery KF8NH wrote:
My fix would be to have myPrefixOf require the prefix be  
terminated in

whatever way is appropriate (end of input, white space, operator?)
instead of simply accepting as soon as it gets a prefix match  
regardless

of what follows.


Maybe you can use notFollowedBy for this.

HTH,

Martijn.




Yes, I've looked at that and am thinking about it. I'm not quite
certain it's needed in my real program... I seem to have convinced
myself that if I actually specify a proper set of unique prefixes, ie,
set the required lengths for both frito and fromage to 3 in the
test program, I won't get into this situation. Assuming I haven't
committed another brain-fart there, that would be sufficient;
presumably, in a real program one would want to actually specify the
unique prefix, rather than a non-unique pre-prefix. It seems to work
fine in my real program, anyway.

Uwe
___
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] 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   = f3 . f3
f5   = f4 . f4

With newtypes I can probably abstract even more. (newtype X a b = X (a (a b))

Inferring the type of f5 also stops my machine in its tracks. But I
*was* able to infer the type of (f4 . f4).

:t (f4 . f4)
(f4 . f4) :: a - T16 (T16 a)

:t f5
-- buy new computer

Even when you only specify a type for f0 in terms of T you'll get more
readable types:

:t f3
f3 :: a - T (T (T (T (T (T (T (T a)))

But the amount of computation required seems the same.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 a
  f0 x = (x,x)

  f1 :: a - X T a
  f1   = f0 . f0

  f2 :: a - X (X T) a
  f2   = f1 . f1

  f3 :: a - X (X (X T)) a
  f3   = f2 . f2

  f4 :: a - X (X (X (X T))) a
  f4   = f3 . f3

 Inferring the type of f5 also stops my machine in its tracks. But I
 *was* able to infer the type of (f4 . f4).
 
 :t (f4 . f4)
 
 (f4 . f4) :: a - T16 (T16 a)
 
 :t f5

Yeah. Asking for the type of 'f4 . f4' doesn't seem to expand the synonyms, 
while checking f5 does for some reason. I'm perplexed that having f5 defined 
in the file doesn't trigger the explosion unless you declare a type (even in 
terms of X and T) or ask for its type at the prompt.

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


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 synonyms,
 while checking f5 does for some reason. I'm perplexed that having f5 defined
 in the file doesn't trigger the explosion unless you declare a type (even in
 terms of X and T) or ask for its type at the prompt.
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
:-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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  
research, but we welcome anyone who wants to join in, from academia or  
industry, from Swansea, or Cardiff, or indeed anywhere in south  
Wales.  As the name of the group also suggests, we're interested in  
all aspects of functional programming, not just Haskell, although we  
expect that to be a central topic, for now at least.


We exist online as a google group: http://groups.google.com/group/fp-southwales

The first point of business is: hello, what shall we do, and when  
shall we do it?  :-)

http://groups.google.com/group/fp-southwales/browse_thread/thread/ddb2d352a14896d8

All welcome!

-Andy

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


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 explanation, but it's a bit more convoluted than I'd 
have initially thought. For instance, if I write:

  e = head ()

it fails immediately with a type error, so clearly it must be doing some level 
of checking immediately. However, it only needs to check 'head' and '()' to 
notice that they're incompatible, so I suppose it may not need to compute the 
type of e (were it well-typed). But then, adding:

  f6 = f5 . f5

produces no more delay than before. Nor does:

  g = snd . f5

So ghci is able to verify that f5 can be instantiated to the forms a - b and 
b - c in the first case, and that it is of the form a - (b,c) in the second 
case, without blowing up. However, either of:

  e = f5 ()
  e' () = f5 ()

does blow up, so it must be verifying more than the fact that f5 is of the 
form a - b, where a can be instantiated to (), which is odd if it's smart 
enough to only compute the portion of the type necessary to verify that 
applications can be well typed.

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


[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 example taken from the book: An agent needs to decide what 
weapon to use based on his distance from the target and the amount of 
ammo each has. The result is in the desirability domain (0-100).


http://code.haskell.org/~hexpuem/fuzzyLogic/AI/Logic/Fuzzy/Example.hs

An excerpt:




weapons = [ Weapon RocketLauncher 9 rocketLauncher,
Weapon ShotGun 13 shotgun,
Weapon AssaultRifle 120 assaultRifle,
Weapon SniperRifle 7 sniperRifle,
Weapon Knife 1 knife ]

chooseWeapon dist = maximum ratings
  where
ratings = [ (f dist ammo, n) | Weapon n ammo f - weapons ]



shotgun :: Double - Double - Double
shotgun dist ammo =

  unfuzz desireDom $ rules (fuzz distDom dist) (fuzz ammoDom ammo)

  where

rules :: Fuzzy Distances - Fuzzy Ammo - FL Desirability
rules distance ammo = do

  distance `is` SniperSuited = Pointless
  distance `is` Far  = Undesirable
  distance `is` Medium   = Undesirable
  distance `is` Melee= Undesirable

  (distance `fairly` Near)  (ammo `fairly` High) = VeryDesirable
  (distance `fairly` Near)  (ammo `fairly` Good) = Desirable
  (distance `fairly` Near)  (ammo `is` Low)  = Undesirable



Full code at http://code.haskell.org/~hexpuem/fuzzyLogic/.

Suggestions welcome - maybe it'd be useful to upload to hackage at some 
point.



It only supports triangle, shoulder, and singleton memberships at the 
moment.




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


[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 easier
to find packages with certain names.

2) I found the columns Direct and Indirect confusing until i found out that
they show the number of reverse dependencies for those packages themselves and
are not related to direct/indirect dependencies of the current package. I don't
think it is necessary to provide those data here and i would be in favor of
reducing the information overload by leaving those data to each package detail
page.

3) Can you try to print the reverse packages horizontally instead of vertically
in tables? Browsing two long tables of direct/indirect reverse dpependencies
like for bytestring makes it tedious to get an overview.

Besides that, i am quite happy.

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


[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 bit.
You should try base ;-)

 1) Can you please sort the reverse dependent package names? That makes it
 easier to find packages with certain names.

 2) I found the columns Direct and Indirect confusing until i found out
 that they show the number of reverse dependencies for those packages
 themselves and are not related to direct/indirect dependencies of the
 current package. I don't think it is necessary to provide those data here
 and i would be in favor of reducing the information overload by leaving
 those data to each package detail page.

I'll respond to 1 and 2 since they are related. Right now the packages
are sorted by their total reverse-dependency count. The idea is that
this gives an idea of the relative importance of a package (in the
closed system of the hackage packet database). However, sorting by
name makes just as much sense.

Sorting by reverse-dependency count is useful if you want to know
which are the most important reverse dependencies.
Sorting by name is useful if you want to find out if a specific
package is a reverse dependency.

Ideally I would like to support both. Maybe a bit of JavaScript could
be used to sort the table client-side.
Something like this: http://www.kryogenix.org/code/browser/sorttable/

 3) Can you try to print the reverse packages horizontally instead of
 vertically in tables? Browsing two long tables of direct/indirect reverse
 dpependencies like for bytestring makes it tedious to get an overview.

That would make sense if I wouldn't also show the reverse-dependencies
of the reverse-dependencies. But I still think that information is
usefull.

Another option would be to have the two tables side-by-side. But that
might be a bit to much for a modestly sized monitor. Again, I wonder
what could be achieved with a little JavaScript in this area.

Thank you for the constructive criticism,
Roel
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 would be to have myPrefixOf require the prefix be terminated in
 whatever way is appropriate (end of input, white space, operator?)
 instead of simply accepting as soon as it gets a prefix match
 regardless of what follows.
 
 Maybe you can use notFollowedBy for this.
 
 HTH,
 
 Martijn.
___
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 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. There is the module System.Environment,
  which seems to be cross-platform, but it does not contain functions to
  manipulate the environment (, just to inspect it). At first glance, I
  didn't find anything relevant in the sub-modules of System.Win32.
 
 Note that often it is enough to set environment variables for the
 programs that you invoke, rather than for your own process. If that's
 enough then you can do it via the System.Process.createProcess action.
 
 Duncan
 

Thanks for the suggestion. In my case, that would be a workaround. Maybe still 
better than writing a .bat-file for the same purpose.

Sönke
___
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 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 using SetEnvironmentVariable does not seem to be compatible with
 getEnv, but calling _putenv does work.

Both solutions seem to work on my system. Using c_putenv doesn't require 
linking additional libraries in my case, so i'm going with that. You've been 
very helpful, thank you very much.

 
 So I guess someone should add this setEnv wrapper to the System.Environment
 module? Ticket?

Once i figure out, how to implement functions differently for linux and 
windows, 
i'll write a ticket with an example module based on your suggestion.

Again, many thanks,

Sönke

 
 On Fri, Oct 9, 2009 at 5:37 PM, Sönke Hahn sh...@cs.tu-berlin.de 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. There is the module System.Environment, which seems to be
  cross-platform, but it does not contain functions to manipulate the
  environment (, just to inspect it). At first glance, I didn't find
 
 anything
 
  relevant in the sub-modules of System.Win32.
 
  Is this just not implemented? How could i implement it myself?
 
  Grateful for any comment,
 
  Sönke
  ___
  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] 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

msgs = [ (0::CULong,PMMsg 0x9c 0x40 0x40)
   , (500,  PMMsg 0x8c 0x40 0x40)
   , (1000, PMMsg 0x9c 0x41 0x40)
   , (1500, PMMsg 0x8c 0x41 0x40) ]



main = do
  let deviceId = 12
  initialize = print
  getDeviceInfo deviceId = print
  startTime - time
  let evts = map (\(t,msg) - PMEvent msg (t+startTime)) msgs
  result - openOutput deviceId 10
  case result of
Right err   - putStrLn (After open:  ++ show err)
Left stream -
do result - writeEvents stream evts
   putStrLn (After write:  ++ show result)
   close stream
   return ()
  terminate = print

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


[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 other day (no, I don't remember 
which one) and it made me reconsider this view. Somebody muttered 
something like GHC is really too big now for just 3 developers to 
manage, which makes it sound as if there are only 3 active 
developers... Surely that can't be correct. (There would never be any 
releases, for one thing...)


Does anybody know anything concrete about this?

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


[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 monotype with `Void'
  Expected type: Void
  Inferred type: a


What does this error mean and why does the code not compile?

Thanks!

Martijn.
___
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 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 does back-end i.e. compiling
this to actual machine code and dealing with idiosyncrasies of all
target systems. and Ian Lynagh is Build engineer maintaining
releases, bug tracking and so on

there are dozens of people doing interesting things with GHC and some
of them are even going to main tree. and there are interns that
implements some rather small and isolated parts of GHC. and dozen or
so of people porting GHC to their environment, building packages and
so on

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[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 still require undecidable
 instances in GHC.


Sorry, I wasn't precise enough.

I didn't mean to say that *every* program which requires undecidable
instance won't terminate.

Rather, take any of the properties which imply decidability. Then,
there *exists* a program which satisfies the negated property and this
program won't terminate.

As you show, for specific cases we can argue that undecidable instances
are decidable. You can even argue that the Add/Mult example is decidable,
assuming we never generate loopy type constraints.

-Martin


 Here is an example:

  {-# LANGUAGE TypeFamilies #-}
 
  type family I x :: *
  type instance I x = x
 
  type family B x :: *
  type instance B x = I x


 GHC 6.8.3 complaints:
Application is no smaller than the instance head
  in the type family application: I x
(Use -fallow-undecidable-instances to permit this)
In the type synonym instance declaration for `B'

 But there cannot possibly be any diverging reduction sequence here, can it?
 The type family I is the identity, and the type family B is its
 alias. There is no recursion. The fact that type families are open is
 not relevant here: our type families I and B are effectively closed,
 because one cannot define any more instance for I and B (or risk
 overlap, which is rightfully not supported for type families).

 The reason GHC complains is because it checks termination
 instance-by-instance. To see the termination in the above program, one
 should consider instances I and B together. Then we will see that I
 does not refer to B, so there are no loops. But this global
 termination check -- for a set of instances -- is beyond the
 abilities of GHC. This is arguably the right decision: after all, GHCi
 is not a full-blown theorem prover.

 Thus there are perfectly decidable type programs that require
 undecidable instances. Indeed, there is no reason to be afraid of that
 extension.

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


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 program:


You may also try
   http://lists.lurk.org/mailman/listinfo/haskell-art 
(haskell-...@lists.lurk.org).

___
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 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 core language, and Simon Marlow does back-end i.e. compiling
 this to actual machine code and dealing with idiosyncrasies of all
 target systems. and Ian Lynagh is Build engineer maintaining
 releases, bug tracking and so on
 
 there are dozens of people doing interesting things with GHC and some
 of them are even going to main tree. and there are interns that
 implements some rather small and isolated parts of GHC. and dozen or
 so of people porting GHC to their environment, building packages and
 so on
 

About 1000 people have worked on libraries on Hackage. That's about two
orders of magnitude more than work on GHC.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 = (iterateNTimes (10^6) (mcons . return $ 0)
(return [])) -- produces output
tntMb :: Maybe Int -- overflows
tntMb = return . head = (iterateNTimes (10^6) (mcons . return $ 0)
(return [])) -- stack overflow

-- equivalently: mcons m ms = (:) $ m * ms
mcons m ms = ap (liftM (:) m) $ ms

I guess the maybe version builds up a huge chain of unevaluated thunks
somewhere, that's usually the reason. But specifically where and why,
and why doesn't IO do the same thing?

Equivalent, with 3 element list:

(mcons $ return $ 0 ) $ (mcons $ return $ 0) $ (mcons $ return $ 0) $
(return [])
(ap . liftM (:) . return $ 0 ) $ (ap . liftM (:) . return $ 0) $ (ap .
liftM (:) . return $ 0) $ (return [])
(ap $ liftM (:) $ return $ 0 ) $ (ap $ liftM (:) $ return $ 0) $ (ap $
liftM (:) $ return $ 0) $ (return [])

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


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 hear that you are interested in writing an alternative
backend! I think LHC is also using ext-core to build a backend, so
this seems like a viable approach.

All the best,
Max

2009/10/13 Dimitry Golubovsky golubov...@gmail.com:
 Max,

 Thanks for the explanation. So, the extcore library is expected to
 match the spec in
 http://www.haskell.org/ghc/docs/6.10.4/html/ext-core/core.pdf and the
 core itself can be produced with -fext-core, correct? I think it might
 be interesting for people working on alternative backends (inlcuding
 myself).

 On Tue, Oct 13, 2009 at 4:53 PM, Max Bolingbroke
 batterseapo...@hotmail.com wrote:
 [skip]

 extcore is a library that parses external Core, which is an
 alternative format intended to be stable and hence a suitable target
 for consumption by non-GHC tooling. You can have GHC output external
 core instead of machine code / C. I don't believe this is widely used
 yet.

 --
 Dimitry Golubovsky

 Anywhere on the Web


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


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 extcore
 library, so *that* should almost certainly match GHC's output.

 It's great to hear that you are interested in writing an alternative
 backend! I think LHC is also using ext-core to build a backend, so
 this seems like a viable approach.

LHC is using a different external core parser.

-- 
Cheers,
  Lemmih
___
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 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 Hackage. That's about two
orders of magnitude more than work on GHC.
  


Sure. But libraries are more or less self-contained, generally. GHC is 
one giant system of closely interacting components, so it (presumably?) 
takes about two orders of magnitude more cooperation to work on it. ;-)


Still, if there are only 10 core people actively working on it... well 
that explains why the wishlist is always so much longer than the feature 
list. (Not that GHC doesn't already _have_ some pretty cool features, 
mind you...)


Does anybody actually get paid to develop GHC? Or is this all people 
working on it in their spare time? It would seem like pushing such a 
huge piece of software forward at anything more than glacial pace would 
require quite a lot of manpower (which I guess is why I assumed there 
were a lot of people working on it). For that matter, who pays for the 
servers which host the code repos and so forth?


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


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,
 Bulatmailto:bulat.zigans...@gmail.com

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


[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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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: 
http://www.nabble.com/Sharing-Subexpressions%3A-Memoization-of-Fibonacci-sequence-tp25861134p25899401.html
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] 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 vs)

 Compiling this with GHC results in:

 Monotype.hs:9:28:
 Cannot match a monotype with `Void'
   Expected type: Void
   Inferred type: a

 What does this error mean and why does the code not compile?

It works if you annotate the type of undefined:

beep (Mono vs) = Mono (map (undefined :: Void - Void) vs)

-- 
Roman I. Cheplyaka :: http://ro-che.info/
Don't let school get in the way of your education. - Mark Twain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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, 2009 at 2:16 PM, Martijn van Steenbergen 
mart...@van.steenbergen.nl wrote:

 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.
 ___
 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] 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):
  http://hpaste.org/fastcgi/hpaste.fcgi/view?id=10565#a10565
 
  Note that using SetEnvironmentVariable does not seem to be compatible
  with getEnv, but calling _putenv does work.
 
 Both solutions seem to work on my system. Using c_putenv doesn't require
 linking additional libraries in my case, so i'm going with that. You've
  been very helpful, thank you very much.
 
  So I guess someone should add this setEnv wrapper to the
  System.Environment module? Ticket?
 
 Once i figure out, how to implement functions differently for linux and
  windows, i'll write a ticket with an example module based on your
  suggestion.

Here's the ticket: http://hackage.haskell.org/trac/ghc/ticket/3587

 
 Again, many thanks,
 
 Sönke
 
  On Fri, Oct 9, 2009 at 5:37 PM, Sönke Hahn sh...@cs.tu-berlin.de 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. There is the module System.Environment, which seems to
   be cross-platform, but it does not contain functions to manipulate the
   environment (, just to inspect it). At first glance, I didn't find
 
  anything
 
   relevant in the sub-modules of System.Win32.
  
   Is this just not implemented? How could i implement it myself?
  
   Grateful for any comment,
  
   Sönke
   ___
   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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 binding is a binding where the function name and at least one 
parameter 
(pattern) appear to the left of '=', while in a pattern binding only bound 
patterns appear 
on the left.

-- function bindings
fun x = expression   -- binds fun
x \/ y = expr'   -- binds (\/)

-- pattern bindings
func = \x - expression  -- binds func
var = expr   -- binds var
(v1,v2) = express-- binds v1 and v2
(a0:a1:tl)   -- binds a0, a1 and tl
| even v1   = exp1
| otherwise = exp2

The first three are *simple* pattern bindings.

 And furthermore:
 Why does the memoization only happen with pattern binding?

I don't know all the details either, but the point is that names bound by a 
(simple) 
pattern binding are constant applicative forms 
(http://www.haskell.org/haskellwiki/CAF) 
which can be shared by all uses (if they have a monomorphic type, cf. also 
http://www.haskell.org/haskellwiki/Monomorphism_Restriction and 
http://haskell.org/onlinereport/decls.html#sect4.5.5), while names bound by a 
function 
binding aren't shared across computations (I think it is generally undecidable 
how much 
could be shared and anyway it would be too complicated for the compiler to 
investigate 
that - too little gain for too much effort).

So with function-bound

fbfib :: Int - Integer
fbfib k =
let fib 0 = 0
fib 1 = 1
fib n = fbfib (n-2) + fbfib (n-1)
in (map fib [0 ..] !! k)

fb2fib :: Int - Integer
fb2fib k =
let fib 0 = 0
fib 1 = 1
fib n = fb2fib (n-2) + fb2fib (n-1)
flst = map fib [0 .. ]
in (flst !! k)

nothing is shared, each (recursive) call to fb(2)fib creates a new list of 
Fibonacci 
values (in principle, different arguments could require very different 
code-paths, so we 
don't even bother to let the compiler look for the few cases where it could 
determine 
sharing would be beneficial).

With pattern-bound functions, it's harder to know when sharing will happen. It 
depends on 
the form of the RHS and where things that might be shared are bound.

In

memoized_fib :: Int - Integer
memoized_fib =
let fib 0 = 0
fib 1 = 1
fib n = memoized_fib (n-2) + memoized_fib (n-1)
in (map fib [0 ..] !!)

the list of Fibonacci numbers is shared, even though it hasn't been given a 
name (In 
general, give entities you want to be shared a name of their own to increase 
the chance of 
them being really shared).

If you define the function with a simple pattern binding which has a 
lambda-expression on 
the right hand side, it depends on whether things are bound within the 
lambda-scope or 
outside. In

plfib :: Int - Integer
plfib = \k -
let fib 0 = 0
fib 1 = 1
fib n = plfib (n-2) + plfib (n-1)
in (map fib [0 ..] !! k)

the things which could be shared are bound inside the lambda-expression, 
therefore they 
aren't shared (they could potentially depend on the lambda-bound variable[s], 
here k). 

Lifting the binding of fib outside the lambda

pblfib :: Int - Integer
pblfib =
let fib 0 = 0
fib 1 = 1
fib n = pblfib (n-2) + pblfib (n-1)
in \k - (map fib [0 ..] !! k)

doesn't help - of course, the list in which we index is still inside the 
lambda. Give it a 
name and hoist it outside the lambda:

peblfib :: Int - Integer
peblfib =
let fib 0 = 0
fib 1 = 1
fib n = peblfib (n-2) + peblfib (n-1)
flst = map fib [0 .. ]
in \k - (flst !! k)

Now flst is a CAF which can be shared, and indeed it is:
*MFib peblfib 40
102334155
(0.00 secs, 0 bytes)


 Best regards,

 Simon

Hope this gets you started,

Daniel

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


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:

 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 example taken from the book: An agent needs to decide what weapon
 to use based on his distance from the target and the amount of ammo each
 has. The result is in the desirability domain (0-100).

 http://code.haskell.org/~hexpuem/fuzzyLogic/AI/Logic/Fuzzy/Example.hshttp://code.haskell.org/%7Ehexpuem/fuzzyLogic/AI/Logic/Fuzzy/Example.hs

 An excerpt:


 

 weapons = [ Weapon RocketLauncher 9 rocketLauncher,
Weapon ShotGun 13 shotgun,
Weapon AssaultRifle 120 assaultRifle,
Weapon SniperRifle 7 sniperRifle,
Weapon Knife 1 knife ]

 chooseWeapon dist = maximum ratings
  where
ratings = [ (f dist ammo, n) | Weapon n ammo f - weapons ]

 

 shotgun :: Double - Double - Double
 shotgun dist ammo =

  unfuzz desireDom $ rules (fuzz distDom dist) (fuzz ammoDom ammo)

  where

rules :: Fuzzy Distances - Fuzzy Ammo - FL Desirability
rules distance ammo = do

  distance `is` SniperSuited = Pointless
  distance `is` Far  = Undesirable
  distance `is` Medium   = Undesirable
  distance `is` Melee= Undesirable

  (distance `fairly` Near)  (ammo `fairly` High) = VeryDesirable
  (distance `fairly` Near)  (ammo `fairly` Good) = Desirable
  (distance `fairly` Near)  (ammo `is` Low)  = Undesirable

 

 Full code at 
 http://code.haskell.org/~hexpuem/fuzzyLogic/http://code.haskell.org/%7Ehexpuem/fuzzyLogic/
 .

 Suggestions welcome - maybe it'd be useful to upload to hackage at some
 point.


 It only supports triangle, shoulder, and singleton memberships at the
 moment.



 ___
 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] 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 university groups, the IHG funds Well-Typed to do
development, as well.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 give you an instance 
automagically. It could have been the case that you intended some other 
instance besides []'s. All generalized newtype deriving does is derive 
instances for newtypes that wrap exactly what the instance is defined over.


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