Re: [Haskell-cafe] Rewrite this imperative in FP way

2012-02-05 Thread Roman Cheplyaka
* Haisheng Wu fre...@gmail.com [2012-02-05 14:28:10+0800]
 a = [1,1,1,1]
 b = [0,1,2,3]
 d = [0,0,0,0]
 
 for i in b:
   for j in c:
 if (i+j)3:
   d[i+j] += a[i]
 
 Do you have any cool solution in FP way?

You can use IntMap as a replacement for arrays:
(I didn't understand your algorithm exactly, since you use 'c', which is
not defined, but hopefully this is close enough)

import Control.Monad
import Data.List
import Data.IntMap as IntMap

a = [1,1,1,1]
b = [0,1,2,3]
c = IntMap.fromList $ zipWith (,) [0..] a

d = foldl' f IntMap.empty $ liftM2 (,) a b
where
f m (i, j) =
let s = i+j in
if s  3 then IntMap.insertWith (+) s (c ! i) m else m

main = print d

A single non-obvious thing here is liftM2 (,) a b -- it builds the
cartesian product of lists a and b and is used here to replace your
nested loops.

-- 
Roman I. Cheplyaka :: http://ro-che.info/

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


Re: [Haskell-cafe] Rewrite this imperative in FP way

2012-02-05 Thread Jon Fairbairn
Haisheng Wu fre...@gmail.com writes:

 a = [1,1,1,1]
 b = [0,1,2,3]
 d = [0,0,0,0]

 for i in b:
   for j in c:
 if (i+j)3:
   d[i+j] += a[i]
 Do you have any cool solution in FP way?

I find the above sufficiently alien that I can’t work out what
it’s meant to do (what is it actually for?). c is undefined for
one thing. But you might like to see what 

do i - b; j -c ; return (i,j)

does and consider what “filter ( 3) . map (uncurry (+))”
does, and possibly look at Data.Array.array, depending on what
the problem you are trying to solve is.

-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk



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


[Haskell-cafe] Fwd: Rewrite this imperative in FP way

2012-02-05 Thread L Corbijn
-- Forwarded message --
From: L Corbijn aspergesoe...@gmail.com
Date: Sun, Feb 5, 2012 at 10:07 AM
Subject: Re: [Haskell-cafe] Rewrite this imperative in FP way
To: Haisheng Wu fre...@gmail.com


On Sun, Feb 5, 2012 at 7:28 AM, Haisheng Wu fre...@gmail.com wrote:
 a = [1,1,1,1]
 b = [0,1,2,3]
 d = [0,0,0,0]

 for i in b:
   for j in c:
     if (i+j)3:
       d[i+j] += a[i]

 My just work implementation in Haskell
 http://hpaste.org/57452

 Another people implementation in Haskell with Monad and it turns out complex
 and very imperatively.
 http://hpaste.org/57358

 Do you have any cool solution in FP way?

 Thanks.
 -Simon

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


Oops forgot to reply to the list,

There are several ways to make it nicer.
Without assumption on what lists a, b and c contain it can be written as
d = [sum $ map (a !!) [i | i - b, j - c, i + j  3, i + j == dIndex]
| dIndex - [0..3]]

With the assumption that b and c are both [0..3] this can be 'improved' to
d = (take 3 . map sum . tail $ inits a) ++ replicate (4 - 3) 0
This generates the first three values by the complicated expression
and then adds the extra zero's by using the replicate expression. This
works as the value of the i-th element of d is the sum over the first
i elements in a if i  3 and 0 otherwise. A list of lists with the
first i elements is generated with 'tail $ inits a' which is then
summed and restricted to length 3.
An alternative for this is
d = (take 3 . snd $ mapAccumL (\acc ai - (acc + ai, acc + ai)) 0 a)
++ replicate (4 - 3) 0
Where the summation and tail generating is done in the mapAccumL function.

Greetings,
Lars

P.S. Yes the replicate (4-3) 0 can be replaced by [0], but I wanted to
explicitly include the length (4) of the expected list.
P.P.S. for those of you wondering what c is, looking at the solutions in hpaste
c is probably defined as c = [0..3].

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


Re: [Haskell-cafe] ANN: combinatorics

2012-02-05 Thread Daniel Fischer
On Wednesday 01 February 2012, 07:53:03, wren ng thornton wrote:
  The primes function in the combinat package is based on an old Cafe
  thread, and actually seems to be faster than the one in the
  combinatorics package.

Yes, but it has a memory leak. On my box at least, with ghc 6.12, 7.0 and 
7.2.

 
 The primes generator was some old code I had laying around for one of 
 those online programming challenges; fast enough for the task.
 I'll  probably trade it in for your algorithm though.

Why not use one of the packages on hackage which offer faster prime 
generators?

I'm aware of the following usable packages:

- primes: decentish performance if you don't need to sieve high, but not 
recommendable if you want to sieve above ~10^7, in my measurements about 
the same performance as the algorithm used in combinat, but without memory 
leak.

- NumberSieves: The O'Neill sieve, about twice as fast as the primes sieve, 
uses less memory (and scales better if you want to sieve to higher limits).

- arithmoi: A segmented Eratosthenes sieve using mutable unboxed arrays. 
Much faster than the above and uses less memory.
If you don't like arrays, it also has a priority queue sieve similar to the 
O'Neill sieve, but with a more efficient PQ implementation.

 One of the things
 I'm disappointed by about the current implementation is the memory
 overhead for storing the primes. It'd be nice to use chunked arrays of
 unboxed integers in order to remove all the pointers; but my attempt at
 doing so  had catastrophic performance...

arithmoi's Eratosthenes sieve offers the option to get a list of sieve 
chunks, basically UArray Int Bool, which gives far more compact storage 
than a list of Integers (~33KB per million range, much more compact than an 
unboxed array of primes for the reachable ranges) from which the list of 
primes can rather efficiently obtained when needed. That may do what you 
want well enough.

Cheers,
Daniel

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


Re: [Haskell-cafe] Rewrite this imperative in FP way

2012-02-05 Thread Haisheng Wu
Sorry there is a mistake in the problem description.
Here it is in Python:

a = [1,1,1,1] b = [0,1,2,3] c = [0,2] d = [0,0,0,0]
for i in b:
for j in c:
if (i+j)3:
d[i+j] += a[i]


-Haisheng


On Sun, Feb 5, 2012 at 2:28 PM, Haisheng Wu fre...@gmail.com wrote:

 a = [1,1,1,1]
 b = [0,1,2,3]
 d = [0,0,0,0]

 for i in b:
   for j in c:
 if (i+j)3:
   d[i+j] += a[i]

 My just work implementation in Haskell
 http://hpaste.org/57452

 Another people implementation in Haskell with Monad and it turns out
 complex and very imperatively.
 http://hpaste.org/57358

 Do you have any cool solution in FP way?

 Thanks.
 -Simon

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


Re: [Haskell-cafe] Rewrite this imperative in FP way

2012-02-05 Thread Yves Parès
Concerning your first solution, I don't understand why you redefine Eq but
not Ord instance. Ord will still work by comparing the tuples and not the
first elements of said tuples.
Plus the good news is you don't have to do this: just use regular tuples
and use sort*By *or group*By *functions from Data.List with the 'on'
function from Data.Function.
For instance your Eq instance could have been written
x == y = (==) `on` (fst . getTuple)

With regular tuples you can write sortBy (compare `on` fst).


Plus can you rewrite your original imperative algorithm with the right
variable names? You're using a 'd' array that's not been defined.


2012/2/5 Haisheng Wu fre...@gmail.com

 a = [1,1,1,1]
 b = [0,1,2,3]
 d = [0,0,0,0]

 for i in b:
   for j in c:
 if (i+j)3:
   d[i+j] += a[i]

 My just work implementation in Haskell
 http://hpaste.org/57452

 Another people implementation in Haskell with Monad and it turns out
 complex and very imperatively.
 http://hpaste.org/57358

 Do you have any cool solution in FP way?

 Thanks.
 -Simon

 ___
 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] Rewrite this imperative in FP way

2012-02-05 Thread Yves Parès
 For instance your Eq instance could have been written
 x == y = (==) `on` (fst . getTuple)

Sorry, wrong arity:
(==) = (==) `on` (fst . getTuple)

Okay for the imperative code.

2012/2/5 Yves Parès yves.pa...@gmail.com

 Concerning your first solution, I don't understand why you redefine Eq but
 not Ord instance. Ord will still work by comparing the tuples and not the
 first elements of said tuples.
 Plus the good news is you don't have to do this: just use regular tuples
 and use sort*By *or group*By *functions from Data.List with the 'on'
 function from Data.Function.
 For instance your Eq instance could have been written
 x == y = (==) `on` (fst . getTuple)

 With regular tuples you can write sortBy (compare `on` fst).


 Plus can you rewrite your original imperative algorithm with the right
 variable names? You're using a 'd' array that's not been defined.


 2012/2/5 Haisheng Wu fre...@gmail.com

 a = [1,1,1,1]
 b = [0,1,2,3]
 d = [0,0,0,0]

 for i in b:
   for j in c:
 if (i+j)3:
   d[i+j] += a[i]

 My just work implementation in Haskell
 http://hpaste.org/57452

 Another people implementation in Haskell with Monad and it turns out
 complex and very imperatively.
 http://hpaste.org/57358

 Do you have any cool solution in FP way?

 Thanks.
 -Simon

 ___
 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] Rewrite this imperative in FP way

2012-02-05 Thread Morel Pisum

+= a[i] is the same as +=1, isn't it?

(i accidentally didn't reply to the list on my first try. sorry.)


Am 05.02.2012 16:36, schrieb Haisheng Wu:

Sorry there is a mistake in the problem description.
Here it is in Python:

a = [1,1,1,1] b = [0,1,2,3] c = [0,2] d = [0,0,0,0]
for i in b:
 for j in c:
 if (i+j)3:
 d[i+j] += a[i]


-Haisheng


On Sun, Feb 5, 2012 at 2:28 PM, Haisheng Wufre...@gmail.com  wrote:


a = [1,1,1,1]
b = [0,1,2,3]
d = [0,0,0,0]

for i in b:
   for j in c:
 if (i+j)3:
   d[i+j] += a[i]

My just work implementation in Haskell
http://hpaste.org/57452

Another people implementation in Haskell with Monad and it turns out
complex and very imperatively.
http://hpaste.org/57358

Do you have any cool solution in FP way?

Thanks.
-Simon




___
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] Rewrite this imperative in FP way

