[Haskell-cafe] ANNOUNCE: tardis

2012-08-07 Thread Dan Burton
I'm pleased to announce that I've uploaded the *tardis* package to hackage.

http://hackage.haskell.org/package/tardis-0.2.0.0

*TardisT* is a monad transformer that combines the (regular, forwards)
State monad
with the backwards State monad, allowing you to communicate on two
channels of state:
one is backwards travelling state, while the other is forwards
travelling state.
Its primitives are comparable to the State monad's get and put, but the
names
disambiguate which channel they operate on:

getPast:: Monad m =   TardisT bw fw m fw
getFuture  :: Monad m =   TardisT bw fw m bw

sendPast   :: Monad m = bw - TardisT bw fw m ()

sendFuture :: Monad m = fw - TardisT bw fw m ()

These primitives allow you to write some very amusing timey-wimey code,
but it only works in the presence of sufficient laziness.
If you run into an infinite loop, try adding laziness annotations
everywhere,
and make sure that what you are trying to do is not a time paradox.

I've provided both *transformers* and *mtl* style modules:
Control.Monad.Trans.Tardis contains the transformer,
while Control.Monad.Tardis.Class contains the MonadTardis class,
and Control.Monad.Tardis re-exports both as well as the TardisT instance
for MonadTardis.

See the readme on github for more details:

https://github.com/DanBurton/tardis#readme

As a side note, since the code base is relatively small, it can also serve
as a simple demonstration of how to use a cabal flag
in conjunction with CPP to selectively include swaths of code
(see Control/Monad/Tardis.hs and tardis.cabal).

I'm not entirely sold on the naming conventions for the package (including
the package name),
and am open to suggestions.

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


Re: [Haskell-cafe] HUnit and table-driven tests

2012-08-07 Thread Dean Herington

At 4:30 PM -0700 8/5/12, Matthew wrote:

On Sun, Aug 5, 2012 at 12:32 AM, Henk-Jan van Tuyl hjgt...@chello.nl wrote:

 On Sun, 05 Aug 2012 03:21:39 +0200, Matthew wonderzom...@gmail.com wrote:


 I've got a function which takes in two chars, describing a playing
 card and a suit. An example would be 4C or TH for a 4 of Clubs or a
 Ten of Hearts. I need to be able to compare the ranks of a card (e.g.
 a King is 13), so a Card is a tuple of rank and suit. The function
 which parses a Card is type String - Maybe Card.

 I'm writing unit tests for this using HUnit, and ideally I'd go with a
 table-driven[1] approach, where each test case is a tuple of the input
 and the expected output. (Possibly I could expand this to a triple, or
 simply a list, to allow for an error message for each test case.) Then
 all the test function has to do is run through each case and assert as
 necessary. Example: [(TH, Just (Hearts, 10)), (XH, Nothing)].



 A simple solution:


 parseCard :: String - Maybe Card
 parseCard string = your function to test
 test :: Bool
 test =  all testEqual [(TH, Just (Hearts, 10)), (XH, Nothing)]
 where
   testEqual (input, output) = parseCard input == output



 For a description of 'all', see:

http://hackage.haskell.org/packages/archive/base/latest/doc/html/Prelude.html#v:all


Thanks for the response. The one problem I have with this is that it
will not be at all obvious which test case (or cases!) failed.

That said, maybe I could do something similar, with a Writer? A passed
test writes , but a failed one writes a test-specific failure
message. Then the test itself uses this string as the assert message.



Let HUnit tell you about the failing test cases.  Here's one way to do it.


import Test.HUnit
import Data.Char (isDigit)

data Suit = Spades | Hearts | Diamonds | Clubs
  deriving (Show, Read, Eq, Ord)
type Rank = Int  -- 2 .. 14 (jack=11, queen=12, king=13, ace=14)
type Card = (Suit, Rank)

parseCard :: String - Maybe Card
parseCard [rankChar, suitChar] = do suit - suitFrom suitChar; rank 
- rankFrom rankChar; return (suit, rank)

parseCard _ = Nothing

suitFrom char = lookup char [('S', Spades), ('H', Hearts), ('D', 
Diamonds), ('C', Clubs)]


rankFrom dig | isDigit dig = let v = read [dig] in if v = 2 then 
Just v else Nothing
rankFrom char = lookup char [('T', 10), ('J', 11), ('Q', 12), ('K', 
13), ('A', 14)]


makeTest :: (String, Maybe Card) - Test
makeTest (string, result) = string ~: result ~=? parseCard string

