[Haskell-cafe] Disjunctive patterns

2011-12-08 Thread Asger Feldthaus
Haskell doesn't seem to support disjunctive patterns, and I'm having a
difficult time writing good Haskell code in situations that would otherwise
call for that type of pattern.

Suppose for an example I have this data type:

data T = Foo Int | Bar Int | Baz

In OCaml I can write something like:

(* foo : T - T - int *)
fun foo x y = match (x,y) with
  | (Foo a | Bar a, Foo b | Bar b) - a + b
  | (Baz, Foo a)
  | (Bar a, Baz) - -a
  | (Baz, Bar a)
  | (Foo a, Baz) - a
  | _ - 0

In Haskell I can't find any equivalent to the disjunctive pattern. If
expanded naively, my Haskell version would look like this:

foo :: T - T - Int
foo x y = case (x,y) of
  (Foo a, Foo b) - a + b
  (Foo a, Bar b) - a + b
  (Bar a, Foo b) - a + b
  (Bar a, Bar b) - a + b
  (Baz, Foo a) - -a
  (Bar a, Baz) - -a
  (Baz, Bar a) - a
  (Foo a, Baz) - a
  _ - 0

While my example is still managable in size, this quickly goes out of hand
in practice. I've tried using pattern guards but with limited success. For
example:

foo2 :: T - T - Int
foo2 x y = case (x,y) of
  (x,y) | Just a - open x,
  Just b - open y -
a+b
  (Baz, Foo a) - -a
  (Bar a, Baz) - -a
  (Baz, Bar a) - a
  (Foo a, Baz) - a
  _ - 0
  where
open (Foo x) = Just x
open (Bar x) = Just x
open Baz = Nothing

I admit it doesn't look that bad in my crafted example, but this approach
doesn't seem to well work for me in practice. In any case, it's still far
more verbose than the disjunctive pattern version.

Nesting the case expressions instead of tuple-matching can reduce some code
duplication, but in general it becomes really verbose, and it is easy to
make mistakes when you have partially overlapped patterns in the
disjunctive-pattern version. Here's the example with nested cases:

foo3 :: T - T - Int
foo3 x y = case x of
  Foo a - case y of
Foo b - a+b
Bar b - a+b
Baz - a
  Bar a - case y of
Foo b - a+b
Bar b - a+b
Baz - -a
  Baz - case y of
Foo b - -b
Bar b - b
Baz - 0

What do people do in this situation - is there a good trick I've
overlooked? And is there some reason why Haskell does not support
disjunctive patterns?

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


Re: [Haskell-cafe] Why doesn't this work? (palindrome :: IO)

2011-12-08 Thread Paul R
Alexej The interesting thing is, that if I change the case ... of
Alexej statement to an if ... then ... else statement, this magically
Alexej starts to work. Since I no longer am enrolled (I have to take
Alexej the course next year), I can't ask a teacher, but my curiosity
Alexej still bugs me. Why doesn't this work? And why does it work with
Alexej a if ... then ...else statement?

maybe you mixed up 'if' and 'case' usages. In fact, 'if' can alway be
translated to 'case' by matching on the boolean condition, like below :

case (s == reverse s) of
  True - s is a palindrome
  False - s is not a palindrome



-- 
  Paul

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


Re: [Haskell-cafe] Disjunctive patterns

2011-12-08 Thread Serguey Zefirov
2011/12/8 Asger Feldthaus asger.feldth...@gmail.com:
 Haskell doesn't seem to support disjunctive patterns, and I'm having a
 difficult time writing good Haskell code in situations that would otherwise
 call for that type of pattern.

 Suppose for an example I have this data type:

 data T = Foo Int | Bar Int | Baz

 In OCaml I can write something like:

 (* foo : T - T - int *)
 fun foo x y = match (x,y) with
   | (Foo a | Bar a, Foo b | Bar b) - a + b

I solve that kind of problem by introducing operation enumerations.

I can write expression definition like that:
data Expr = Plus Int Int | Minus Int Int | Mul Int Int | Neg Int | Inv
Int | Var String

And then I will have exactly your problem.

I prefer to write such definition like that:
data Expr = Bin BinOp Int Int | Un UnOp Int | Var String
data BinOp = Plus | Minus | Mul
data UnOp = Neg | Inv

And I have to write less code in all subsequent constructions and
pattern matches.

This is especially good when I used that method for an expression with
result size:
data Expr size where
Bin :: BinOp xSize ySize resultSize - Expr xSize - Expr ySize -
Expr resultSize

data BinOp a b r where
Plus :: BinOp a a a
Concatenate :: BinOp a b (Plus a b)
Equal :: BinOp a a ONE

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


Re: [Haskell-cafe] Disjunctive patterns

2011-12-08 Thread Emil Axelsson

Instead of pattern guards you can use ViewPatterns:

  http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns

This reduces some of the noise.


{-# LANGUAGE ViewPatterns #-}

data T = Foo Int | Bar Int | Baz

fooBar (Foo a) = Just a
fooBar (Bar a) = Just a
fooBar _   = Nothing

foo :: T - T - Int
foo x y = case (x,y) of
  (fooBar - Just a, fooBar - Just b) - a + b
  (Bar a, Baz) - -a
  (Foo a, Baz) - a
  _ - 0


/ Emil


2011-12-08 11:13, Asger Feldthaus skrev:

Haskell doesn't seem to support disjunctive patterns, and I'm having a
difficult time writing good Haskell code in situations that would
otherwise call for that type of pattern.

Suppose for an example I have this data type:

data T = Foo Int | Bar Int | Baz

In OCaml I can write something like:

(* foo : T - T - int *)
fun foo x y = match (x,y) with
   | (Foo a | Bar a, Foo b | Bar b) - a + b
   | (Baz, Foo a)
   | (Bar a, Baz) - -a
   | (Baz, Bar a)
   | (Foo a, Baz) - a
   | _ - 0

In Haskell I can't find any equivalent to the disjunctive pattern. If
expanded naively, my Haskell version would look like this:

foo :: T - T - Int
foo x y = case (x,y) of
   (Foo a, Foo b) - a + b
   (Foo a, Bar b) - a + b
   (Bar a, Foo b) - a + b
   (Bar a, Bar b) - a + b
   (Baz, Foo a) - -a
   (Bar a, Baz) - -a
   (Baz, Bar a) - a
   (Foo a, Baz) - a
   _ - 0

While my example is still managable in size, this quickly goes out of
hand in practice. I've tried using pattern guards but with limited
success. For example:

foo2 :: T - T - Int
foo2 x y = case (x,y) of
   (x,y) | Just a - open x,
   Just b - open y -
 a+b
   (Baz, Foo a) - -a
   (Bar a, Baz) - -a
   (Baz, Bar a) - a
   (Foo a, Baz) - a
   _ - 0
   where
 open (Foo x) = Just x
 open (Bar x) = Just x
 open Baz = Nothing

I admit it doesn't look that bad in my crafted example, but this
approach doesn't seem to well work for me in practice. In any case, it's
still far more verbose than the disjunctive pattern version.

Nesting the case expressions instead of tuple-matching can reduce some
code duplication, but in general it becomes really verbose, and it is
easy to make mistakes when you have partially overlapped patterns in the
disjunctive-pattern version. Here's the example with nested cases:

foo3 :: T - T - Int
foo3 x y = case x of
   Foo a - case y of
 Foo b - a+b
 Bar b - a+b
 Baz - a
   Bar a - case y of
 Foo b - a+b
 Bar b - a+b
 Baz - -a
   Baz - case y of
 Foo b - -b
 Bar b - b
 Baz - 0

What do people do in this situation - is there a good trick I've
overlooked? And is there some reason why Haskell does not support
disjunctive patterns?

Thanks,
Asger


___
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] Disjunctive patterns

