[Haskell-cafe] Subject: ANNOUNCE: grid-3.0.1 (tile maps for board games or maths)

2013-02-18 Thread Amy de Buitléir
I'm happy to announce a new major release of the grid package:

http://hackage.haskell.org/package/grid
https://github.com/mhwombat/grid/wiki (wiki)

WHAT'S NEW:

Functions for reporting the boundary and centre of bounded grid have been added,
along with some miscellaneous new utility functions. IMPORTANT: The order of
parameters for some functions has changed to make it easier to use them with map
and fold operations.

ABOUT GRID:
Grid provides tools for working with regular arrangements of tiles, such as
might be used in a board game or self-organising map (SOM). Grid currently
supports triangular, square, and hexagonal tiles, with various 2D and toroidal
layouts. If you need a tile shape or layout that isn't currently provided,
please let me know. See Math.Geometry.Grid for an example of how to use the
package. Suggestions for improvement are welcome.


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


Re: [Haskell-cafe] Subject: ANNOUNCE: grid-3.0.1 (tile maps for board games or maths)

2013-02-18 Thread Twan van Laarhoven

On 18/02/13 13:41, Amy de Buitléir wrote:

I'm happy to announce a new major release of the grid package:

 http://hackage.haskell.org/package/grid
 https://github.com/mhwombat/grid/wiki (wiki)



After taking a peek at the documentation: have you considered removing the size 
function from Grid? It is the only function that actually uses the type 
parameter 's'. If you really need it, I would suggest putting it in a separate 
class,


class HasSize a s | a - s where
size :: a - s


It might also be useful to add a rectangular grid type where diagonally adjacent 
cells are also neighbors.


Another interesting idea is to have modifier types that change which cells are 
neighbors, for example you could have

class Colinear g x | g x where
-- | Are three points separated by moves in the same direction?
isColinear :: g - x - x - x - Bool

-- neighbors are separated by diagonal moves
newtype Diagonal g = Diagonal g
instance (Grid g, Colinear g x) = Grid (Diagonal g) x where
neighbors g x = [z | y - neigbhors x, z - neigbhors y
   , not (isColinear x y z)]

newtype Rook g = ...
newtype Knight g = ...
-- etc.


Twan

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


[Haskell-cafe] generalized, tail-recursive left fold that can finish tne computation prematurely

2013-02-18 Thread Petr Pudlák
Dear Haskellers,

while playing with folds and trying to implement `!!` by folding, I came to
the conclusion that:

- `foldr` is unsuitable because it counts the elements from the end, while
`!!` needs counting from the start (and it's not tail recursive).
- `foldl` is also unsuitable, because it always traverses the whole list.

I came up with the following tail-recursive generalization of `foldl` that
allows exiting the computation prematurely:

foldlE :: (a - c) - (a - b - Either c a) - Either c a - [b] - c
foldlE f g = fld
  where
fld (Left c)  _ = c
fld (Right a) []= f a
fld (Right a) (x:xs)= fld (g a x) xs

`foldl` can be defined from it  as

foldl'' :: (a - b - a) - a - [b] - a
foldl'' f z = foldlE id ((Right .) . f) (Right z)

and `!!` as:

-- Checks for a negative index omitted for brevity.
index :: Int - [a] - a
index i = foldlE (error $ No such index) f (Right i)
  where
f 0 x = Left x
f n _ = Right (n - 1)

Is something like that already available somewhere?

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


[Haskell-cafe] generalized, tail-recursive left fold that can finish tne computation prematurely

2013-02-18 Thread Petr Pudlák
Dear Haskellers,

while playing with folds and trying to implement `!!` by folding, I came to
the conclusion that:

- `foldr` is unsuitable because it counts the elements from the end, while
`!!` needs counting from the start (and it's not tail recursive).
- `foldl` is also unsuitable, because it always traverses the whole list.

I came up with the following tail-recursive generalization of `foldl` that
allows exiting the computation prematurely:

foldlE :: (a - c) - (a - b - Either c a) - Either c a - [b] - c
foldlE f g = fld
  where
fld (Left c)  _ = c
fld (Right a) []= f a
fld (Right a) (x:xs)= fld (g a x) xs

`foldl` can be defined from it  as

foldl'' :: (a - b - a) - a - [b] - a
foldl'' f z = foldlE id ((Right .) . f) (Right z)

and `!!` as:

-- Checks for a negative index omitted for brevity.
index :: Int - [a] - a
index i = foldlE (error $ No such index) f (Right i)
  where
f 0 x = Left x
f n _ = Right (n - 1)

Is something like that already available somewhere?

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


Re: [Haskell-cafe] generalized, tail-recursive left fold that can finish tne computation prematurely

2013-02-18 Thread Andres Löh
Hi.

 while playing with folds and trying to implement `!!` by folding, I came to
 the conclusion that:

 - `foldr` is unsuitable because it counts the elements from the end, while
 `!!` needs counting from the start (and it's not tail recursive).

What is the problem with the following definition using foldr?

 index :: Int - [a] - a
 index n xs =
   foldr
 (\ x r n - if n == 0 then x else r (n - 1))
 (const (error $ No such index))
 xs
 n

Cheers,
  Andres

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


Re: [Haskell-cafe] generalized, tail-recursive left fold that can finish tne computation prematurely

2013-02-18 Thread Roman Cheplyaka
* Petr Pudlák petr@gmail.com [2013-02-18 17:10:26+0100]
 Dear Haskellers,
 
 while playing with folds and trying to implement `!!` by folding, I came to
 the conclusion that:
 
 - `foldr` is unsuitable because it counts the elements from the end, while
 `!!` needs counting from the start (and it's not tail recursive).
 - `foldl` is also unsuitable, because it always traverses the whole list.

Every structurally-recursive function is definable through foldr,
because foldr *is* the structural recursion (aka catamorphism) operation
for lists.

Here the trick is to make the accumulator a function. This way you can
pass a value from left to right.

Something like

  foldr (\x rest n - ...) id list 0

I'll leave filling in the dots as an exercise.

Roman

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


Re: [Haskell-cafe] generalized, tail-recursive left fold that can finish tne computation prematurely

2013-02-18 Thread Roman Cheplyaka
* Roman Cheplyaka r...@ro-che.info [2013-02-18 18:28:47+0200]
 * Petr Pudlák petr@gmail.com [2013-02-18 17:10:26+0100]
  Dear Haskellers,
  
  while playing with folds and trying to implement `!!` by folding, I came to
  the conclusion that:
  
  - `foldr` is unsuitable because it counts the elements from the end, while
  `!!` needs counting from the start (and it's not tail recursive).
  - `foldl` is also unsuitable, because it always traverses the whole list.
 
 Every structurally-recursive function is definable through foldr,
 because foldr *is* the structural recursion (aka catamorphism) operation
 for lists.
 
 Here the trick is to make the accumulator a function. This way you can
 pass a value from left to right.
 
 Something like
 
   foldr (\x rest n - ...) id list 0
 
 I'll leave filling in the dots as an exercise.

Er, my template is not quite right — I had 'length' in mind while writing
it. Anyway, Andres showed the correct definition.

Roman

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


Re: [Haskell-cafe] generalized, tail-recursive left fold that can finish tne computation prematurely

2013-02-18 Thread Petr Pudlák
Thanks Roman and Andres for the tip. I knew the trick with accumulating a
function, but I had never imagined it could work so efficiently. I thought
the problem with using foldr would be that the function would be neither
tail recursive nor efficient and so I hadn't even tried. Apparently that
was wrong. After your suggestion I checked its performance and how it
compiles to core and to my surprise GHC optimizes the whole thing into a
most-efficient tail recursive function!

  Best regards,
  Petr


2013/2/18 Roman Cheplyaka r...@ro-che.info

 * Petr Pudlįk petr@gmail.com [2013-02-18 17:10:26+0100]
  Dear Haskellers,
 
  while playing with folds and trying to implement `!!` by folding, I came
 to
  the conclusion that:
 
  - `foldr` is unsuitable because it counts the elements from the end,
 while
  `!!` needs counting from the start (and it's not tail recursive).
  - `foldl` is also unsuitable, because it always traverses the whole list.

 Every structurally-recursive function is definable through foldr,
 because foldr *is* the structural recursion (aka catamorphism) operation
 for lists.

 Here the trick is to make the accumulator a function. This way you can
 pass a value from left to right.

 Something like

   foldr (\x rest n - ...) id list 0

 I'll leave filling in the dots as an exercise.

 Roman

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


[Haskell-cafe] layers: A prototypical 2d platform game

2013-02-18 Thread Daniel Trstenjak

Hi all,

also if there's not that much to see and only a few minutes of gameplay,
but after spending quite a few hours writing it, getting a feeling for
Haskell and it's usage, perhaps it's in some way useful for someone,
even if just for a few minutes of distraction.

https://github.com/dan-t/layers


Greetings,
Daniel

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


Re: [Haskell-cafe] generalized, tail-recursive left fold that can finish tne computation prematurely

2013-02-18 Thread Niklas Hambüchen
On 18/02/13 16:10, Petr Pudlák wrote:
 - `foldr` is unsuitable because it counts the elements from the end,
 while `!!` needs counting from the start (and it's not tail recursive).

It is common misconception that foldr processes the list from the right.

foldr brackets from the right, but this has nothing to do with
processing direction; all [a] are processed left to right, since this is
the only way to structurally deconstruct them.

This is the reason why it is possible to write
foldr (:) [] [1..]

If foldr processed the list from the right, it would on infinite lists -
and it does.

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


Re: [Haskell-cafe] Maintaining lambdabot

2013-02-18 Thread Jason Dagit
On Sun, Feb 17, 2013 at 8:53 PM, Cale Gibbard cgibb...@gmail.com wrote:

 On 17 February 2013 18:03, Jan Stolarek jan.stola...@p.lodz.pl wrote:
  ...
  This changes would be quite invasive and code wouldn't be compatible
 with the lambdabot repo on
  haskell.org. So before I start making any of them I would like to hear
 from the community if such
  changes in the source code of lambdabot would be  considered helpful and
 acceptable.
 
  Janek

 I say go for it! I'll be quite happy to start running your new code in
 #haskell as soon as we get GHC 7.6 installed on Jason's Linode
 account. :)


My name is Jason and I endorse this message :)

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


[Haskell-cafe] ~ operator ?

2013-02-18 Thread briand
Hi all,

I was creating bigger uncurries which I am simply extending from an existing 
uncurry I found some where, e.g.

uncurry4 :: (a - b - c - d - e) - ((a, b, c, d) - e)
uncurry4 f ~(a,b,c,d) = f a b c d

when I realized, what's the ~ for ?

I've only been able to find a partial explanation that it involves preserving 
laziness, or something, maybe ?

I was hoping someone could enlighten me.

Thanks

Brian


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


Re: [Haskell-cafe] ~ operator ?

2013-02-18 Thread Patrick Palka
The difference the ~ makes in this case is that `uncurry4 (\_ _ _ _ - ())
undefined` evaluates to `()` instead of bottom. The ~ is called an
irrefutable pattern, and it helps make code that pattern matches on
constructors more lazy. This seems like a good explanation of the subject:
http://en.wikibooks.org/wiki/Haskell/Laziness#Lazy_pattern_matching

On Mon, Feb 18, 2013 at 2:02 PM, bri...@aracnet.com wrote:

 Hi all,

 I was creating bigger uncurries which I am simply extending from an
 existing uncurry I found some where, e.g.

 uncurry4 :: (a - b - c - d - e) - ((a, b, c, d) - e)
 uncurry4 f ~(a,b,c,d) = f a b c d

 when I realized, what's the ~ for ?

 I've only been able to find a partial explanation that it involves
 preserving laziness, or something, maybe ?

 I was hoping someone could enlighten me.

 Thanks

 Brian


 ___
 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] Aeson + MongoDB, how to effortlessly store and retrieve json?

2013-02-18 Thread Alfredo Di Napoli
Good evening guys,

suppose I write a very simple parser using Aeson with these types and
ToJSON / FromJSON instances:

https://github.com/cakesolutions/the-pragmatic-haskeller/blob/master/01-json/Pragmatic/Types.hs
https://github.com/cakesolutions/the-pragmatic-haskeller/blob/master/01-json/Pragmatic/JSON/Parser.hs

My question is simple: is it possible to automagically store the haskell
data structure produced from the aeson encoding using

http://hackage.haskell.org/packages/archive/mongoDB/1.3.2/doc/html/Database-MongoDB-Query.html#g:7

Any tip/suggestion is welcome,

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


Re: [Haskell-cafe] ~ operator ?

2013-02-18 Thread briand
On Mon, 18 Feb 2013 19:13:13 +
Mateusz Kowalczyk fuuze...@fuuzetsu.co.uk wrote:

 On 18/02/13 19:02, bri...@aracnet.com wrote:
  Hi all,
  
  I was creating bigger uncurries which I am simply extending from an 
  existing uncurry I found some where, e.g.
  
  uncurry4 :: (a - b - c - d - e) - ((a, b, c, d) - e)
  uncurry4 f ~(a,b,c,d) = f a b c d
  
  when I realized, what's the ~ for ?
  
  I've only been able to find a partial explanation that it involves 
  preserving laziness, or something, maybe ?
  
  I was hoping someone could enlighten me.
  
  Thanks
  
  Brian
  
  
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
  
 
 [1] explains it in section 4.4 — ‘Lazy patterns’.
 
 [1] - http://www.haskell.org/tutorial/patterns.html
 

how strange - I was sure I looked through the tutorial...

Thanks Mateusz and Patrick.

Brian



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


Re: [Haskell-cafe] Aeson + MongoDB, how to effortlessly store and retrieve json?

2013-02-18 Thread Niklas Hambüchen
Not sure if this is helpful, but have a look at aesonbson:

https://github.com/nh2/aesonbson/blob/master/Data/AesonBson.hs

It can convert aeson to bson and the other way around, so you can easily
convert 'Object's to 'Document's.

Is that what you are looking for?

On 18/02/13 21:37, Alfredo Di Napoli wrote:
 My question is simple: is it possible to automagically store the
 haskell data structure produced from the aeson encoding using
 
 http://hackage.haskell.org/packages/archive/mongoDB/1.3.2/doc/html/Database-MongoDB-Query.html#g:7

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


Re: [Haskell-cafe] FunPtr to C function with #arguments determined atruntime?

2013-02-18 Thread Daniel Peebles
Considering that the GHC FFI is already built on libffi (I'm reasonably
sure) it seems unnecessary for the Hackage library to depend on an external
version. Is it not already getting linked in?


On Sun, Feb 17, 2013 at 6:53 PM, Ryan Newton rrnew...@gmail.com wrote:

  The scenario is pretty simple.  I generate C code at runtime.  I compile
 it
  to a .so.  I know how many arguments it expects (but only at runtime),
 and
  I get a FunPtr back from 'dlsym'.  How do I call it?
 I feel that I might be confused about the problem, but since I don't
 see anyone direct answers -- in order to call a FunPtr, you can use
 foreign import ccall dynamic, to create a regular function.   As
 described in the library documentation for Foreign.Ptr, which I bet
 you've seen, so you know this.

 You can cast the FunPtr to whatever type you like, so you can call the
 function with an argument list different from its initial declaration.


 My problem is that I can't create a type representing what I want at the
 Haskell type-check time, and I need such a type for either casting or a
 foreign import.  For example, let's say the function takes a number of Int
 arguments between 1 and 1000.  If I find out at runtime that I need a
 function with 613 Int arguments, I would need to create the type (Int -
 Int ... - IO ()) to cast to.  I suppose there may be some way to create
 such a dependent type with Typeable/Data.Dynamic, since it's monomorphic.
  Or in theory you could dynamically generate new Haskell code to create the
 type (System.Eval.Haskell)...

 libffi, which Krzysztof mentioned, is a good solution:

 http://www.haskell.org/haskellwiki/Library/libffi

 Because it allows you to pass a list of arguments

  callFFI :: FunPtr a - RetType b - [Arg] - IO b


 But it does introduce an extra dependency on a C library (read, deployment
 liability).  It cabal install'd the first time on my linux box, but my
 mac said The pkg-config package libffi is required but it could not be
 found.  (even though libffi.dylib is definitely installed globally).

 Anyway, in this case it wasn't *too *painful to just generate a bunch of
 extra boilerplate C functions for (1) creating a data structure to hold the
 arguments, (2) loading them in one at a time, and (3) deallocating the
 structure when the call is done.  Yuck.  But no extra dependencies.

 Cheers,
   -Ryan


 ___
 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] generalized, tail-recursive left fold that can finish tne computation prematurely

2013-02-18 Thread oleg

As others have pointed out, _in principle_, foldr is not at all
deficient. We can, for example, express foldl via foldr. Moreover, we
can express head, tail, take, drop and even zipWith through
foldr. That is, the entire list processing library can be written in
terms of foldr:

http://okmij.org/ftp/Algorithms.html#zip-folds

That said, to express foldl via foldr, we need a higher-order
fold. There are various problems with higher-order folds, related to
the cost of building closures. The problems are especially severe 
in strict languages or strict contexts. Indeed,

foldl_via_foldr f z l = foldr (\e a z - a (f z e)) id l z

first constructs the closure and then applies it to z. The closure has
the same structure as the list -- it is isomorphic to the
list. However, the closure representation of a list takes typically
quite more space than the list. So, in strict languages, expressing
foldl via foldr is a really bad idea. It won't work for big lists.
BTW, this is why foldM is _left_ fold.

The arguments against higher-order folds as a `big hammer' were made
back in 1998 by Gibbons and Jones
http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.42.1735

So, the left-fold with the early termination has a good
justification. In fact, this is how Iteratees were first presented, at
the DEFUN08 tutorial (part of the ICFP2008 conference). The idea of
left fold with early termination is much older though. For example, Takusen
(a database access framework) has been using it since 2003 or so. For
a bit of history, see

http://okmij.org/ftp/Streams.html#fold-stream


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


Re: [Haskell-cafe] Aeson + MongoDB, how to effortlessly store and retrieve json?

2013-02-18 Thread Alfredo Di Napoli
Hi Niklas,

From a quick look it seems to be suitable for my task. I'll have a look ASAP 
and I'll keep you posted.

Many thanks!

Alfredo Di Napoli

On 19/feb/2013, at 00:32, Niklas Hambüchen m...@nh2.me wrote:

 Not sure if this is helpful, but have a look at aesonbson:
 
 https://github.com/nh2/aesonbson/blob/master/Data/AesonBson.hs
 
 It can convert aeson to bson and the other way around, so you can easily
 convert 'Object's to 'Document's.
 
 Is that what you are looking for?
 
 On 18/02/13 21:37, Alfredo Di Napoli wrote:
 My question is simple: is it possible to automagically store the
 haskell data structure produced from the aeson encoding using
 
 http://hackage.haskell.org/packages/archive/mongoDB/1.3.2/doc/html/Database-MongoDB-Query.html#g:7

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


Re: [Haskell-cafe] generalized, tail-recursive left fold that can finish tne computation prematurely

2013-02-18 Thread Roman Cheplyaka
* o...@okmij.org o...@okmij.org [2013-02-19 06:27:10-]
 
 As others have pointed out, _in principle_, foldr is not at all
 deficient. We can, for example, express foldl via foldr. Moreover, we
 can express head, tail, take, drop and even zipWith through
 foldr. That is, the entire list processing library can be written in
 terms of foldr:
 
 http://okmij.org/ftp/Algorithms.html#zip-folds
 
 That said, to express foldl via foldr, we need a higher-order
 fold. There are various problems with higher-order folds, related to
 the cost of building closures. The problems are especially severe 
 in strict languages or strict contexts. Indeed,
 
 foldl_via_foldr f z l = foldr (\e a z - a (f z e)) id l z
 
 first constructs the closure and then applies it to z. The closure has
 the same structure as the list -- it is isomorphic to the
 list. However, the closure representation of a list takes typically
 quite more space than the list. So, in strict languages, expressing
 foldl via foldr is a really bad idea. It won't work for big lists.

If we unroll foldr once (assuming l is not empty), we'll get

  \z - foldr (\e a z - a (f z e)) id (tail l) (f z (head l))

which is a (shallow) closure. In order to observe what you describe (a
closure isomorphic to the list) we'd need a language which does
reductions inside closures.

Am I wrong?

Roman

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