[Haskell-cafe] ANN: rematch, an library for composable assertions with human readable failure messages

2013-04-16 Thread Tom Crayford
I kept on running into this thing where I was calling error in quickcheck to get good error messages about the things I was comparing. In Java land, this stuff is handled by Hamcrest: a library for composable assertions with good error messages. This library is basically a port of hamcrest's core a

Re: [Haskell-cafe] ANN: rematch, an library for composable assertions with human readable failure messages

2013-04-16 Thread Tom Ellis
On Tue, Apr 16, 2013 at 10:17:48AM +0100, Tom Crayford wrote: > I kept on running into this thing where I was calling error in quickcheck > to get good error messages about the things I was comparing. In Java land, > this stuff is handled by Hamcrest: a library for composable assertions with > good

Re: [Haskell-cafe] ANN: rematch, an library for composable assertions with human readable failure messages

2013-04-16 Thread Oliver Charles
On 04/16/2013 11:24 AM, Tom Ellis wrote: On Tue, Apr 16, 2013 at 10:17:48AM +0100, Tom Crayford wrote: I kept on running into this thing where I was calling error in quickcheck to get good error messages about the things I was comparing. In Java land, this stuff is handled by Hamcrest: a library

[Haskell-cafe] data types with overlapping component names (in one module)?

2013-04-16 Thread Johannes Waldmann
What is the current situation: can we have two types with overlapping component names in one module? module M where data T1 = C1 { foo :: Int } data T2 = C2 { foo :: String } It seems not (ghc says: Multiple declarations of 'foo'). This comes close: http://www.haskell.org/ghc/docs/7.6.2/html/use

Re: [Haskell-cafe] data types with overlapping component names (in one module)?

2013-04-16 Thread Artyom Kazak
I'll just leave it here: http://hackage.haskell.org/trac/ghc/wiki/Records ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Monad fold

2013-04-16 Thread Christopher Howard
So, I'm doing something like this foldl (>>=) someA list :: Monad m => m a where list :: Monad m => [a -> m a], someA :: Monad m => m a Is there a more concise way to write this? I don't think foldM is what I want -- or is it? -- frigidcode.com signature.asc Description: OpenPGP digital

Re: [Haskell-cafe] Monad fold

2013-04-16 Thread Lyndon Maydwell
You could do: runKleisli . mconcat . map Kleisli :: Monoid (Kleisli m a b) => [a -> m b] -> a -> m b Would that work for you? On Tue, Apr 16, 2013 at 8:35 PM, Christopher Howard < christopher.how...@frigidcode.com> wrote: > So, I'm doing something like this > > foldl (>>=) someA list :: Monad

Re: [Haskell-cafe] Monad fold

2013-04-16 Thread Oliver Charles
On 04/16/2013 01:47 PM, Lyndon Maydwell wrote: You could do: runKleisli . mconcat . map Kleisli :: Monoid (Kleisli m a b) => [a -> m b] -> a -> m b Would that work for you? I can't find an instance for Monoid (Kleisli m a b) in `base`, so presumably the author would also have to write this i

Re: [Haskell-cafe] Monad fold

2013-04-16 Thread Lyndon Maydwell
Wow looks like this Monoid instance isn't included in Control.Monad... My mistake. On Tue, Apr 16, 2013 at 8:47 PM, Lyndon Maydwell wrote: > You could do: > > runKleisli . mconcat . map Kleisli :: Monoid (Kleisli m a b) => [a -> m b] > -> a -> m b > > Would that work for you? > > > On Tue, Apr

Re: [Haskell-cafe] Monad fold

2013-04-16 Thread Roman Cheplyaka
* Christopher Howard [2013-04-16 04:35:39-0800] > So, I'm doing something like this > > foldl (>>=) someA list :: Monad m => m a > > where > list :: Monad m => [a -> m a], > someA :: Monad m => m a > > Is there a more concise way to write this? I don't think foldM is what I > want -- or is

Re: [Haskell-cafe] Monad fold

2013-04-16 Thread Tom Ellis
On Tue, Apr 16, 2013 at 01:53:19PM +0100, Oliver Charles wrote: > On 04/16/2013 01:47 PM, Lyndon Maydwell wrote: > >You could do: > > > >runKleisli . mconcat . map Kleisli :: Monoid (Kleisli m a b) => [a > >-> m b] -> a -> m b > > > >Would that work for you? > I can't find an instance for Monoid (K

Re: [Haskell-cafe] Monad fold

2013-04-16 Thread Lyndon Maydwell
Yep. I was backstabbed by ghci seemingly having no issue with my definition when I asked for the type. On Tue, Apr 16, 2013 at 9:49 PM, Tom Ellis < tom-lists-haskell-cafe-2...@jaguarpaw.co.uk> wrote: > On Tue, Apr 16, 2013 at 01:53:19PM +0100, Oliver Charles wrote: > > On 04/16/2013 01:47 PM, Ly

Re: [Haskell-cafe] Monad fold

2013-04-16 Thread Roman Cheplyaka
Right. See also this discussion: http://www.haskell.org/pipermail/libraries/2009-July/012106.html Roman * Tom Ellis [2013-04-16 14:49:48+0100] > On Tue, Apr 16, 2013 at 01:53:19PM +0100, Oliver Charles wrote: > > On 04/16/2013 01:47 PM, Lyndon Maydwell wrote: > > >You could do: > > > > > >runKl

Re: [Haskell-cafe] Monad fold

2013-04-16 Thread Arseniy Alekseyev
Hi! Although foldM won't make things much nicer, it can be used here as well: someA >>= \a -> foldM (flip id) a list Cheers! Arseniy On 16 April 2013 13:35, Christopher Howard wrote: > So, I'm doing something like this > > foldl (>>=) someA list :: Monad m => m a > > where > list :: Monad m

Re: [Haskell-cafe] Haskell / Functional Programmers Group in Madrid (Spain)?

2013-04-16 Thread Hector Guilarte
Hello Alejandro, I was just searching the list to see if there are any Haskellers in Barcelona. I've been living in Spain for almost a year and a half and haven't been able to find at least one person who knows about Haskell nor functional programming. I'd like to extend Alejandro's query to Barc

Re: [Haskell-cafe] ANN: rematch, an library for composable assertions with human readable failure messages

2013-04-16 Thread Roman Cheplyaka
Hi Tom, This is a neat idea! I'd like to use something like this in smallcheck and test-framework-golden. The main obstacle to that is that your package depends on QuickCheck and HUnit, and every package using rematch would transitively depend on them, too. This has little sense, especially for s

Re: [Haskell-cafe] ANN: rematch, an library for composable assertions with human readable failure messages

2013-04-16 Thread Tom Crayford
Roman, Thanks for the feedback! I'd originally left the QuickCheck and HUnit implementations in this library for convenience, thinking that there aren't going to be many people who care about the transitive dep. But you care, so I'm happy moving them out of core. I'll release a 0.2 with both the H

Re: [Haskell-cafe] ANN: rematch, an library for composable assertions with human readable failure messages

2013-04-16 Thread Roman Cheplyaka
* Tom Crayford [2013-04-16 15:24:07+0100] > Re the Control namespace, these matchers aren't exclusively a testing tool. > I've been using the core api for other purposes as well (primarily for > validating forms in user interfaces in conjunction with > digestive-functors). I couldn't figure anythi

[Haskell-cafe] Contravariant applicatives, monads and arrows (was ANN: rematch, an library for composable assertions with human readable failure messages)

2013-04-16 Thread Alejandro Serrano Mena
Hi, First of all, let me say that this work on matchers is really useful :) Following Roman advice, I'm trying to find a more principled approach that could be useful for this library. It seems that "Match" could easily be converted to Either and thus made into Functor, Applicative, Alternative an

Re: [Haskell-cafe] When - O'Reilly book on Parallel and Concurrent Haskell

2013-04-16 Thread amslonewolf
Answering my own question - the book can be found at http://ofps.oreilly.com/titles/9781449335946/index.html On Saturday, April 13, 2013 5:39:32 AM UTC-4, amslo...@gmail.com wrote: > > Are there updates on when Simon Marlow's O'Reilly book on Parallel and > Concurrent Haskell is going to be re

Re: [Haskell-cafe] Contravariant applicatives, monads and arrows (was ANN: rematch, an library for composable assertions with human readable failure messages)

2013-04-16 Thread Roman Cheplyaka
My idea was to convert Matcher to be a covariant functor. It would be essentially a Matcher which has been applied to the tested value. And the type argument would denote the result of a computation. For example, consider hasRight :: (Show a, Show b) => Matcher b -> Matcher (Either a b) Inste

Re: [Haskell-cafe] ANN: rematch, an library for composable assertions with human readable failure messages

2013-04-16 Thread Petr Pudlák
Hi tom, I had problems installing version 0.1.2.1 on GHC 7.4.1: Resolving dependencies... > Downloading rematch-0.1.2.1... > Configuring rematch-0.1.2.1... > Building rematch-0.1.2.1... > Preprocessing library rematch-0.1.2.1... > [1 of 4] Compiling Control.Rematch.Formatting ( > Control/Rematch

Re: [Haskell-cafe] ANN: rematch, an library for composable assertions with human readable failure messages

2013-04-16 Thread Ross Paterson
On Tue, Apr 16, 2013 at 10:17:48AM +0100, Tom Crayford wrote: > The core API is very simple: > > data Matcher a = Matcher { > match :: a -> Bool > -- ^ A function that returns True if the matcher should pass, False if it > should fail > , description :: String > -- ^ A description of th

[Haskell-cafe] Unit Testing with Control.Proxy

2013-04-16 Thread Dan
Hi all, I've discovered the excellent proxy library recently and one thing strikes me. How do you unit test a proxy? Are there any specific methods or workflows for doing this cleanly and consistently? Daniel -- ~~ Whatever happens, the sun's still gonna come up tomorrow ~~

Re: [Haskell-cafe] ANN: rematch, an library for composable assertions with human readable failure messages

2013-04-16 Thread Petr Pudlák
2013/4/16 Ross Paterson > On Tue, Apr 16, 2013 at 10:17:48AM +0100, Tom Crayford wrote: > > The core API is very simple: > > > > data Matcher a = Matcher { > > match :: a -> Bool > > -- ^ A function that returns True if the matcher should pass, False if > it > > should fail > > , descrip

[Haskell-cafe] trying to understand out of memory exceptions

2013-04-16 Thread Anatoly Yakovenko
-- So why does this code run out of memory? import Control.DeepSeq import System.IO import qualified Data.ByteString.Char8 as BS scanl' :: NFData a => (a -> b -> a) -> a -> [b] -> [a] scanl' f q ls = q : (case ls of [] -> [] x:xs -> let q' = f q

Re: [Haskell-cafe] trying to understand out of memory exceptions

2013-04-16 Thread Clark Gaebel
See the comment for hGetContents: "This function reads chunks at a time, doubling the chunksize on each read. The final buffer is then realloced to the appropriate size. For files > half of available memory, this may lead to memory exhaustion. Consider using readFile

Re: [Haskell-cafe] trying to understand out of memory exceptions

2013-04-16 Thread Anatoly Yakovenko
unfortunately read file tries to get the file size readFile :: FilePath -> IO ByteStringreadFile f = bracket (openFile f ReadMode) hClose(\h -> hFileSize h >>= hGet h . fromIntegral) which wont work on a special file, like a socket. which is what i am trying to simulate here. On Tue, Apr

Re: [Haskell-cafe] trying to understand out of memory exceptions

2013-04-16 Thread Clark Gaebel
Have you tried the lazy bytestring version? http://hackage.haskell.org/packages/archive/bytestring/0.10.2.0/doc/html/Data-ByteString-Lazy-Char8.html#g:29 - Clark On Tuesday, April 16, 2013, Anatoly Yakovenko wrote: > unfortunately read file tries to get the file size > > readFile :: FilePath

Re: [Haskell-cafe] trying to understand out of memory exceptions

2013-04-16 Thread Anatoly Yakovenko
ah, doh, my mistake. i accidently pulled in Strict version of bytestring. the Lazy works file :). I have a much more complex program that isn't working correctly which i was trying to simplify and looks like i added an error :) On Tue, Apr 16, 2013 at 11:29 AM, Clark Gaebel wrote: > See the

Re: [Haskell-cafe] Contravariant applicatives, monads and arrows (was ANN: rematch, an library for composable assertions with human readable failure messages)

2013-04-16 Thread Stephen Tetley
On 16 April 2013 16:12, Alejandro Serrano Mena wrote: > Hi, > First of all, let me say that this work on matchers is really useful :) > > Following Roman advice, I'm trying to find a more principled approach > that could be useful for this library. It seems that "Match" could > easily be converted

Re: [Haskell-cafe] customizing haskeline?

2013-04-16 Thread Albert Y. C. Lai
On 13-04-14 10:22 PM, Evan Laforge wrote: I tried to colorize a haskeline prompt by putting control characters in it, but line editing was hopelessly confused, presumably because haskeline doesn't understand control characters and thought the prompt was longer than it really was. http://trac.ha

[Haskell-cafe] Derving NFData via Generics from a type that has a vector doesn't work. (was trying to understand out of memory exceptions)

2013-04-16 Thread Anatoly Yakovenko
-- ok, something in deriving NFData using Generics in a type that has a Vector in it. {-# LANGUAGE DeriveGeneric #-} import Control.DeepSeq import System.IO import GHC.Generics (Generic) import qualified Data.Vector as V import qualified Data.ByteString.Lazy.Char8 as BL scanl' :: NFData a => (a

Re: [Haskell-cafe] Derving NFData via Generics from a type that has a vector doesn't work. (was trying to understand out of memory exceptions)

2013-04-16 Thread José Pedro Magalhães
What is the error that you get? Cheers, Pedro On Tue, Apr 16, 2013 at 8:07 PM, Anatoly Yakovenko wrote: > -- ok, something in deriving NFData using Generics in a type that has a > Vector in it. > > > {-# LANGUAGE DeriveGeneric #-} > import Control.DeepSeq > import System.IO > import GHC.Generic

Re: [Haskell-cafe] Derving NFData via Generics from a type that has a vector doesn't work. (was trying to understand out of memory exceptions)

2013-04-16 Thread anatoly yakovenko
This compiles but the process runs out of memory, so it seams that NFData derivation isn't doing its job. On Apr 16, 2013, at 12:15 PM, José Pedro Magalhães wrote: > What is the error that you get? > > > Cheers, > Pedro > > On Tue, Apr 16, 2013 at 8:07 PM, Anatoly Yakovenko > wrote: > --

Re: [Haskell-cafe] data types with overlapping component names (in one module)?

2013-04-16 Thread Sturdy, Ian
I have seen some talk about fixing this, but none anywhere close to reality. As far as what you can use now, there are several libraries implementing alternatives to records; 'vinyl' uses type-level literal strings and is very slick (although all fields with the same name have the same type), wh

[Haskell-cafe] Haskell/functional-language people in Raleigh/Durham, North Carolina, USA?

2013-04-16 Thread Benjamin Redelings
Hi, I'm curious if there are any other people on this list who are interested in Haskell and functional languages in the Triangle Area, in North Carolina? thanks! -BenRI ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell

Re: [Haskell-cafe] Haskell/functional-language people in Raleigh/Durham, North Carolina, USA?

2013-04-16 Thread Taylor Hedberg
Benjamin Redelings, Tue 2013-04-16 @ 16:25:26-0400: > I'm curious if there are any other people on this list who are > interested in Haskell and functional languages in the Triangle Area, > in North Carolina? I am! Funny you should ask, actually, as I was just wondering the same thing myself earl

Re: [Haskell-cafe] Contravariant applicatives, monads and arrows (was ANN: rematch, an library for composable assertions with human readable failure messages)

2013-04-16 Thread Jake McArthur
The type looks similar to the denotation for sets, but implementing a covariant interface for it would not be straightforward and may also be inefficient. On Apr 16, 2013 11:17 AM, "Alejandro Serrano Mena" wrote: > Hi, > First of all, let me say that this work on matchers is really useful :) > >

Re: [Haskell-cafe] I would like to know how to use the following events handlers : dropTargetOnData, dropTargetOnDrop, dropTargetOnEnter,

2013-04-16 Thread Henk-Jan van Tuyl
On Fri, 12 Apr 2013 14:47:23 +0200, luc taesch < wrote: As no one else has responded so far, I think you are in uncharted territory; wxHaskell is huge and there are not many applications using it. good point. ! do we have some kind of census of application that wrok or still work with wxha

Re: [Haskell-cafe] data types with overlapping component names (in one module)?

2013-04-16 Thread Anthony Cowley
On Tue, Apr 16, 2013 at 4:05 PM, Sturdy, Ian wrote: > 'vinyl' uses type-level literal strings and is very slick (although all > fields with the same name have the same type) This is not entirely true, depending on what you mean by "name". The following is just fine. You only have naming issues i

Re: [Haskell-cafe] Haskell/functional-language people in Raleigh/Durham, North Carolina, USA?

2013-04-16 Thread Michael Alan Dorman
Taylor Hedberg writes: > Benjamin Redelings, Tue 2013-04-16 @ 16:25:26-0400: >> I'm curious if there are any other people on this list who are >> interested in Haskell and functional languages in the Triangle Area, >> in North Carolina? > > I am! > > Funny you should ask, actually, as I was just w

[Haskell-cafe] Yampa integral function

2013-04-16 Thread felipe zapata
Hello, I'm trying to write some simulator of physical systems using Yampa. The fundamental idea is to integrate the position and velocity, using the following algorithm: 1. get the velocity using the formula, v = v0 + integral ( 0.5 * force * recip mass) where v0 is the previous velocity. 2. ca

Re: [Haskell-cafe] Yampa integral function

2013-04-16 Thread Jerzy Karczmarczuk
Le 17/04/2013 00:36, felipe zapata a écrit : Hello, I'm trying to write some simulator of physical systems using Yampa. The fundamental idea is to integrate the position and velocity, using the following algorithm: ... ... Nothing to do with Haskell. Where do you get this factor 0.5 in your form

Re: [Haskell-cafe] Yampa integral function

2013-04-16 Thread Jerzy Karczmarczuk
Le 17/04/2013 01:48, Jerzy Karczmarczuk a écrit : With constant acceleration v=v0+a*Dt => 1.01, not 1.05 Gosh, trivial errors seem to be contagious. Of course I meant 1.1, not 1.01. Sorry. JK ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org h

Re: [Haskell-cafe] Derving NFData via Generics from a type that has a vector doesn't work. (was trying to understand out of memory exceptions)

2013-04-16 Thread Anatoly Yakovenko
-- + Roman, -- hey Roman, -- seems like i cant use deepseq or Generic derive of NFData on data types containing vectors. The following code tries to use deepseq to force evaluation of a type containing vectors, but when the code is running it seems to not work as expected (blows up in memory).

Re: [Haskell-cafe] Derving NFData via Generics from a type that has a vector doesn't work. (was trying to understand out of memory exceptions)

2013-04-16 Thread Andres Löh
Hi Anatoly. I don't think that the normal deepseq package currently provides generic deriving at all. This doesn't have anything to do with vector. There's a default implementation for rnf that defines it to be seq, which is not what you want in this case, of course. There are additional packages