2012-02-05 Thread Mike Burns
Can you write it as a Python function? Another way of asking: is the
goal to mutate  d  or is it to produce the list?

On 2012-02-05 23.36.28 +0800, Haisheng Wu wrote:
 Sorry there is a mistake in the problem description.
 Here it is in Python:
 
 a = [1,1,1,1] b = [0,1,2,3] c = [0,2] d = [0,0,0,0]
 for i in b:
 for j in c:
 if (i+j)3:
 d[i+j] += a[i]
 
 
 -Haisheng
 
 
 On Sun, Feb 5, 2012 at 2:28 PM, Haisheng Wu fre...@gmail.com wrote:
 
  a = [1,1,1,1]
  b = [0,1,2,3]
  d = [0,0,0,0]
 
  for i in b:
for j in c:
  if (i+j)3:
d[i+j] += a[i]
 
  My just work implementation in Haskell
  http://hpaste.org/57452
 
  Another people implementation in Haskell with Monad and it turns out
  complex and very imperatively.
  http://hpaste.org/57358
 
  Do you have any cool solution in FP way?
 
  Thanks.
  -Simon
 

 ___
 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] Rewrite this imperative in FP way

2012-02-05 Thread Matthew Farkas-Dyck
On Sun, Feb 5, 2012 at 2:28 PM, Haisheng Wu fre...@gmail.com wrote:
 for i in b:
   for j in c:
 if (i+j)3:
   d[i+j] += a[i]

 Do you have any cool solution in FP way?

Not sure whether this is cool, but here it is nonetheless:

a = repeat 1;
b = [0..3];
c = [0,2];
d = map (sum ∘ map ((a !!) ∘ fromIntegral) ∘ ($ (filter (3) ∘ map sum
∘ sequence) [b,c]) ∘ filter ∘ (≡)) [1..];

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


[Haskell-cafe] Increase GHC stack size?

2012-02-05 Thread Michael Rice
Stack space overflow: current size 8388608 bytes.
Use `+RTS -Ksize -RTS' to increase it.

==

Couldn't find much on the man or info pages. Example please, say double it
(1600) for starters.

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


Re: [Haskell-cafe] Increase GHC stack size?

2012-02-05 Thread Mathijs Kwik
./myProgram +RTS -K1600

If that gives an error, you're program was probably compiled without
support for setting RTS options from the command line.
Recompile with -rtsopts.
Then the above should work



On Sun, Feb 5, 2012 at 8:16 PM, Michael Rice limitc...@gmail.com wrote:
 Stack space overflow: current size 8388608 bytes.
 Use `+RTS -Ksize -RTS' to increase it.

 ==

 Couldn't find much on the man or info pages. Example please, say double it
 (1600) for starters.

 Michael


 ___
 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] Increase GHC stack size?

2012-02-05 Thread Michael Rice
I'm using
ghc --make...

-rtsopts seems to be a link directive.

The GHC docs seem to be project oriented. What's the two step process to
compile and link a simple .hs file?

ghc source.hs (to compile)

link step?

Michael





On Sun, Feb 5, 2012 at 2:21 PM, Mathijs Kwik math...@bluescreen303.nlwrote:

 ./myProgram +RTS -K1600

 If that gives an error, you're program was probably compiled without
 support for setting RTS options from the command line.
 Recompile with -rtsopts.
 Then the above should work



 On Sun, Feb 5, 2012 at 8:16 PM, Michael Rice limitc...@gmail.com wrote:
  Stack space overflow: current size 8388608 bytes.
  Use `+RTS -Ksize -RTS' to increase it.
 
  ==
 
  Couldn't find much on the man or info pages. Example please, say double
 it
  (1600) for starters.
 
  Michael
 
 
  ___
  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] Increase GHC stack size?

2012-02-05 Thread Krzysztof Skrzętnicki
No, you supply -rtsopts along with --make. Actually --make is just a
shorthand for a few other options, you can see which with --verbose. See
the documentation too.

One important thing though: very often stack overflows come from bad code.
See the wiki for more info:
http://www.haskell.org/haskellwiki/Stack_overflow

Best regards,
Krzysztof Skrzętnicki

On Sun, Feb 5, 2012 at 20:50, Michael Rice limitc...@gmail.com wrote:

 I'm using
 ghc --make...

 -rtsopts seems to be a link directive.

 The GHC docs seem to be project oriented. What's the two step process to
 compile and link a simple .hs file?

 ghc source.hs (to compile)

 link step?

 Michael





 On Sun, Feb 5, 2012 at 2:21 PM, Mathijs Kwik math...@bluescreen303.nlwrote:

 ./myProgram +RTS -K1600

 If that gives an error, you're program was probably compiled without
 support for setting RTS options from the command line.
 Recompile with -rtsopts.
 Then the above should work



 On Sun, Feb 5, 2012 at 8:16 PM, Michael Rice limitc...@gmail.com wrote:
  Stack space overflow: current size 8388608 bytes.
  Use `+RTS -Ksize -RTS' to increase it.
 
  ==
 
  Couldn't find much on the man or info pages. Example please, say double
 it
  (1600) for starters.
 
  Michael
 
 
  ___
  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] Increase GHC stack size?

2012-02-05 Thread Michael Rice
I had tried -rtsopts in a few spots in the command line, both with and
without --make, seemingly with no effect .

There was indeed a code problem, a function applied to an expression that
should have been in parens. Shoulda known better.

Thanks, all.

Michael

2012/2/5 Krzysztof Skrzętnicki gte...@gmail.com

 No, you supply -rtsopts along with --make. Actually --make is just a
 shorthand for a few other options, you can see which with --verbose. See
 the documentation too.

 One important thing though: very often stack overflows come from bad code.
 See the wiki for more info:
 http://www.haskell.org/haskellwiki/Stack_overflow

 Best regards,
 Krzysztof Skrzętnicki

 On Sun, Feb 5, 2012 at 20:50, Michael Rice limitc...@gmail.com wrote:

 I'm using
 ghc --make...

 -rtsopts seems to be a link directive.

 The GHC docs seem to be project oriented. What's the two step process to
 compile and link a simple .hs file?

 ghc source.hs (to compile)

 link step?

 Michael





 On Sun, Feb 5, 2012 at 2:21 PM, Mathijs Kwik math...@bluescreen303.nlwrote:

 ./myProgram +RTS -K1600

 If that gives an error, you're program was probably compiled without
 support for setting RTS options from the command line.
 Recompile with -rtsopts.
 Then the above should work



 On Sun, Feb 5, 2012 at 8:16 PM, Michael Rice limitc...@gmail.com
 wrote:
  Stack space overflow: current size 8388608 bytes.
  Use `+RTS -Ksize -RTS' to increase it.
 
  ==
 
  Couldn't find much on the man or info pages. Example please, say
 double it
  (1600) for starters.
 
  Michael
 
 
  ___
  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


[Haskell-cafe] ANN: exists-0.1

2012-02-05 Thread Gábor Lehel
There's a common pattern in Haskell of writing:

data E where E :: C a = a - E
also written
data E = forall a. C a = E a

I recently uploaded a package to Hackage which uses the new
ConstraintKinds extension to factor this pattern out into an Exists
type parameterized on the constraint, and also for an Existential type
class which can encompass these kind of types:

http://hackage.haskell.org/package/exists

My motivation was mostly to play with my new toys, if it turns out to
be useful for anything that's a happy and unexpected bonus.

Some interesting things I stumbled upon while writing it:

- Did you know you can write useful existentials for Functor,
Foldable, and Traversable? I sure didn't beforehand.

- You can even write them for various Comonad classes, though in their
case I don't think it's good for anything because you have no way to
run them.

- Surprisingly to me, the only * kinded class in the standardish
libraries I found which is useful with existentials is Show, the * -
* kinded ones are more numerous.

- I don't know if anyone's ever set out what the precise requirements
are for a type class method to be useful with existentials. For
example, any method which requires two arguments of the same type (the
type in the class head) is clearly useless, because if you have two
existentials there's no way to tell whether or not their contents were
of the same type. I think this holds any time you have more than one
value of the type among the method's parameters in any kind of way
(even if it's e.g. a single parameter that's a list). If the
type-from-the-class-head (is there a word for this?) is used in the
method's parameters in a position where it's not the outermost type
constructor of a type (i.e. it's a type argument), that's also no
good, because there's no way to extract the type from the existential,
you can only extract the value. On the other hand, in the method's
return type it's fine if there are multiple values of the
type-from-the-class-head (or if it's used as a type argument?),
because (as long as the method also has an argument of the type) the
type to put into the resulting existentials can be deduced to be the
same as the one that was in the argument. But if the
type-from-the-class-head is used *only* in the return type, then it's
difficult to construct an existential out of the return value because
the instance to use will be ambiguous.

- There are a lot of ways you can write existentials, and the library
only captures a small part of them. Multiparameter constraint? No go.
More than one constraint? No go (though you can use
Control.Constraint.Combine). More than one type/value stored? No go.
Anything which doesn't exactly match the patterns data E where E :: C
a = a - E or data E a where E :: C f = f a - E a? No go. I don't
think there's any way to capture all of the possibilities in a finite
amount of code.

- ConstraintKinds lets you write class aliases as type synonyms, type
Stringy a = (Show a, Eq a). The old way to do this is class (Show a,
Eq a) = Stringy a; instance (Show a, Eq a) = Stringy a and requires
UndecidableInstances. But if the alias has multiple parameters, the
old way is still superior, because it can be partially applied where
type synonyms can't. This is analogous to the situation with type
synonyms versus newtype/data declarations, but interestingly, unlike
data and newtypes, the class+instance method doesn't require you to do
any manual wrapping and unwrapping, only the declaration itself is
different.

- One of the advantages FunctionalDependencies has over TypeFamilies
is that type signatures using them tend to be more readable and
concise than ones which have to write out explicit equality
constraints. For example, foo :: MonadState s m = s - m () is nicer
than foo :: (MonadState m, State m ~ s) = s - m (). But with
equality superclass constraints (as of GHC 7.2), it's possible to
translate from TF-form to FD-form (but not the reverse, as far as I
know): class (MonadStateTF m, s ~ State m) = MonadStateFDish s m;
instance (MonadStateTF m, s ~ State m) = MonadStateFDish s m.

- PolyKinds only seems to be useful as long as there's no value-level
representation of the polykinded type involved (it's only used as a
phantom). As soon as you have to write 'a' for kind * and 'f a' for
kind * - *, you have to do the duplication manually. Is this right?

- Writing this library really made me want to have a type-level Ord
instance for constraints, more precisely a type-level is-implied-by
operator. The typechecker clearly knows that Eq is-implied-by Ord, for
example, and that Foo is-implied-by (Foo :: Bar), but I have no way
to ask it, I can only use (~). I tried implementing this with
OverlappingInstances, but it seems to be fundamentally impossible
because you really need a transitive case (instance (c :=: d, d :=:
e) = c :=: e) but the transitive case can't work. (My best
understanding is that it's because the typechecker doesn't work
forward, seeing ah, c 

Re: [Haskell-cafe] ANN: combinatorics

2012-02-05 Thread wren ng thornton

On 2/5/12 10:21 AM, Daniel Fischer wrote:

Why not use one of the packages on hackage which offer faster prime
generators?


Mostly because I hadn't looked, having had the code already laying 
around. I'm not opposed to it, however another goal is to remain 
portable to other compilers, which means being H98/H2010 compliant. 
NumberSieves uses BangPatterns, but that would be easily remedied if the 
author is willing; arithmoi looks quite nice, however it is GHC-only.


--
Live well,
~wren

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


[Haskell-cafe] ANNOUNCE: system-filepath 0.4.5 and system-fileio 0.3.4

2012-02-05 Thread John Millikin
Both packages now have much-improved support for non-UTF8 paths on
POSIX systems. There are no significant changes to Windows support in
this release.

system-filepath 0.4.5:
Hackage: http://hackage.haskell.org/package/system-filepath-0.4.5
API reference: 
https://john-millikin.com/software/haskell-filesystem/reference/system-filepath/0.4.5/

system-fileio 0.3.4:
Hackage: http://hackage.haskell.org/package/system-fileio-0.3.4
API reference: 
https://john-millikin.com/software/haskell-filesystem/reference/system-fileio/0.3.4/Filesystem/

-

In GHC  7.2 and later, file path handling in the platform libraries
was changed to treat all paths as text (encoded according to locale).
This does not work well on POSIX systems, because POSIX paths are byte
sequences. There is no guarantee that any particular path will be
valid in the user's locale encoding.

system-filepath and system-fileio were modified to partially support
this new behavior, but because the underlying libraries were unable to
represent certain paths, they were still broken when built with GHC
7.2+. The changes in this release mean that they are now fully
compatible (to the best of my knowledge) with GHC 7.2 and 7.4.

Important changes:

* system-filepath has been converted from GHC's escaping rules to its
own, more compatible rules. This lets it support file paths that
cannot be represented in GHC 7.2's escape format.

* The POSIX layer of system-fileio has been completely rewritten to
use the FFI, rather than System.Directory. This allows it to work with
arbitrary POSIX paths, including those that GHC itself cannot handle.
The Windows layer still uses System.Directory, since it seems to work
properly.

* The POSIX implementation of createTree will no longer recurse into
directory symlinks that it does not have permission to remove. This is
a change in behavior from the directory package's implementation. See
http://www.haskell.org/pipermail/haskell-cafe/2012-January/098911.html
for details and the reasoning behind the change. Since Windows does
not support symlinks, I have not modified the Windows implementation
(which uses removeDirectoryRecursive).

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


Re: [Haskell-cafe] ANN: combinatorics

2012-02-05 Thread Daniel Fischer
On Sunday 05 February 2012, 23:14:35, wren ng thornton wrote:
 On 2/5/12 10:21 AM, Daniel Fischer wrote:
  Why not use one of the packages on hackage which offer faster prime
  generators?
 
 Mostly because I hadn't looked, having had the code already laying
 around.

Yeah, that's fine, it was just

  I'll  probably trade it in for your algorithm though.

that made me wonder.

 I'm not opposed to it, however another goal is to remain
 portable to other compilers, which means being H98/H2010 compliant.

A noble goal.

 NumberSieves uses BangPatterns, but that would be easily remedied if the
 author is willing; arithmoi looks quite nice, however it is GHC-only.

The curse of striving for efficiency.
Portability is on the to-do list (with low priority, however).
It just climbed a place.

Cheers,
Daniel


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


[Haskell-cafe] ANN: Updated OpenGL libraries

2012-02-05 Thread Jason Dagit
Hello,

I'm pleased to anounce a minor bug fix release of the OpenGL
libraries.  This release was prompted by issues and warnings when
compiling with ghc-7.4.1.

The following packages have been updated:
  * OpenGLRaw 1.2.0.0
  * OpenGL 2.5.0.0
  * GLURaw 1.2.0.0
  * GLUT 2.3.0.0

Thanks goes out to:
  * Corey O'Connor
  * mgajda (github id)
  * #haskell-game and #haskell on freenode

The changes include:
  * Removing a data type context
  * Exposing the GLfoo constructors from OpenGLRaw
  * Deriving Typeable instead of using the now deprecated mkTyCon
  * Added Eq constraint, necessary now that Num doesn't have an Eq constraint
  * Tighten constraints in cabal files
  * Conservative package version bump (X.Y.Z - X.(Y+1).0)

As usual, please submit pull requests and bug reports on github:
https://github.com/haskell-opengl

Thank you!
Jason

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


Re: [Haskell-cafe] ANN: combinatorics

2012-02-05 Thread wren ng thornton

On 2/5/12 5:40 PM, Daniel Fischer wrote:

On Sunday 05 February 2012, 23:14:35, wren ng thornton wrote:

On 2/5/12 10:21 AM, Daniel Fischer wrote:

Why not use one of the packages on hackage which offer faster prime
generators?


Mostly because I hadn't looked, having had the code already laying
around.


Yeah, that's fine, it was just


I'll  probably trade it in for your algorithm though.


that made me wonder.


Well, I would've looked around before making the change :)



I'm not opposed to it, however another goal is to remain
portable to other compilers, which means being H98/H2010 compliant.


A noble goal.


By which I really mean H98/H2010 plus all the things that were already 
'standard' in the days of GHC 6.6 and Hugs. MPTCs and some of the 
related extensions for making type classes more flexible really need to 
be added to the standard, despite the valid political reasons for 
wanting to wait for the FD vs TF/AT issues to get resolved.




NumberSieves uses BangPatterns, but that would be easily remedied if the
author is willing; arithmoi looks quite nice, however it is GHC-only.


The curse of striving for efficiency.
Portability is on the to-do list (with low priority, however).
It just climbed a place.


Unless I'm doing something that by its nature requires GHC extensions, 
I've been doing my best to avoid them in published packages. Not that I 
have anything against them, but rather that I'd like to support JHC, 
UHC, and other alternatives (just as I used to support Hugs before it 
died). I think there's great value in compiler competition, so I'd like 
to foster it as much as I can. There're quite a number of efficiency 
hacks you can do while remaining in standard Haskell (and you can always 
hide the GHC-only parts with CPP).


--
Live well,
~wren

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


Re: [Haskell-cafe] ANN: exists-0.1

2012-02-05 Thread Yves Parès
That is a great initiative.
I didn't know about those Kind extensions that enable you to pass a
typeclass as a type parameter...

However, have you considered putting the Data.Exists.Default module in a
separate package? That would reduce the dependencies for those who just
need Exists and Existential.

2012/2/5 Gábor Lehel illiss...@gmail.com

 There's a common pattern in Haskell of writing:

 data E where E :: C a = a - E
 also written
 data E = forall a. C a = E a

 I recently uploaded a package to Hackage which uses the new
 ConstraintKinds extension to factor this pattern out into an Exists
 type parameterized on the constraint, and also for an Existential type
 class which can encompass these kind of types:

 http://hackage.haskell.org/package/exists

 My motivation was mostly to play with my new toys, if it turns out to
 be useful for anything that's a happy and unexpected bonus.

 Some interesting things I stumbled upon while writing it:

 - Did you know you can write useful existentials for Functor,
 Foldable, and Traversable? I sure didn't beforehand.

 - You can even write them for various Comonad classes, though in their
 case I don't think it's good for anything because you have no way to
 run them.

 - Surprisingly to me, the only * kinded class in the standardish
 libraries I found which is useful with existentials is Show, the * -
 * kinded ones are more numerous.

 - I don't know if anyone's ever set out what the precise requirements
 are for a type class method to be useful with existentials. For
 example, any method which requires two arguments of the same type (the
 type in the class head) is clearly useless, because if you have two
 existentials there's no way to tell whether or not their contents were
 of the same type. I think this holds any time you have more than one
 value of the type among the method's parameters in any kind of way
 (even if it's e.g. a single parameter that's a list). If the
 type-from-the-class-head (is there a word for this?) is used in the
 method's parameters in a position where it's not the outermost type
 constructor of a type (i.e. it's a type argument), that's also no
 good, because there's no way to extract the type from the existential,
 you can only extract the value. On the other hand, in the method's
 return type it's fine if there are multiple values of the
 type-from-the-class-head (or if it's used as a type argument?),
 because (as long as the method also has an argument of the type) the
 type to put into the resulting existentials can be deduced to be the
 same as the one that was in the argument. But if the
 type-from-the-class-head is used *only* in the return type, then it's
 difficult to construct an existential out of the return value because
 the instance to use will be ambiguous.

 - There are a lot of ways you can write existentials, and the library
 only captures a small part of them. Multiparameter constraint? No go.
 More than one constraint? No go (though you can use
 Control.Constraint.Combine). More than one type/value stored? No go.
 Anything which doesn't exactly match the patterns data E where E :: C
 a = a - E or data E a where E :: C f = f a - E a? No go. I don't
 think there's any way to capture all of the possibilities in a finite
 amount of code.

 - ConstraintKinds lets you write class aliases as type synonyms, type
 Stringy a = (Show a, Eq a). The old way to do this is class (Show a,
 Eq a) = Stringy a; instance (Show a, Eq a) = Stringy a and requires
 UndecidableInstances. But if the alias has multiple parameters, the
 old way is still superior, because it can be partially applied where
 type synonyms can't. This is analogous to the situation with type
 synonyms versus newtype/data declarations, but interestingly, unlike
 data and newtypes, the class+instance method doesn't require you to do
 any manual wrapping and unwrapping, only the declaration itself is
 different.

 - One of the advantages FunctionalDependencies has over TypeFamilies
 is that type signatures using them tend to be more readable and
 concise than ones which have to write out explicit equality
 constraints. For example, foo :: MonadState s m = s - m () is nicer
 than foo :: (MonadState m, State m ~ s) = s - m (). But with
 equality superclass constraints (as of GHC 7.2), it's possible to
 translate from TF-form to FD-form (but not the reverse, as far as I
 know): class (MonadStateTF m, s ~ State m) = MonadStateFDish s m;
 instance (MonadStateTF m, s ~ State m) = MonadStateFDish s m.

 - PolyKinds only seems to be useful as long as there's no value-level
 representation of the polykinded type involved (it's only used as a
 phantom). As soon as you have to write 'a' for kind * and 'f a' for
 kind * - *, you have to do the duplication manually. Is this right?

 - Writing this library really made me want to have a type-level Ord
 instance for constraints, more precisely a type-level is-implied-by
 operator. The typechecker clearly knows that Eq 

[Haskell-cafe] Greetings and Maybe GSoC-2012

2012-02-05 Thread Sergiu Ivanov
Hello everyone,

(long mail ahead)

My name is Sergiu Ivanov, I have been trying to wrap my mind around
Haskell for 2 years already, but success still feels far away :-) This
makes me more and more attached to Haskell though, so I can plainly
say: I love this language :-)

I guess I should have joined the online Haskell community wy
earlier; too bad the idea's only struck me now.  Therefore, I'd like
to hereby greet everyone and wish a lot of good luck and good fun with
whatever Haskell-related and non-Haskell-related tasks you may be on!
:-)

I have graduated Computer Science and I'm now pursuing my MSc in what
is officially referred to Mathematics and Informatics (sic), but has
turned out to be quite heavily biased towards algebra for me.  The
subject I currently seriously focus on is category theory; I have
graduated a course in module theory and I'm now going through
quasigroups, lattices, and Gröbner bases.  I'm doing some research in
computability theory, namely, in P systems
(http://en.wikipedia.org/wiki/P_system), but also other computing
devices, including some attempts at quantum computer science.

My usual IRC nickname is scolobb, and I plan to be hanging out on
#haskell quite regularly.  I'd be glad to contribute to the community
with whatever knowledge and skill assets I'd be able to provide :-)

(End of Presentation)

I'll turn to the Maybe part of the subject of this letter now.  I've
seen haskell.org has participated as an org in GSoC 2011.  If the
community plans to file an application this year as well and if
haskell.org is accepted again, I'd be happy to submit an application
for some fancy project.  I'd enjoy working on something hard,
requiring a lot of mental effort to understand, something which would
make me feel cleverer when I have finished it :-) I have a fairly
broad experience with programming languages and frameworks, so I don't
mind committing to
http://hackage.haskell.org/trac/summer-of-code/ticket/1592 ,
http://hackage.haskell.org/trac/summer-of-code/ticket/1547 , or
http://hackage.haskell.org/trac/summer-of-code/ticket/1583 .  However,
among my favourites is this one:
http://hackage.haskell.org/trac/summer-of-code/ticket/1582 .  This one
sounds complicated and mixing a lot of stuff.  My experience with LLVM
is zero, but I'm willing to learn, of course.

You can apprehend my Haskell skills by throwing a look at
https://gitorious.org/remoting and
https://gitorious.org/psim/haskellengine .  The first one is a simple
actor-model based remoting framework; that was a project for one of
the university projects.  The second one is a part of my graduation
project, in which I mixed Java, Jython, CUDA and, of course, Haskell.
I'm not trying to boast, though: I can easily see the yet unwide
horizon of my Haskell knowledge, which I would like to expand as far
as possible.

As far as I remember from my previous experience with GSoC, potential
students are required to solve some simpler tasks to show what they're
capable of.  I understand that it's quite premature to talk about the
summer of code as yet, but I'd be glad to hear of such possible test
(or not-so-test) tasks which I could complete.

Thank you for reading this much,
Sergiu

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


Re: [Haskell-cafe] ANNOUNCE: system-filepath 0.4.5 and system-fileio 0.3.4

2012-02-05 Thread Joey Hess
John Millikin wrote:
 In GHC  7.2 and later, file path handling in the platform libraries
 was changed to treat all paths as text (encoded according to locale).
 This does not work well on POSIX systems, because POSIX paths are byte
 sequences. There is no guarantee that any particular path will be
 valid in the user's locale encoding.

I've been dealing with this change too, but my current understanding
is that GHC's handling of encoding for FilePath is documented to allow
arbitrary undecodable bytes to be round-tripped through it.

As long as FilePaths are read using this file system encoding, any
FilePath should be usable even if it does not match the user's encoding.

For FFI, anything that deals with a FilePath should use this
withFilePath, which GHC contains but doesn't export(?), rather than the
old withCString or withCAString:

import GHC.IO.Encoding (getFileSystemEncoding)
import GHC.Foreign as GHC

withFilePath :: FilePath - (CString - IO a) - IO a
withFilePath fp f = getFileSystemEncoding = \enc - GHC.withCString enc fp f

Code that reads or writes a FilePath to a Handle (including even to
stdout!) must take care to set the right encoding too:

fileEncoding :: Handle - IO ()
fileEncoding h = hSetEncoding h = getFileSystemEncoding

 * system-filepath has been converted from GHC's escaping rules to its
 own, more compatible rules. This lets it support file paths that
 cannot be represented in GHC 7.2's escape format.

I'm dobutful about adding yet another encoding to the mix. Things are
complicated enough already! And in my tests, GHC 7.4's FilePath encoding
does allow arbitrary bytes in FilePaths.

BTW, GHC now also has RawFilePath. Parts of System.Directory could be
usefully written to support that data type too. For example, the parent
directory can be determined. Other things are more difficult to do with
RawFilepath.

-- 
see shy jo


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


Re: [Haskell-cafe] ANNOUNCE: system-filepath 0.4.5 and system-fileio 0.3.4

2012-02-05 Thread John Millikin
On Sun, Feb 5, 2012 at 18:49, Joey Hess j...@kitenet.net wrote:
 John Millikin wrote:
 In GHC  7.2 and later, file path handling in the platform libraries
 was changed to treat all paths as text (encoded according to locale).
 This does not work well on POSIX systems, because POSIX paths are byte
 sequences. There is no guarantee that any particular path will be
 valid in the user's locale encoding.

 I've been dealing with this change too, but my current understanding
 is that GHC's handling of encoding for FilePath is documented to allow
 arbitrary undecodable bytes to be round-tripped through it.

 As long as FilePaths are read using this file system encoding, any
 FilePath should be usable even if it does not match the user's encoding.

That was my understanding also, then QuickCheck found a
counter-example. It turns out that there are cases where a valid path
cannot be roundtripped in the GHC 7.2 encoding.

--
$ ~/ghc-7.0.4/bin/ghci
Prelude writeFile .txt test
Prelude readFile .txt
test
Prelude

$ ~/ghc-7.2.1/bin/ghci
Prelude import System.Directory
Prelude System.Directory getDirectoryContents .
[\61347.txt,\61347.txt,..,.]
Prelude System.Directory readFile \61347.txt
*** Exception: .txt: openFile: does not exist (No such file or directory)
Prelude System.Directory
--

The issue is that  [238,189,178] decodes to 0xEF72, which is within
the 0xEF00-0xEFFF range that GHC uses to represent un-decodable bytes.

 For FFI, anything that deals with a FilePath should use this
 withFilePath, which GHC contains but doesn't export(?), rather than the
 old withCString or withCAString:

 import GHC.IO.Encoding (getFileSystemEncoding)
 import GHC.Foreign as GHC

 withFilePath :: FilePath - (CString - IO a) - IO a
 withFilePath fp f = getFileSystemEncoding = \enc - GHC.withCString enc fp f

If code uses either withFilePort or withCString, then the filenames
written will depend on the user's locale. This is wrong. Filenames are
either non-encoded text strings (Windows), UTF8 (OSX), or arbitrary
bytes (non-OSX POSIX). They must not change depending on the locale.

 Code that reads or writes a FilePath to a Handle (including even to
 stdout!) must take care to set the right encoding too:

 fileEncoding :: Handle - IO ()
 fileEncoding h = hSetEncoding h = getFileSystemEncoding

This is also wrong. A file path cannot be written to a handle with
any hope of correct behavior. If it's to be displayed to the user, a
path should be converted to text first, then displayed.

 * system-filepath has been converted from GHC's escaping rules to its
 own, more compatible rules. This lets it support file paths that
 cannot be represented in GHC 7.2's escape format.

 I'm dobutful about adding yet another encoding to the mix. Things are
 complicated enough already! And in my tests, GHC 7.4's FilePath encoding
 does allow arbitrary bytes in FilePaths.

Unlike the GHC encoding, this encoding is entirely internal, and
should not change the API's behavior.

 BTW, GHC now also has RawFilePath. Parts of System.Directory could be
 usefully written to support that data type too. For example, the parent
 directory can be determined. Other things are more difficult to do with
 RawFilepath.

This is new in 7.4, and won't be backported, right? I tried compiling
the new unix package in 7.2 to get proper file path support, but it
failed with an error about some new language extension.

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


Re: [Haskell-cafe] ANNOUNCE: system-filepath 0.4.5 and system-fileio 0.3.4

2012-02-05 Thread John Millikin
On Sun, Feb 5, 2012 at 19:17, John Millikin jmilli...@gmail.com wrote:
 --
 $ ~/ghc-7.0.4/bin/ghci
 Prelude writeFile .txt test
 Prelude readFile .txt
 test
 Prelude

Sorry, that got a bit mangled in the email. Corrected version:

--
$ ~/ghc-7.0.4/bin/ghci
Prelude writeFile \xA3.txt test
Prelude readFile \xA3.txt
test
Prelude writeFile \xEE\xBE\xA3.txt test 2
Prelude readFile \xEE\xBE\xA3.txt
test 2
--

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