2011-12-08 Thread Øystein Kolsrud
Or perhaps this?

data T = Foo Int | Bar Int | Baz

fooBar (Foo a) = Just a
fooBar (Bar a) = Just a
fooBar _   = Nothing

foo :: T - T - Int
foo x y = sum $ catMaybes $ map fooBar [x,y]

/Øystein

On Thu, Dec 8, 2011 at 1:15 PM, Emil Axelsson e...@chalmers.se wrote:

 Instead of pattern guards you can use ViewPatterns:

  
 http://hackage.haskell.org/**trac/ghc/wiki/ViewPatternshttp://hackage.haskell.org/trac/ghc/wiki/ViewPatterns

 This reduces some of the noise.

 ~~**~~
 {-# LANGUAGE ViewPatterns #-}


 data T = Foo Int | Bar Int | Baz

 fooBar (Foo a) = Just a
 fooBar (Bar a) = Just a
 fooBar _   = Nothing


 foo :: T - T - Int
 foo x y = case (x,y) of
  (fooBar - Just a, fooBar - Just b) - a + b
  (Bar a, Baz) - -a

  (Foo a, Baz) - a
  _ - 0
 ~~**~~

 / Emil


 2011-12-08 11:13, Asger Feldthaus skrev:

 Haskell doesn't seem to support disjunctive patterns, and I'm having a
 difficult time writing good Haskell code in situations that would
 otherwise call for that type of pattern.

 Suppose for an example I have this data type:

 data T = Foo Int | Bar Int | Baz

 In OCaml I can write something like:

 (* foo : T - T - int *)
 fun foo x y = match (x,y) with
   | (Foo a | Bar a, Foo b | Bar b) - a + b
   | (Baz, Foo a)
   | (Bar a, Baz) - -a
   | (Baz, Bar a)
   | (Foo a, Baz) - a
   | _ - 0

 In Haskell I can't find any equivalent to the disjunctive pattern. If
 expanded naively, my Haskell version would look like this:

 foo :: T - T - Int
 foo x y = case (x,y) of
   (Foo a, Foo b) - a + b
   (Foo a, Bar b) - a + b
   (Bar a, Foo b) - a + b
   (Bar a, Bar b) - a + b
   (Baz, Foo a) - -a
   (Bar a, Baz) - -a
   (Baz, Bar a) - a
   (Foo a, Baz) - a
   _ - 0

 While my example is still managable in size, this quickly goes out of
 hand in practice. I've tried using pattern guards but with limited
 success. For example:

 foo2 :: T - T - Int
 foo2 x y = case (x,y) of
   (x,y) | Just a - open x,
   Just b - open y -
 a+b
   (Baz, Foo a) - -a
   (Bar a, Baz) - -a
   (Baz, Bar a) - a
   (Foo a, Baz) - a
   _ - 0
   where
 open (Foo x) = Just x
 open (Bar x) = Just x
 open Baz = Nothing

 I admit it doesn't look that bad in my crafted example, but this
 approach doesn't seem to well work for me in practice. In any case, it's
 still far more verbose than the disjunctive pattern version.

 Nesting the case expressions instead of tuple-matching can reduce some
 code duplication, but in general it becomes really verbose, and it is
 easy to make mistakes when you have partially overlapped patterns in the
 disjunctive-pattern version. Here's the example with nested cases:

 foo3 :: T - T - Int
 foo3 x y = case x of
   Foo a - case y of
 Foo b - a+b
 Bar b - a+b
 Baz - a
   Bar a - case y of
 Foo b - a+b
 Bar b - a+b
 Baz - -a
   Baz - case y of
 Foo b - -b
 Bar b - b
 Baz - 0

 What do people do in this situation - is there a good trick I've
 overlooked? And is there some reason why Haskell does not support
 disjunctive patterns?

 Thanks,
 Asger


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe




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


[Haskell-cafe] Converting string to System.Time.ClockTime

2011-12-08 Thread dokondr
Hi,
What would be the simplest way to convert strings like Wed, 07 Dec 2011
10:09:21 + to System.Time.ClockTime ?

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


Re: [Haskell-cafe] Disjunctive patterns

2011-12-08 Thread David Waern
2011/12/8 Asger Feldthaus asger.feldth...@gmail.com:
 Haskell doesn't seem to support disjunctive patterns, and I'm having a
 difficult time writing good Haskell code in situations that would otherwise
 call for that type of pattern.

I've also missed this after having done a bit of OCaml coding. Perhaps
if a good syntax can be found (since | is already taken) it could be
added as an extension to GHC.

David

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


Re: [Haskell-cafe] Disjunctive patterns

2011-12-08 Thread Holger Siegel

Am 08.12.2011 um 11:13 schrieb Asger Feldthaus:

 Haskell doesn't seem to support disjunctive patterns, and I'm having a 
 difficult time writing good Haskell code in situations that would otherwise 
 call for that type of pattern.
 
 

 In Haskell I can't find any equivalent to the disjunctive pattern. If 
 expanded naively, my Haskell version would look like this:
 
 foo :: T - T - Int
 foo x y = case (x,y) of
   (Foo a, Foo b) - a + b
   (Foo a, Bar b) - a + b
   (Bar a, Foo b) - a + b
   (Bar a, Bar b) - a + b
   (Baz, Foo a) - -a
   (Bar a, Baz) - -a
   (Baz, Bar a) - a
   (Foo a, Baz) - a
   _ - 0
 
 While my example is still managable in size, this quickly goes out of hand in 
 practice. I've tried using pattern guards but with limited success.

value :: T - Int
value (Foo a) = a
value (Bar a) = a
value Baz = 0

foo :: T - T - Int
foo Baz (Foo a) = -a
foo (Bar a) Baz = -a
foo x y = value x + value y


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


Re: [Haskell-cafe] Converting string to System.Time.ClockTime

2011-12-08 Thread Erik Hesselink
I'm not sure if you really need ClockTime (from old-time), but if you
don't, the types from the 'time' package are all parseable with
`parseTime` [1].

Erik

[1] 
http://hackage.haskell.org/packages/archive/time/latest/doc/html/Data-Time-Format.html#v:parseTime

On Thu, Dec 8, 2011 at 14:16, dokondr doko...@gmail.com wrote:
 Hi,
 What would be the simplest way to convert strings like Wed, 07 Dec 2011
 10:09:21 + to System.Time.ClockTime ?

 Thanks!



 ___
 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] Converting string to System.Time.ClockTime

2011-12-08 Thread dokondr
I need to parse time strings like Wed, 07 Dec 2011 10:09:21 + to a
type that:
1) implements Eq, Ord
2) is numerical, so I could subtract one value from another to find the
difference or interval length

To answer 1) requirement I wrote the following snippet. Yet I could not
subtract  UTCTime values. How can I convert them to milliseconds?

import Data.Time.Format
import Data.Time.Clock
import Locale
import Data.Maybe

s1 = Wed, 07 Dec 2011 10:09:21 +
s2 = Wed, 07 Dec 2011 10:11:00 +
t1 = fromJust $ tryParseTime s1
t2 = fromJust $ tryParseTime s2

t = compare t1 t2

tryParseTime :: String - Maybe UTCTime
tryParseTime timeStr = tryFormat (parseTime defaultTimeLocale timeFormat1
timeStr :: Maybe UTCTime)
   where
 tryFormat time
| time == Nothing = parseTime defaultTimeLocale timeFormat2 timeStr
:: Maybe UTCTime
| otherwise = time

 timeFormat1 = %a, %d %b %Y %T %z
 timeFormat2 = %m/%e/%Y %l:%M:%S %p



On Thu, Dec 8, 2011 at 6:12 PM, Erik Hesselink hessel...@gmail.com wrote:

 I'm not sure if you really need ClockTime (from old-time), but if you
 don't, the types from the 'time' package are all parseable with
 `parseTime` [1].

 Erik

[1]
 http://hackage.haskell.org/packages/archive/time/latest/doc/html/Data-Time-Format.html#v:parseTime

 On Thu, Dec 8, 2011 at 14:16, dokondr doko...@gmail.com wrote:
  Hi,
  What would be the simplest way to convert strings like Wed, 07 Dec 2011
  10:09:21 + to System.Time.ClockTime ?
 
  Thanks!
 
 
 
  ___
  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] Converting string to System.Time.ClockTime

2011-12-08 Thread dokondr
Now, when I have managed to convert UTCTime to seconds (see code below) I
got stuck trying to convert from UTCTime to CalendarTime, how to do this?

import Data.Time.Format
import Data.Time.Clock
import Locale
import Data.Maybe
import Data.Time.Clock.POSIX

s1 = Wed, 07 Dec 2011 10:09:21 +
s2 = Wed, 07 Dec 2011 10:11:00 +
t1 = fromJust $ tryParseTime s1
t2 = fromJust $ tryParseTime s2
pt1 = utcTimeToPOSIXSeconds t1  -- :: UTCTime - POSIXTime
pt2 = utcTimeToPOSIXSeconds t2
pt3 = pt1 + (pt2 - pt1) / 2
t3 = posixSecondsToUTCTime pt3

t = compare t1 t2

tryParseTime :: String - Maybe UTCTime
tryParseTime timeStr = tryFormat (parseTime defaultTimeLocale timeFormat1
timeStr :: Maybe UTCTime)
   where
 tryFormat time
| time == Nothing = parseTime defaultTimeLocale timeFormat2 timeStr
:: Maybe UTCTime
| otherwise = time

 timeFormat1 = %a, %d %b %Y %T %z
 timeFormat2 = %m/%e/%Y %l:%M:%S %p
-- timeFormat1 = %m/%d/%Y %l:%M:%S %p


On Thu, Dec 8, 2011 at 6:30 PM, dokondr doko...@gmail.com wrote:

 I need to parse time strings like Wed, 07 Dec 2011 10:09:21 + to a
 type that:
 1) implements Eq, Ord
 2) is numerical, so I could subtract one value from another to find the
 difference or interval length

 To answer 1) requirement I wrote the following snippet. Yet I could not
 subtract  UTCTime values. How can I convert them to milliseconds?

 import Data.Time.Format
 import Data.Time.Clock
 import Locale
 import Data.Maybe

 s1 = Wed, 07 Dec 2011 10:09:21 +
 s2 = Wed, 07 Dec 2011 10:11:00 +
 t1 = fromJust $ tryParseTime s1
 t2 = fromJust $ tryParseTime s2

 t = compare t1 t2

 tryParseTime :: String - Maybe UTCTime
 tryParseTime timeStr = tryFormat (parseTime defaultTimeLocale timeFormat1
 timeStr :: Maybe UTCTime)
where
  tryFormat time
 | time == Nothing = parseTime defaultTimeLocale timeFormat2
 timeStr :: Maybe UTCTime
 | otherwise = time

  timeFormat1 = %a, %d %b %Y %T %z
  timeFormat2 = %m/%e/%Y %l:%M:%S %p




 On Thu, Dec 8, 2011 at 6:12 PM, Erik Hesselink hessel...@gmail.comwrote:

 I'm not sure if you really need ClockTime (from old-time), but if you
 don't, the types from the 'time' package are all parseable with
 `parseTime` [1].

 Erik

 [1]
 http://hackage.haskell.org/packages/archive/time/latest/doc/html/Data-Time-Format.html#v:parseTime

 On Thu, Dec 8, 2011 at 14:16, dokondr doko...@gmail.com wrote:
  Hi,
  What would be the simplest way to convert strings like Wed, 07 Dec 2011
  10:09:21 + to System.Time.ClockTime ?
 
  Thanks!
 
 
 
  ___
  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] Converting string to System.Time.ClockTime

2011-12-08 Thread Antoine Latter
On Thu, Dec 8, 2011 at 9:01 AM, dokondr doko...@gmail.com wrote:
 Now, when I have managed to convert UTCTime to seconds (see code below) I
 got stuck trying to convert from UTCTime to CalendarTime, how to do this?



It might be easier to use 'diffUTCTime' and 'addUTCTime' instead of
converting to and from POSIX seconds.

What do you need the 'CalendarTime' for? I recommend not mixing the
'time' and 'old-time' packages if you can avoid it.

If you really need to for inter-operating with some other library, it
looks like you can use the 'datetime' package to convert from a
UTCTime to a ClockTime, and then you can use the 'old-time' package to
convert from a 'ClockTime' to a 'CalendarTime'.

Antoine

 import Data.Time.Format
 import Data.Time.Clock
 import Locale
 import Data.Maybe
 import Data.Time.Clock.POSIX


 s1 = Wed, 07 Dec 2011 10:09:21 +
 s2 = Wed, 07 Dec 2011 10:11:00 +
 t1 = fromJust $ tryParseTime s1
 t2 = fromJust $ tryParseTime s2
 pt1 = utcTimeToPOSIXSeconds t1  -- :: UTCTime - POSIXTime
 pt2 = utcTimeToPOSIXSeconds t2
 pt3 = pt1 + (pt2 - pt1) / 2
 t3 = posixSecondsToUTCTime pt3


 t = compare t1 t2

 tryParseTime :: String - Maybe UTCTime
 tryParseTime timeStr = tryFormat (parseTime defaultTimeLocale timeFormat1
 timeStr :: Maybe UTCTime)
    where
  tryFormat time
     | time == Nothing = parseTime defaultTimeLocale timeFormat2 timeStr
 :: Maybe UTCTime
     | otherwise = time

  timeFormat1 = %a, %d %b %Y %T %z
  timeFormat2 = %m/%e/%Y %l:%M:%S %p
 -- timeFormat1 = %m/%d/%Y %l:%M:%S %p



 On Thu, Dec 8, 2011 at 6:30 PM, dokondr doko...@gmail.com wrote:

 I need to parse time strings like Wed, 07 Dec 2011 10:09:21 + to a
 type that:
 1) implements Eq, Ord
 2) is numerical, so I could subtract one value from another to find the
 difference or interval length

 To answer 1) requirement I wrote the following snippet. Yet I could not
 subtract  UTCTime values. How can I convert them to milliseconds?

 import Data.Time.Format
 import Data.Time.Clock
 import Locale
 import Data.Maybe

 s1 = Wed, 07 Dec 2011 10:09:21 +
 s2 = Wed, 07 Dec 2011 10:11:00 +
 t1 = fromJust $ tryParseTime s1
 t2 = fromJust $ tryParseTime s2

 t = compare t1 t2

 tryParseTime :: String - Maybe UTCTime
 tryParseTime timeStr = tryFormat (parseTime defaultTimeLocale timeFormat1
 timeStr :: Maybe UTCTime)
    where
  tryFormat time
     | time == Nothing = parseTime defaultTimeLocale timeFormat2
 timeStr :: Maybe UTCTime
     | otherwise = time

  timeFormat1 = %a, %d %b %Y %T %z
  timeFormat2 = %m/%e/%Y %l:%M:%S %p




 On Thu, Dec 8, 2011 at 6:12 PM, Erik Hesselink hessel...@gmail.com
 wrote:

 I'm not sure if you really need ClockTime (from old-time), but if you
 don't, the types from the 'time' package are all parseable with
 `parseTime` [1].

 Erik

 [1]
 http://hackage.haskell.org/packages/archive/time/latest/doc/html/Data-Time-Format.html#v:parseTime

 On Thu, Dec 8, 2011 at 14:16, dokondr doko...@gmail.com wrote:
  Hi,
  What would be the simplest way to convert strings like Wed, 07 Dec
  2011
  10:09:21 + to System.Time.ClockTime ?
 
  Thanks!
 
 
 
  ___
  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] Converting string to System.Time.ClockTime

2011-12-08 Thread Antoine Latter
On Thu, Dec 8, 2011 at 9:13 AM, Antoine Latter aslat...@gmail.com wrote:
 On Thu, Dec 8, 2011 at 9:01 AM, dokondr doko...@gmail.com wrote:
 Now, when I have managed to convert UTCTime to seconds (see code below) I
 got stuck trying to convert from UTCTime to CalendarTime, how to do this?



 It might be easier to use 'diffUTCTime' and 'addUTCTime' instead of
 converting to and from POSIX seconds.


For those reading along at home, 'addUTCTime' and 'diffUTCTime' are
implemented in terms of 'posixSecondsToUTCTime' and
'utcTimeToPOSIXSeconds'. So it's pretty similar in the end.

Antoine

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


Re: [Haskell-cafe] Converting string to System.Time.ClockTime

2011-12-08 Thread dokondr
Ok, maybe you could advise what packages to use for this simple scenario:

I have two text strings with dates:
s1 = Wed, 07 Dec 2011 10:09:21 +
s2 = Wed, 07 Dec 2011 10:11:00 +

I need:
1) Find how many seconds are between  these dates
2) Calculate the date in the middle between these dates
3) Print out all three dates in the different format, like these:
 2011,  7 Dec, Wed, 10:11:00

What functions should I use to implement this?

On Thu, Dec 8, 2011 at 7:13 PM, Antoine Latter aslat...@gmail.com wrote:

 On Thu, Dec 8, 2011 at 9:01 AM, dokondr doko...@gmail.com wrote:
  Now, when I have managed to convert UTCTime to seconds (see code below) I
  got stuck trying to convert from UTCTime to CalendarTime, how to do this?
 
 

 It might be easier to use 'diffUTCTime' and 'addUTCTime' instead of
 converting to and from POSIX seconds.

 What do you need the 'CalendarTime' for? I recommend not mixing the
 'time' and 'old-time' packages if you can avoid it.

 If you really need to for inter-operating with some other library, it
 looks like you can use the 'datetime' package to convert from a
 UTCTime to a ClockTime, and then you can use the 'old-time' package to
 convert from a 'ClockTime' to a 'CalendarTime'.

 Antoine

  import Data.Time.Format
  import Data.Time.Clock
  import Locale
  import Data.Maybe
  import Data.Time.Clock.POSIX
 
 
  s1 = Wed, 07 Dec 2011 10:09:21 +
  s2 = Wed, 07 Dec 2011 10:11:00 +
  t1 = fromJust $ tryParseTime s1
  t2 = fromJust $ tryParseTime s2
  pt1 = utcTimeToPOSIXSeconds t1  -- :: UTCTime - POSIXTime
  pt2 = utcTimeToPOSIXSeconds t2
  pt3 = pt1 + (pt2 - pt1) / 2
  t3 = posixSecondsToUTCTime pt3
 
 
  t = compare t1 t2
 
  tryParseTime :: String - Maybe UTCTime
  tryParseTime timeStr = tryFormat (parseTime defaultTimeLocale timeFormat1
  timeStr :: Maybe UTCTime)
 where
   tryFormat time
  | time == Nothing = parseTime defaultTimeLocale timeFormat2
 timeStr
  :: Maybe UTCTime
  | otherwise = time
 
   timeFormat1 = %a, %d %b %Y %T %z
   timeFormat2 = %m/%e/%Y %l:%M:%S %p
  -- timeFormat1 = %m/%d/%Y %l:%M:%S %p
 
 
 
  On Thu, Dec 8, 2011 at 6:30 PM, dokondr doko...@gmail.com wrote:
 
  I need to parse time strings like Wed, 07 Dec 2011 10:09:21 + to a
  type that:
  1) implements Eq, Ord
  2) is numerical, so I could subtract one value from another to find the
  difference or interval length
 
  To answer 1) requirement I wrote the following snippet. Yet I could not
  subtract  UTCTime values. How can I convert them to milliseconds?
 
  import Data.Time.Format
  import Data.Time.Clock
  import Locale
  import Data.Maybe
 
  s1 = Wed, 07 Dec 2011 10:09:21 +
  s2 = Wed, 07 Dec 2011 10:11:00 +
  t1 = fromJust $ tryParseTime s1
  t2 = fromJust $ tryParseTime s2
 
  t = compare t1 t2
 
  tryParseTime :: String - Maybe UTCTime
  tryParseTime timeStr = tryFormat (parseTime defaultTimeLocale
 timeFormat1
  timeStr :: Maybe UTCTime)
 where
   tryFormat time
  | time == Nothing = parseTime defaultTimeLocale timeFormat2
  timeStr :: Maybe UTCTime
  | otherwise = time
 
   timeFormat1 = %a, %d %b %Y %T %z
   timeFormat2 = %m/%e/%Y %l:%M:%S %p
 
 
 
 
  On Thu, Dec 8, 2011 at 6:12 PM, Erik Hesselink hessel...@gmail.com
  wrote:
 
  I'm not sure if you really need ClockTime (from old-time), but if you
  don't, the types from the 'time' package are all parseable with
  `parseTime` [1].
 
  Erik
 
  [1]
 
 http://hackage.haskell.org/packages/archive/time/latest/doc/html/Data-Time-Format.html#v:parseTime
 
  On Thu, Dec 8, 2011 at 14:16, dokondr doko...@gmail.com wrote:
   Hi,
   What would be the simplest way to convert strings like Wed, 07 Dec
   2011
   10:09:21 + to System.Time.ClockTime ?
  
   Thanks!
  
  
  

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


Re: [Haskell-cafe] Converting string to System.Time.ClockTime

2011-12-08 Thread Antoine Latter
On Thu, Dec 8, 2011 at 9:30 AM, dokondr doko...@gmail.com wrote:
 Ok, maybe you could advise what packages to use for this simple scenario:

 I have two text strings with dates:

 s1 = Wed, 07 Dec 2011 10:09:21 +
 s2 = Wed, 07 Dec 2011 10:11:00 +

 I need:
 1) Find how many seconds are between  these dates
 2) Calculate the date in the middle between these dates

It looks like you already have 1) and 2) finished, using the 'time' package.

 3) Print out all three dates in the different format, like these:
  2011,  7 Dec, Wed, 10:11:00

If you need to convert into a specific time-zone you can use the
'utcToLocalTime' function in the 'time' package, which takes a UTCTime
and a TimeZone to create a 'LocalTime'. I'm just guessing that you
might want this, as your output format doesn't include time-zone
information.

Then for formatting, the 'Data.Time.Format' module in the 'time'
package has the function 'formatTime', which uses the same sort of
format string used by 'parseTime'.

I hope that helps! It took me a while to find my way around the 'time'
package properly.

Antoine

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


Re: [Haskell-cafe] Converting string to System.Time.ClockTime

2011-12-08 Thread dokondr
On Thu, Dec 8, 2011 at 7:39 PM, Antoine Latter aslat...@gmail.com wrote:

 On Thu, Dec 8, 2011 at 9:30 AM, dokondr doko...@gmail.com wrote:
  Ok, maybe you could advise what packages to use for this simple scenario:
 
  I have two text strings with dates:
 
  s1 = Wed, 07 Dec 2011 10:09:21 +
  s2 = Wed, 07 Dec 2011 10:11:00 +
 
  I need:
  1) Find how many seconds are between  these dates
  2) Calculate the date in the middle between these dates

 It looks like you already have 1) and 2) finished, using the 'time'
 package.

  3) Print out all three dates in the different format, like these:
   2011,  7 Dec, Wed, 10:11:00

 If you need to convert into a specific time-zone you can use the
 'utcToLocalTime' function in the 'time' package, which takes a UTCTime
 and a TimeZone to create a 'LocalTime'. I'm just guessing that you
 might want this, as your output format doesn't include time-zone
 information.

 Then for formatting, the 'Data.Time.Format' module in the 'time'
 package has the function 'formatTime', which uses the same sort of
 format string used by 'parseTime'.

 I hope that helps! It took me a while to find my way around the 'time'
 package properly.

 Antoine



Thanks so much for your help! I think I finally :) solved this problem:

import Data.Time.Format
import Data.Time.Clock
import Locale
import Data.Maybe
import Data.Time.Clock.POSIX

timeFormat1 = %a, %d %b %Y %T %z
timeFormat2 = %m/%e/%Y %l:%M:%S %p

s1 = Wed, 07 Dec 2011 10:09:21 +
s2 = Wed, 07 Dec 2011 10:11:00 +
t1 = fromJust $ tryParseTime s1 -- :: UTCTime
t2 = fromJust $ tryParseTime s2
pt1 = utcTimeToPOSIXSeconds t1  -- :: POSIXTime
pt2 = utcTimeToPOSIXSeconds t2
pt3 = pt1 + (pt2 - pt1) / 2
t3 = posixSecondsToUTCTime pt3  -- :: UTCTime

-- formatTime :: FormatTime t = TimeLocale - String - t - String
s3 = formatTime defaultTimeLocale timeFormat2 t3

test = (compare t1 t2) == (compare pt1 pt2)

tryParseTime :: String - Maybe UTCTime
tryParseTime timeStr = tryFormat (parseTime defaultTimeLocale timeFormat1
timeStr :: Maybe UTCTime)
   where
 tryFormat time
| time == Nothing = parseTime defaultTimeLocale timeFormat2 timeStr
:: Maybe UTCTime
| otherwise = time
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Recommended class instances for container type

2011-12-08 Thread Christoph Breitkopf
Hello,

I'm in the process of implementing a container data type, and wonder what
class instances are generally considered necessary. E.g. is it ok to start
out with a Show that's adequate for debugging, or is it a 'must' to include
instances of everything possible (Eq, Ord if possible, Read, Show, Functor,
...).

And what about the more experimental things? Say, DeepSeq, Typeable, Data?
I'd like to keep this simple at start, and I've admittedly not followed
recent developments in Haskell-land (recent meaning the last 10 years or
so. I _do_ know about hierachical modules ;-) ).

OTOH, if not having such instances makes it impossible to do things the
modern way, I'd probably take the time to implement (and maybe understand)
them.

Thanks,

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


Re: [Haskell-cafe] Recommended class instances for container type

2011-12-08 Thread Edward Z. Yang
I'd hazard that if you went 'containers' and looked at what instances were
implemented, that would give you a good idea. :^)  (For example,
if you look at Data.MAp, it has NFData, Typeable2 and Data instances.)

Edward

Excerpts from Christoph Breitkopf's message of Thu Dec 08 11:12:06 -0500 2011:
 Hello,
 
 I'm in the process of implementing a container data type, and wonder what
 class instances are generally considered necessary. E.g. is it ok to start
 out with a Show that's adequate for debugging, or is it a 'must' to include
 instances of everything possible (Eq, Ord if possible, Read, Show, Functor,
 ...).
 
 And what about the more experimental things? Say, DeepSeq, Typeable, Data?
 I'd like to keep this simple at start, and I've admittedly not followed
 recent developments in Haskell-land (recent meaning the last 10 years or
 so. I _do_ know about hierachical modules ;-) ).
 
 OTOH, if not having such instances makes it impossible to do things the
 modern way, I'd probably take the time to implement (and maybe understand)
 them.
 
 Thanks,
 
 Chris

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


Re: [Haskell-cafe] Recommended class instances for container type

2011-12-08 Thread Christoph Breitkopf
That's what I did, and the reason for my question. 'Cause I was scared off
by looking at Data.Map (CPP, lots of language extensions).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Recommended class instances for container type

2011-12-08 Thread Bryan O'Sullivan
On Thu, Dec 8, 2011 at 8:12 AM, Christoph Breitkopf 
chbreitk...@googlemail.com wrote:


 I'm in the process of implementing a container data type, and wonder what
 class instances are generally considered necessary. E.g. is it ok to start
 out with a Show that's adequate for debugging, or is it a 'must' to include
 instances of everything possible (Eq, Ord if possible, Read, Show, Functor,
 ...).


If you're only beginning or partway through the implementation, my advice
would be to simply not worry about instances at all just yet, until you've
got things in reasonable shape. When the time comes, implement the
instances you think appropriate in order of importance, relevance, and
difficulty.

Of course if you're new to the community, it won't be too obvious what's
important or relevant (difficulty should be obvious enough). Basically, aim
at the standard classes first, based on how often you'd expect to use them
yourself.

And what about the more experimental things? Say, DeepSeq, Typeable, Data?


None of those are experimental. They're all frequently used in production
code. DeepSeq is far more important than the other two, though. For
Typeable and Data, you could copy the approach taken by Data.Map and be
fine.

At some point, if you want your container class to be useful to others,
you'll want to implement Foldable and Traversable.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Recommended class instances for container type

2011-12-08 Thread Christoph Breitkopf
Hello Bryan,

On Thu, Dec 8, 2011 at 6:03 PM, Bryan O'Sullivan b...@serpentine.com wrote:

 And what about the more experimental things? Say, DeepSeq, Typeable, Data?

 None of those are experimental. They're all frequently used in production
 code. DeepSeq is far more important than the other two, though. For
 Typeable and Data, you could copy the approach taken by Data.Map and be
 fine.


Well, including a some file via CPP did look experimental enough to me. I'd
like to stay away from GHC-only code, if possible.


 At some point, if you want your container class to be useful to others,
 you'll want to implement Foldable and Traversable.


Being useful to others would be the whole point in releasing it at all :-)

Thanks for your explanations - I take this as: Yes, the Haskell community
is really using all this stuff in production code, so better offer it, or
your library might not be that usable.
I'll try to be complete, then.

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


Re: [Haskell-cafe] Recommended class instances for container type

2011-12-08 Thread Daniel Fischer
On Thursday 08 December 2011, 18:13:50, Christoph Breitkopf wrote: 
 Well, including a some file via CPP did look experimental enough to me.
 I'd like to stay away from GHC-only code, if possible.

CPP is standard (maybe not in the sense that it's included in the language 
standard, but every implementation I'm aware of supports CPP).

 
  At some point, if you want your container class to be useful to
  others, you'll want to implement Foldable and Traversable.
 
 Being useful to others would be the whole point in releasing it at all
 :-)
 
 Thanks for your explanations - I take this as: Yes, the Haskell
 community is really using all this stuff in production code, so better
 offer it, or your library might not be that usable.

To varying extent. Stuff can be quite usable without Data or Typeable 
instances. You can start with what you consider most important and add the 
rest when you get feature requests.

 I'll try to be complete, then.
 
 - Chris


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


Re: [Haskell-cafe] More liberal than liberal type synonyms

2011-12-08 Thread Brent Yorgey
On Wed, Dec 07, 2011 at 04:47:47PM +0100, Gábor Lehel wrote:
 On Wed, Dec 7, 2011 at 1:07 PM, Dmitry Kulagin dmitry.kula...@gmail.com 
 wrote:
  For short, type synonyms work for mere aliases, but not for full-fledged 
  type-level non-inductive functions. And sometimes we intuitively want to 
  use them as such.
  Thank you, Yves! It is now more clear for me.
 
  Still, it seems that ability to use partially applied type synonyms would be
  very natural (and useful) extension to the language. It would allow to avoid
  boilerplate code associated with creating really new types instead of just
  using synonims for existing ones.
 
 The problem as I understand it is that partially-applied type synonyms
 are in effect type level lambdas, and type checking in the presence of
 type level lambdas requires higher-order unification, which is
 undecidable in general. Restricted cases might be possible, I'm not an
 expert in the field. GHC hackers could probably elaborate.
 
 [1] 
 http://stackoverflow.com/questions/8248217/are-there-type-level-combinators-will-they-exist-in-some-future
 [2]
 http://en.wikipedia.org/wiki/Unification_(computer_science)#Higher-order_unification

It's actually type *inference* that requires higher-order unification
in the presence of type-level lambdas, not type checking.  This might
not be a huge deal: we just have to clearly state that enabling
-XPartialTypeFunApps means that you may have to provide some explicit
type annotations in places where type inference cannot figure things
out.  We already have extensions like this (e.g. RankNTypes).

The bigger problem for the moment is that for various technical
reasons, enabling partial applications of type functions can lead to
unsoundness (i.e. typechecked programs which nonetheless crash at
runtime) in the way that type equality is handled.  For more details
see 

  
http://stackoverflow.com/questions/7866375/why-does-ghc-think-that-this-type-variable-is-not-injective/7950614#7950614

I agree that the ability to use partially applied type
synonyms/functions would be natural and useful.  I hope we will
eventually see a version of GHC which supports it but there are some
nontrivial technical issues to be worked out first.

-Brent

 
 
  On Wed, Dec 7, 2011 at 3:51 PM, Yves Parès limestr...@gmail.com wrote:
  Ah, maybe Dan could tell us if it works only with GHC 7.
 
  Dmitry, I had your problem many times. The last time was when I saw you
  could define the ContT monad in terms of Cont (the opposite is done in the
  mtl).
  It leads to a simpler code, but you are stucked when trying to define ContT
  as an instance of MonadTrans:
 
  data Cont r a = ...
  -- [instances of Monad Cont, blah blah blah]
 
  type ContT r m a = Cont r (m a)
 
  instance MonadTrans (ContT r) where  -- This doesn't compile, even if it is
  logical
    lift = ...
 
  For short, type synonyms work for mere aliases, but not for full-fledged
  type-level non-inductive functions.
  And sometimes we intuitively want to use them as such.
 
 
  2011/12/7 Dmitry Kulagin dmitry.kula...@gmail.com
 
   Dmitry, does your code work with LiberalTypeSynonyms extention
   activated?
  No, the same error:
  Type synonym `StateA' should have 1 argument, but has been given 0
 
  But I have GHC 6.12.3
 
  Dmitry
  2011/12/7 Yves Parès limestr...@gmail.com:
   This is impossible:
   in the definition of 'StateT s m a', m must be a monad and then have the
   *
   - * kind.
   So you cannot pass (StateA a), because it has simply the * kind.
  
   Dmitry, does your code work with LiberalTypeSynonyms extention
   activated?
  
  
   2011/12/7 Øystein Kolsrud kols...@gmail.com
  
   You should be able to write something like this:
  
   type StateB a b = StateT SomeOtherState (StateA a) b
  
   Best regards, Øystein Kolsrud
  
  
   On Wed, Dec 7, 2011 at 11:48 AM, Dmitry Kulagin
   dmitry.kula...@gmail.com
   wrote:
  
   Hi Dan,
  
   I am still pretty new in Haskell, but this problem annoys me already.
  
   If I define certain monad as a type synonym:
  
      type StateA a = StateT SomeState SomeMonad a
  
   Then I can't declare new monad based on the synonym:
  
      type StateB a = StateT SomeOtherState StateA a
  
   The only way I know to overcome is to declare StateA without `a':
  
      type StateA = StateT SomeState SomeMonad
  
   But it is not always possible with existing code base.
  
   I am sorry, if this is offtopic, but it seemed to me that the problem
   is realted to partially applied type synomyms you described.
  
   Thanks!
   Dmitry
  
   On Tue, Dec 6, 2011 at 10:59 PM, Dan Doel dan.d...@gmail.com wrote:
Greetings,
   
In the process of working on a Haskell-alike language recently, Ed
Kmett and I realized that we had (without really thinking about it)
implemented type synonyms that are a bit more liberal than GHC's.
With
LiberalTypeSynonyms enabled, GHC allows:
   
   type Foo a b = b - a
   type Bar f = f String Int
   
   

Re: [Haskell-cafe] Recommended class instances for container type

2011-12-08 Thread Johan Tibell
On Thu, Dec 8, 2011 at 8:12 AM, Christoph Breitkopf 
chbreitk...@googlemail.com wrote:

 Hello,

 I'm in the process of implementing a container data type, and wonder what
 class instances are generally considered necessary. E.g. is it ok to start
 out with a Show that's adequate for debugging, or is it a 'must' to include
 instances of everything possible (Eq, Ord if possible, Read, Show, Functor,
 ...).


Start out with Show and spend your time making sure that you're container
type performs well (unless you're doing this as an exercise of course). A
featureful API for something that's as slow as linked lists isn't very
useful. ;)

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


Re: [Haskell-cafe] Why doesn't this work? (palindrome :: IO)

2011-12-08 Thread Tom Murphy
On Wed, Dec 7, 2011 at 11:46 PM, Brandon Allbery allber...@gmail.comwrote:

 On Wed, Dec 7, 2011 at 23:24, Alexej Segeda aloscha_den_st...@hotmail.com
  wrote:

 case s of
(s == reverse s)- putStrLn (s ++  is a
 palindrome)
otherwise   - putStrLn (s ++  is not a
 palindrome)


 case does pattern matching, not Boolean expressions.  (s == reverse s) is
 not a useful pattern, and in fact is probably a syntax error because ==is not 
 a valid infix constructor.

 If you want to do Boolean comparisons in a case, you need to use
 something like

  case () of
() | s == reverse s - putStrLn palindrome
_   - putStrLn nope




This is kind of a hack of case, though. I think what the OP was looking for
is

palindrome :: IO ()
palindrome = do putStrLn Type in a word
s - getLine
isPalindrome s

isPalindrome word
  | (word == reverse word) = putStrLn (word ++  is a palindrome)
  | otherwise  = putStrLn (word ++  is not a palindrome)


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


[Haskell-cafe] Does anyone maintain trac.haskell.org?

2011-12-08 Thread Justin Bailey
The community Trac hosting server isn't sending email, which Trac requires.

I've submitted several tickets to supp...@community.haskell.org but
gotten no response.

Does anyone maintain that server anymore?

Justin

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


Re: [Haskell-cafe] Does anyone maintain trac.haskell.org?

2011-12-08 Thread Alistair Bayley
On 9 December 2011 10:39, Justin Bailey jgbai...@gmail.com wrote:
 The community Trac hosting server isn't sending email, which Trac requires.

 I've submitted several tickets to supp...@community.haskell.org but
 gotten no response.

 Does anyone maintain that server anymore?

Had the same problem in July. Raised a ticket etc. I don't think there
is anyone actually responsible for the trac server.

Alistair

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


Re: [Haskell-cafe] Why doesn't this work? (palindrome :: IO)

2011-12-08 Thread Brandon Allbery
On Thu, Dec 8, 2011 at 15:52, Tom Murphy amin...@gmail.com wrote:

 On Wed, Dec 7, 2011 at 11:46 PM, Brandon Allbery allber...@gmail.comwrote:

  case () of
() | s == reverse s - putStrLn palindrome
_   - putStrLn nope



 This is kind of a hack of case, though. I think what the OP was looking
 for is

 isPalindrome word

   | (word == reverse word) = putStrLn (word ++  is a palindrome)
   | otherwise  = putStrLn (word ++  is not a palindrome)


Erm?  It's as much of a hack of case as yours is, since the above is
actually using case.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] [ANNOUNCE] cereal-0.3.5.0

2011-12-08 Thread Trevor Elliott

Hi Everyone,

I'm pleased to announce the release of cereal version 0.3.5.0!  New to 
this release is support for default, generic implementations of the get 
and put methods of the Serialize class, when support is available.  This 
functionality comes to you courtesy of Bas van Dijk.


Happy Hacking!

--trevor



smime.p7s
Description: S/MIME Cryptographic Signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] CfP: Only one week left for submitting abstracts to TAP 2012 (International Conference on Test and Proofs

2011-12-08 Thread Achim D. Brucker
(Apologies for duplicates) 

 *
   Less than one week until the deadline  ***
    for submitting abstract to TAP 2012*** 
 *
 

CALL FOR PAPERS
Full and short Research Paper, Industrial Expierence Papers, Tool Papers 
Abstract submission: Dec 14, 2011, Paper submission Dec 21, 2012 


  6th INTERNATIONAL CONFERENCE ON TEST AND PROOFS (TAP 2012)
  http://lifc.univ-fcomte.fr/tap2012/
  May 31 - June 1, 2012, Prague, Czech Republic

   Part of the TOOLS Federated Conferences 2012
http://tools2012.fit.cvut.cz/

The TAP conference is devoted to the convergence of proofs and tests,
to the application of techniques from both sides and their combination
for the advancement of software quality. Test and Proof seem to be
contradictory techniques: if you have proved your program to be
correct, it is fruitless to comb it for bugs; and if you are testing
it, that is surely a sign that you have given up on any hope to prove
its correctness.  Accordingly, proofs and tests have, since the onset
of software engineering research, been pursued by distinct
communities.

However, the development of both approaches lead to the discovery of
common issues and to the realization that each may need the other. The
emergence of model checking has been one of the first signs that
contradiction may yield to complementarity. Further evidence give test
data generation techniques from models or programs which boil down to
constraint resolution techniques for relatively large formula; the
advent of powerful SMT solvers have therefore powered new testing
techniques.  Finally, since formal, proof-based verification is
costly, testing invariants and background theories can be helpful to
detect errors early and to improve cost effectivity.  Summing up, in
the past few years an increasing number of research efforts have
encountered the need for combining proofs and tests, dropping earlier
dogmatic views of incompatibility and taking instead the best of what
each of these software engineering domains has to offer.

The TAP conference aims to bring together researchers and practitioners
working in the converging fields of testing and proving, and will offer
a generous allocation of papers, panels and informal discussions.

Topics of interest cover theory definitions, tool constructions and 
experimentations and include (other topics related to TAP are welcome):
- Transfer of concepts from testing to proving (e.g., coverage criteria)
  and from proving to testing
- Program proving with the aid of testing techniques
- New problematics in automated reasoning emerging from specificities
  of test generation
- Verification and testing techniques combining proofs and tests
- Generation of test data, oracles, or preambles by deductive
  techniques such as: theorem proving, model checking, symbolic
  execution, constraint logic programming
- Model-based testing and verification
- Generation of specifications by deduction
- Automatic bug finding
- Debugging of programs combining static and dynamic analysis
- Formal frameworks
- Tool descriptions and experience reports
- Case studies combining tests and proofs
- Applying combination of test and proof techniques to new application 
  domains such as validating security procotols or vulnerability
  detection of programs 

Important Dates:

Abstract submission:December 14, 2011 
Paper submission:   December 21, 2011
Notification:   March 2, 2012
Camera ready version:   March 19, 2012
TAP conference: May 31 - June 1, 2012 (to be confirmed)

TOOLS conferences (TOOLS, ICMT, SC, TAP): May 29 - June 01, 2012
Conference Chairs: Bertrand Meyer
Program Chairs:Achim D. Brucker and Jacques Julliand

Program Committee (to be extended): 
===
Nazareno Aguirre, Bernhard K. Aichernig, Paul Ammann, Dirk Beyer,
Nikolaj Bjorner, Robert Clarisó, Marco Comini, Catherine Dubois,
Gordon Fraser, Angelo Gargantini, Alain Giorgetti, Patrice Godefroid, 
Martin Gogolla, Arnaud Gotlieb, Reiner Hähnle, Bart Jacobs, Thierry Jéron, 
Gregory Kapfhammer, Nikolai Kosmatov, Victor Kuliamin, Karl Meinke, Jeff 
Offutt, Holger Schlingloff, T.H. Tse, Margus Veanes, Luca Viganò, Burkhart 
Wolff, Fatiha Zaidi

Submission:
===
Please submit your papers via http://lifc.univ-fcomte.fr/tap2012/. 
TAP 2012 will accept two types of papers: 
- Research papers: full papers with at most 16 pages in LNCS format
  (pdf), which have to be original, unpublished and not submitted
  elsewhere.
- Short contributions: work in progress, (industrial) experience
  reports or tool demonstrations, position statements; an extended
  abstract with at most 6 pages in LNCS format (pdf) is expected.

Accepted papers will be published in the Springer LNCS series and