tests = [(TH, Just (Hearts, 10)), (XH, Nothing)]

main = (runTestTT . TestList . map makeTest) tests


Dean

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


Re: [Haskell-cafe] [Haskell] ANNOUNCE: tardis

2012-08-07 Thread Ben Millwood
On Tue, Aug 7, 2012 at 7:04 AM, Dan Burton danburton.em...@gmail.com wrote:
 As a side note, since the code base is relatively small, it can also serve
 as a simple demonstration of how to use a cabal flag
 in conjunction with CPP to selectively include swaths of code
 (see Control/Monad/Tardis.hs and tardis.cabal).

Eep, your API changes based on compile-time settings. I think this is
a bad idea, because other packages cannot depend on a flag, so
realistically other packages cannot depend on the instances existing,
so they're nearly useless.

UndecidableInstances is excessively maligned and usually fine anyway.
If it compiles, it won't go wrong.

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


Re: [Haskell-cafe] Benchmark of DFT libraries in Haskell

2012-08-07 Thread Erik de Castro Lopo
Takayuki Muranushi wrote:

  * vector-fftw with wisdom was more than 1/2 times faster than fftw in
  C with wisdom (and with communication overhead.)
 
  I would be suspicious of that result. Calling a C function from a library
  should be slower from Haskell than from C.
 
 Sorry for the confusion, What I meant is that vector-fftw version takes
 more time than C version, but less than twice.

That makes much more sense. Whether you're calling fftw from C or from
Haskell, its still the fftw library doing most of the work. As you 
increase the FFT length, the difference between C and Haskell should
decrease.

Cheers,
Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/

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


[Haskell-cafe] Possible bug in Criterion or Statistics package

2012-08-07 Thread Till Berger

Dear all,

I may have stumbled upon a bug in the Criterion package. When running  
the attached Haskell program (Benchmark.hs, a simple test case) on  
multiple cores (with +RTS -N, +RTS -N2, +RTS -N3 etc.) it sooner or  
later crashes with the following exception:


Benchmark: thread blocked indefinitely in an MVar operation

With profiling support enabled and run with the xc flag I get the  
following output before the crash:


*** Exception (reporting due to +RTS -xc): (THUNK_STATIC), stack trace:
  Statistics.Resampling.Bootstrap.bootstrapBCA,
  called from Main.main,
  called from Main.CAF
  -- evaluated by: Main.main,
  called from Main.CAF
*** Exception (reporting due to +RTS -xc): (THUNK_STATIC), stack trace:
  Statistics.Resampling.Bootstrap.bootstrapBCA,
  called from Main.main
*** Exception (reporting due to +RTS -xc): (THUNK_STATIC), stack trace:
  Statistics.Resampling.Bootstrap.bootstrapBCA,
  called from Main.main
*** Exception (reporting due to +RTS -xc): (THUNK_STATIC), stack trace:
  Statistics.Resampling.Bootstrap.bootstrapBCA,
  called from Main.main,
  called from Main.CAF

I have tested this with GHC versions 7.0.4 and 7.4.2 and Criterion 0.6.0.1.

So I am not sure if this is a bug in Criterion itself, the Statistics  
package or any dependency or if I am doing something obviously wrong.  
I would be grateful if someone could look into this as it is holding  
me back from using Criterion for benchmarking my code.


Regards,
Till Berger
import Criterion.Main

test _ = ()

createBgroups num =
if (num = 0) then (bench (show num) $ nf test ()):(createBgroups (num - 1))
else []

main = do
defaultMain (createBgroups 5000)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Possible bug in Criterion or Statistics package

2012-08-07 Thread Johan Tibell
Hi Till,

This would make an excellent bug report at:

  https://github.com/bos/criterion/issues

Cheers,
Johan

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


Re: [Haskell-cafe] Possible bug in Criterion or Statistics package

2012-08-07 Thread Aleksey Khudyakov

On 07.08.2012 18:16, Till Berger wrote:

Dear all,

I may have stumbled upon a bug in the Criterion package. When running
the attached Haskell program (Benchmark.hs, a simple test case) on
multiple cores (with +RTS -N, +RTS -N2, +RTS -N3 etc.) it sooner or
later crashes with the following exception:

Benchmark: thread blocked indefinitely in an MVar operation

With profiling support enabled and run with the xc flag I get the
following output before the crash:

*** Exception (reporting due to +RTS -xc): (THUNK_STATIC), stack trace:
Statistics.Resampling.Bootstrap.bootstrapBCA,
called from Main.main,
called from Main.CAF
-- evaluated by: Main.main,
called from Main.CAF
*** Exception (reporting due to +RTS -xc): (THUNK_STATIC), stack trace:
Statistics.Resampling.Bootstrap.bootstrapBCA,
called from Main.main
*** Exception (reporting due to +RTS -xc): (THUNK_STATIC), stack trace:
Statistics.Resampling.Bootstrap.bootstrapBCA,
called from Main.main
*** Exception (reporting due to +RTS -xc): (THUNK_STATIC), stack trace:
Statistics.Resampling.Bootstrap.bootstrapBCA,
called from Main.main,
called from Main.CAF

I have tested this with GHC versions 7.0.4 and 7.4.2 and Criterion 0.6.0.1.

So I am not sure if this is a bug in Criterion itself, the Statistics
package or any dependency or if I am doing something obviously wrong. I
would be grateful if someone could look into this as it is holding me
back from using Criterion for benchmarking my code.

I would suspect Statistics.Resampling.resample. From quick glance 
criterion doesn't use any concurrent stuff. I'll try create smaller test 
case


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


[Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-07 Thread Daniel Trstenjak

Hi all,

it should be possible a call a function on all elements of the data
structure, to add and remove elements.

What I currently have:

the type class:

class Foo a where
   hasId :: a - Int - Maybe a


a few instances:

data A = A deriving Show
instance Foo A where
   hasId a 1 = Just a
   hasId _ _ = Nothing

data B = B deriving Show
instance Foo B where
   hasId a 2 = Just a
   hasId _ _ = Nothing

data C = C deriving Show
instance Foo C where
   hasId a 3 = Just a
   hasId _ _ = Nothing


the data structure holding any instance of Foo, which itself is a
instance of Foo:

data Foos l r = Foos l r
  | FooL l
  | FooR r
  | NoFoos deriving Show

instance (Foo l, Foo r) = Foo (Foos l r) where
   hasId (Foos l r) id =
  case (hasId l id, hasId r id) of
   (Just l, Just r) - Just $ Foos l r
   (Just l, _ ) - Just $ FooL l
   (_ , Just r) - Just $ FooR r
   _- Nothing


combinator for Foos:

(+++) :: l - r - Foos l r
l +++ r = Foos l r
infixr 5 +++


Now I can write:

*Main A +++ B +++ C +++ A
Foos A (Foos B (Foos C A))
*Main (A +++ B +++ C +++ A) `hasId` 1
Just (Foos A (FooR (FooR A)))


Doesn't seem that nice. For every operation I would have to extend the
type class. After some operations the data structure contains many
dummy nodes (FooR, FooL).

Is there some nicer way?


Greetings,
Daniel

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


Re: [Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-07 Thread Joey Adams
On Tue, Aug 7, 2012 at 2:03 PM, Daniel Trstenjak
daniel.trsten...@gmail.com wrote:
 Data structure containing elements which are instances of the same type class

Are you looking for existential quantification [1]?

data SomeFoo = forall a. Foo a = a

 [1]: 
http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html#existential-quantification

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


Re: [Haskell-cafe] HUnit and table-driven tests

2012-08-07 Thread Matthew
On Tue, Aug 7, 2012 at 12:51 AM, Dean Herington
heringtonla...@mindspring.com wrote:
 At 4:30 PM -0700 8/5/12, Matthew wrote:

 On Sun, Aug 5, 2012 at 12:32 AM, Henk-Jan van Tuyl hjgt...@chello.nl
 wrote:

  On Sun, 05 Aug 2012 03:21:39 +0200, Matthew wonderzom...@gmail.com
 wrote:

  I've got a function which takes in two chars, describing a playing
  card and a suit. An example would be 4C or TH for a 4 of Clubs or a
  Ten of Hearts. I need to be able to compare the ranks of a card (e.g.
  a King is 13), so a Card is a tuple of rank and suit. The function
  which parses a Card is type String - Maybe Card.

  I'm writing unit tests for this using HUnit, and ideally I'd go with a
  table-driven[1] approach, where each test case is a tuple of the input
  and the expected output. (Possibly I could expand this to a triple, or
  simply a list, to allow for an error message for each test case.) Then
  all the test function has to do is run through each case and assert as
  necessary. Example: [(TH, Just (Hearts, 10)), (XH, Nothing)].



  A simple solution:

  parseCard :: String - Maybe Card
  parseCard string = your function to test
  test :: Bool
  test =  all testEqual [(TH, Just (Hearts, 10)), (XH, Nothing)]
  where
testEqual (input, output) = parseCard input == output



  For a description of 'all', see:


 http://hackage.haskell.org/packages/archive/base/latest/doc/html/Prelude.html#v:all


 Thanks for the response. The one problem I have with this is that it
 will not be at all obvious which test case (or cases!) failed.

 That said, maybe I could do something similar, with a Writer? A passed
 test writes , but a failed one writes a test-specific failure
 message. Then the test itself uses this string as the assert message.



 Let HUnit tell you about the failing test cases.  Here's one way to do it.


 import Test.HUnit
 import Data.Char (isDigit)

 data Suit = Spades | Hearts | Diamonds | Clubs
   deriving (Show, Read, Eq, Ord)
 type Rank = Int  -- 2 .. 14 (jack=11, queen=12, king=13, ace=14)
 type Card = (Suit, Rank)


 parseCard :: String - Maybe Card
 parseCard [rankChar, suitChar] = do suit - suitFrom suitChar; rank -
 rankFrom rankChar; return (suit, rank)
 parseCard _ = Nothing

 suitFrom char = lookup char [('S', Spades), ('H', Hearts), ('D', Diamonds),
 ('C', Clubs)]

 rankFrom dig | isDigit dig = let v = read [dig] in if v = 2 then Just v
 else Nothing
 rankFrom char = lookup char [('T', 10), ('J', 11), ('Q', 12), ('K', 13),
 ('A', 14)]

 makeTest :: (String, Maybe Card) - Test
 makeTest (string, result) = string ~: result ~=? parseCard string

 tests = [(TH, Just (Hearts, 10)), (XH, Nothing)]

 main = (runTestTT . TestList . map makeTest) tests

...it seems so obvious now. This is *exactly* what I was looking for;
clearly I was over-thinking this.

Thanks, Dean!



 Dean

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


Re: [Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-07 Thread Daniel Trstenjak

Hi Joey,

On Tue, Aug 07, 2012 at 02:13:09PM -0400, Joey Adams wrote:
 Are you looking for existential quantification [1]?
 
 data SomeFoo = forall a. Foo a = a
 
  [1]: 
 http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html#existential-quantification

Thanks! Yes, that looks really nice. :)

data A = A deriving Show
data B = B deriving Show
data C = C deriving Show

data Foo = forall a. Show a = MkFoo a (Int - Bool)

instance Show Foo where
   show (MkFoo a f) = show a

hasId foos id = filter (\(MkFoo a f) - f id) foos

*Main let foos = [MkFoo A (==1), MkFoo B (==2), MkFoo C (==3)]
*Main hasId foos 1
[A]


Greetings,
Daniel

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


Re: [Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-07 Thread Alexander Solla
On Tue, Aug 7, 2012 at 11:03 AM, Daniel Trstenjak 
daniel.trsten...@gmail.com wrote:


 Hi all,

 it should be possible a call a function on all elements of the data
 structure, to add and remove elements.

 What I currently have:

 the type class:

 class Foo a where
hasId :: a - Int - Maybe a


 a few instances:

 data A = A deriving Show
 instance Foo A where
hasId a 1 = Just a
hasId _ _ = Nothing

 data B = B deriving Show
 instance Foo B where
hasId a 2 = Just a
hasId _ _ = Nothing

 data C = C deriving Show
 instance Foo C where
hasId a 3 = Just a
hasId _ _ = Nothing


 the data structure holding any instance of Foo, which itself is a
 instance of Foo:

 data Foos l r = Foos l r
   | FooL l
   | FooR r
   | NoFoos deriving Show

 instance (Foo l, Foo r) = Foo (Foos l r) where
hasId (Foos l r) id =
   case (hasId l id, hasId r id) of
(Just l, Just r) - Just $ Foos l r
(Just l, _ ) - Just $ FooL l
(_ , Just r) - Just $ FooR r
_- Nothing


 combinator for Foos:

 (+++) :: l - r - Foos l r
 l +++ r = Foos l r
 infixr 5 +++


 Now I can write:

 *Main A +++ B +++ C +++ A
 Foos A (Foos B (Foos C A))
 *Main (A +++ B +++ C +++ A) `hasId` 1
 Just (Foos A (FooR (FooR A)))


 Doesn't seem that nice. For every operation I would have to extend the
 type class. After some operations the data structure contains many
 dummy nodes (FooR, FooL).

 Is there some nicer way?


Read Data types a la carte.  You can use the free package for most of
the plumbing (I think -- it definitely does free monads, which are a
tangentially related idea, but it has a module for dealing with these funny
functors, if I recall correctly.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe