[Haskell-cafe] Beginners Question: Problem with Data Type Declaration

2011-06-16 Thread kaffeepause73
I try to create an own data type containing Vector Double from the H-Matrix
package. The code:

## 

data PowerSig = PowerSig Int Double Vector Double

main = do
let p5 = PowerSig 1 0.1 (fromList [1,2,3])

## 

When compiling with ghci, I get however the following message:

`Vector' is not applied to enough type arguments
Expected kind `?', but `Vector' has kind `* - *'
In the type `Vector'
In the definition of data constructor `PowerSig'
In the data type declaration for `PowerSig'

I don't understand the compilers message and couldn't find any
wiki-page/other material to help me.
The Data Declaration somehow seems not to understand that Vector Double
belongs together, but brackets don't help either.

Cheers Phil



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/Beginners-Question-Problem-with-Data-Type-Declaration-tp4494012p4494012.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Beginners Question: Problem with Data Type Declaration

2011-06-16 Thread Johan Tibell
Hi,

On Thu, Jun 16, 2011 at 9:53 AM, kaffeepause73 kaffeepaus...@yahoo.de wrote:
 I try to create an own data type containing Vector Double from the H-Matrix
 package. The code:

 ##

 data PowerSig = PowerSig Int Double Vector Double

You need to put parenthesis around (Vector Double). Otherwise this is
interpreted as a constructor with 4 fields (instead of 3).

Johan

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


Re: [Haskell-cafe] Best platform for development with GHC?

2011-06-16 Thread Ketil Malde
Dmitri O.Kondratiev doko...@gmail.com writes:

 Let me know if you would like opinions on Emacs vs vi!

 I know vi, but it is just that I got used to Emacs which is my main IDE for
 most PL that I work with and for many years already )

No, no! Stop, it was just a joke, really.  I regret it already. :-)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] Best platform for development with GHC?

2011-06-16 Thread Ketil Malde
John D. Ramsdell ramsde...@gmail.com writes:

 Developers should be using older versions of GHC because they cannot
 be sure users will have an up-to-date GHC.  

I wonder, how hard would it be to have, say Amazon images of various
Linux distributions with ghc and cabal-install available?  Currently, I
have a discontious integration server that checks my stuff by pulling
off hackage, but this is a bit limited, as well as a security risk.  I'd
consider running something off Amazon instead - perhaps it could
even be automated, so that I could do 'cabal install whatever' in
parallel on a slew of configurations?  And, although I could probably
pay for my own stuff, perhaps Amazon could contribute (som of) the CPU
time?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] Beginners Question: Problem with Data Type Declaration

2011-06-16 Thread kaffeepause73
Hi Johan, 

actually quite obvious. Code works now, many thanks. :-)


import Data.Packed.Vector

data PowerSig = PowerSig Int Double (Vector Double) -- signal Index timeStep
data 

instance Show PowerSig where  
  show (PowerSig idx dt vector) = PowerSignal Nr:  ++ show idx ++   dt: 
++ show dt ++  val: ++ show vector
  
main = do 

let p = PowerSig 5 0.1 (fromList [0..10::Double])
putStrLn (show p)

--
View this message in context: 
http://haskell.1045720.n5.nabble.com/Beginners-Question-Problem-with-Data-Type-Declaration-tp4494012p4494166.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] Win32: cabal install --prefix=$HOME --user ?

2011-06-16 Thread Dmitri O.Kondratiev
On win32 cabal install --prefix=$HOME --user fails:

cabal install --prefix=$HOME --user
Resolving dependencies...
Configuring split-0.1.4...
cabal: expected an absolute directory name for --prefix: $HOME
cabal: Error: some packages failed to install:
split-0.1.4 failed during the configure step. The exception was:
ExitFailure 1

What is the right equivalent of cabal install --prefix=$HOME --user on
Win32?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Build failure on Hackage, missing syb

2011-06-16 Thread José Pedro Magalhães
Hi all,

What causes the following build failure on Hackage?

*** setup configure

 Configuring instant-generics-0.3.2...
 cabal-setup: At least the following dependencies are missing:
 syb 0.4


This is in package
instant-generics-0.3.2http://hackage.haskell.org/packages/archive/instant-generics/0.3.2/logs/failure/ghc-7.0.
The syb package built fine on Hackage. Previously, packages depending on syb
built fine too (e.g. http://hackage.haskell.org/package/syz). So why is
instant-generics-0.3.2 not building?


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


Re: [Haskell-cafe] Parsing Haskell in Parsec

2011-06-16 Thread Johannes Waldmann

 You may browse my source code (quite unpolished) ...

updated locations:

http://dfa.imn.htwk-leipzig.de/cgi-bin/gitweb.cgi?p=ws10-cb.git;a=summary

git clone  git://dfa.imn.htwk-leipzig.de/srv/git/ws10-cb




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


Re: [Haskell-cafe] Best platform for development with GHC?

2011-06-16 Thread cheater cheater
Hi,
let me chime in as someone who wanted to deploy a Haskell app on a
fairly popular hosting environment (Slicehost).
The support of GHC on the Ubuntu server front is tragic - there's no
official Haskell Platform for the currently suggested server version
of Ubuntu, which is Ubuntu 10.04 LTS (Long Term Support). It will
still have to be supported for the next about-five years. Setting
aside arguments of whether Ubuntu is the best choice for a server, it
is fairly popular, and easy to use. You can expect any developer who
wants to jump into Haskell for e.g. web-related servers to use Ubuntu,
because it's easy. 10.04 LTS only has single GHC packages and some
other stuff, but the Platform is missing. It is impossible to compile
HP on a virtual server, and cross-compiling is beyond the casual
user's skill. The solution would be to have a PPA with binaries that
people can use - PPA usage is well documented and popular among Ubuntu
folks.

In the end this project died off because I simply could not get HP into the box.

Notice that - ironically - Ubuntu 10.10 and further versions, none of
which are Long Term Support versions, do have HP as a package.

I hope this can happen and that it can be officially backed - as
opposed to a halfway-effort which will be someone hosting a private
PPA, getting bored of it after 3 months/weeks/hours, and the whole
situation returning to an even worse state than it was before.

I hope we can get good Haskell support for the most popular server
version of one of the most popular Linux distribution, because frankly
the current options are just terrible and useless.

Cheers,
D.

On Thu, Jun 16, 2011 at 08:40, Ketil Malde ke...@malde.org wrote:
 John D. Ramsdell ramsde...@gmail.com writes:

 Developers should be using older versions of GHC because they cannot
 be sure users will have an up-to-date GHC.

 I wonder, how hard would it be to have, say Amazon images of various
 Linux distributions with ghc and cabal-install available?  Currently, I
 have a discontious integration server that checks my stuff by pulling
 off hackage, but this is a bit limited, as well as a security risk.  I'd
 consider running something off Amazon instead - perhaps it could
 even be automated, so that I could do 'cabal install whatever' in
 parallel on a slew of configurations?  And, although I could probably
 pay for my own stuff, perhaps Amazon could contribute (som of) the CPU
 time?

 -k
 --
 If I haven't seen further, it is by standing in the footprints of giants

 ___
 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] Data Type Inheritance ala OO - Inheritence -- howto best in Haskell ?

2011-06-16 Thread kaffeepause73
Dear all, 

I'm created a timeSignal datatype as container around a Vector Double data
type (see simple code below) and subsequently started to instanciate Num 
Eq to be able to perform operations on it. Additionally I want store ifno
like an index, time information and eventually an inheritence log (the log
is not yet in there).  

As I will in the end need up to 10 different datatypes, however using
slightly different content (time signal, single value, distribution, ...) I
ask myself, how I could define a super data-type with sub-data-types to
inherit, but then also overload certain functions (like u would do in OO). 

What is best way in haskell to achieve this ? (I'm unsure wether haskell
classes are what I'm looking for)

Cheers Phil

## Code below

import qualified Data.Vector.Unboxed as V

data TimeSig = TimeSig Int Double (V.Vector Double) -- signal Index timeStep
data 

getVect :: TimeSig - (V.Vector Double) 
getVect (TimeSig idx dt vect)= vect

getIdx :: TimeSig - Int
getIdx (TimeSig idx dt vect) = idx

getdt :: TimeSig - Double
getdt (TimeSig idx dt vect) = dt

pzipWith :: (Double - Double - Double) - TimeSig - TimeSig - TimeSig
pzipWith f p1 p2 =  TimeSig idx dt vect
  where 
vect = V.zipWith f (getVect p1)  (getVect p2) 
idx = getIdx p1
dt = getdt p1
  
pmap :: (Double - Double) - TimeSig - TimeSig
pmap f p = TimeSig (getIdx p) (getdt p) (V.map f (getVect p))

instance Num TimeSig 
  where
  (+) p1 p2 = pzipWith (+) p1 p2
  (-) p1 p2 = pzipWith (-) p1 p2
  negate p1 = pmap negate p1
  abs p1 = pmap abs p1
  (*) p1 p2 = pzipWith (*) p1 p2

instance Eq TimeSig where
(==) p1 p2 = (==) (getVect p1) (getVect p2)


instance Show TimeSig where  
  show (TimeSig idx dt vect) = TimeSignal Nr:  ++ show idx ++   dt:  ++
show dt ++  val: ++ show vect
  
  
  
main = do 

let p = TimeSig 5 0.1 (V.fromList [0..10::Double])
putStrLn (show p)
putStrLn (show (p+p))

--
View this message in context: 
http://haskell.1045720.n5.nabble.com/Data-Type-Inheritance-ala-OO-Inheritence-howto-best-in-Haskell-tp4494800p4494800.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] Data.Map: Values to keys and keys to values

2011-06-16 Thread Dmitri O.Kondratiev
Hi,
Data.Map has many great functions, yet I could not find the one that allows
from one map create another map where keys are values and values are keys of
the first one.
Something like:
transMap:: (Ord k, Ord a) = Map k a - Map a k

Does such function exist?
Thanks!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Map: Values to keys and keys to values

2011-06-16 Thread Johan Tibell
On Thu, Jun 16, 2011 at 3:01 PM, Dmitri O.Kondratiev doko...@gmail.com wrote:
 Hi,
 Data.Map has many great functions, yet I could not find the one that allows
 from one map create another map where keys are values and values are keys of
 the first one.
 Something like:
 transMap:: (Ord k, Ord a) = Map k a - Map a k

 Does such function exist?

Note that such a function would be lossy as there might be duplicate
values in the map.

Cheers,
Johan

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


Re: [Haskell-cafe] Data.Map: Values to keys and keys to values

2011-06-16 Thread Daniel Peebles
Why not make it unlossy and have:

trans :: (Ord k, Ord a) = Map k a - Map a (Set k)



On Thu, Jun 16, 2011 at 9:10 AM, Johan Tibell johan.tib...@gmail.comwrote:

 On Thu, Jun 16, 2011 at 3:01 PM, Dmitri O.Kondratiev doko...@gmail.com
 wrote:
  Hi,
  Data.Map has many great functions, yet I could not find the one that
 allows
  from one map create another map where keys are values and values are keys
 of
  the first one.
  Something like:
  transMap:: (Ord k, Ord a) = Map k a - Map a k
 
  Does such function exist?

 Note that such a function would be lossy as there might be duplicate
 values in the map.

 Cheers,
 Johan

 ___
 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] Data.Map: Values to keys and keys to values

2011-06-16 Thread Francesco Mazzoli

On 16/06/11 15:01, Dmitri O.Kondratiev wrote:

Hi,
Data.Map has many great functions, yet I could not find the one that
allows from one map create another map where keys are values and values
are keys of the first one.
Something like:
transMap:: (Ord k, Ord a) = Map k a - Map a k

Does such function exist?
Thanks!



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


What about something like

transMap :: (Ord k, Ord a) = Map k a - Map a k
transMap = M.fromList . map swap . M.toList

?

Francesco.

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


Re: [Haskell-cafe] Data.Map: Values to keys and keys to values

2011-06-16 Thread Johan Tibell
On Thu, Jun 16, 2011 at 3:01 PM, Dmitri O.Kondratiev doko...@gmail.com wrote:
 Hi,
 Data.Map has many great functions, yet I could not find the one that allows
 from one map create another map where keys are values and values are keys of
 the first one.
 Something like:
 transMap:: (Ord k, Ord a) = Map k a - Map a k

I don't think implementing this function in the library would add much
as it cannot be implemented more efficiently with access to the
internal representation than it can using the public API. Just write

transMap = M.fromList . map swap . M.toList

and stick it in some utility file.

Johan

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


Re: [Haskell-cafe] Data.Map: Values to keys and keys to values

2011-06-16 Thread Dmitri O.Kondratiev
On Thu, Jun 16, 2011 at 5:38 PM, Johan Tibell johan.tib...@gmail.comwrote:

 On Thu, Jun 16, 2011 at 3:01 PM, Dmitri O.Kondratiev doko...@gmail.com
 wrote:
  Hi,
  Data.Map has many great functions, yet I could not find the one that
 allows
  from one map create another map where keys are values and values are keys
 of
  the first one.
  Something like:
  transMap:: (Ord k, Ord a) = Map k a - Map a k

 I don't think implementing this function in the library would add much
 as it cannot be implemented more efficiently with access to the
 internal representation than it can using the public API. Just write

transMap = M.fromList . map swap . M.toList

 and stick it in some utility file.

 Johan



Yes, this is a good one. Thanks!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Win32: cabal install --prefix=$HOME --user ?

2011-06-16 Thread Ryan Yates
There is a nice table in the cabal docs that explains how prefix gets used:

http://www.haskell.org/ghc/docs/7.0.4/html/Cabal/builders.html#simple-paths

For Vista and above C:\Documents and settings\myusername\ is
C:\Users\myusername.  The equivalent to $HOME on Windows would be
$USERPROFILE but the syntax of expanding an environment variable is
going to depend on the shell you are using:

cmd window:  cabal install --prefix=%USERPROFILE% --user
PowerShell:  cabal install --prefix=${env:USERPROFILE} --user
msys window:  cabal install --prefix=$USERPROFILE --user

Note that msys does define $HOME and it is a different physical path
than $USERPROFILE.


Ryan

On Thu, Jun 16, 2011 at 5:48 AM, Dmitri O.Kondratiev doko...@gmail.com wrote:
 On win32 cabal install --prefix=$HOME --user fails:

 cabal install --prefix=$HOME --user
 Resolving dependencies...
 Configuring split-0.1.4...
 cabal: expected an absolute directory name for --prefix: $HOME
 cabal: Error: some packages failed to install:
 split-0.1.4 failed during the configure step. The exception was:
 ExitFailure 1

 What is the right equivalent of cabal install --prefix=$HOME --user on
 Win32?


 ___
 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] Win32: cabal install --prefix=$HOME --user ?

2011-06-16 Thread Dmitri O.Kondratiev
On Thu, Jun 16, 2011 at 6:18 PM, Ryan Yates fryguy...@gmail.com wrote:

 There is a nice table in the cabal docs that explains how prefix gets used:

 http://www.haskell.org/ghc/docs/7.0.4/html/Cabal/builders.html#simple-paths

 For Vista and above C:\Documents and settings\myusername\ is
 C:\Users\myusername.  The equivalent to $HOME on Windows would be
 $USERPROFILE but the syntax of expanding an environment variable is
 going to depend on the shell you are using:

 cmd window:  cabal install --prefix=%USERPROFILE% --user
 PowerShell:  cabal install --prefix=${env:USERPROFILE} --user
 msys window:  cabal install --prefix=$USERPROFILE --user

 Note that msys does define $HOME and it is a different physical path
 than $USERPROFILE.


Ryan, thanks!
This win32 $HOME story is clear now.
And why not just use:
cabal install
instead of:
cabal install --prefix=%USERPROFILE% --user
for win32 platform?
Where in this case cabal install root will be?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Win32: cabal install --prefix=$HOME --user ?

2011-06-16 Thread Ryan Yates
I never set the prefix manually and just use the default.  The default
for Windows is $APPDATA/Cabal.  Where that ends up depends on your
version of Windows.  On Windows --user is also the default.

On Thu, Jun 16, 2011 at 10:47 AM, Dmitri O.Kondratiev doko...@gmail.com wrote:


 On Thu, Jun 16, 2011 at 6:18 PM, Ryan Yates fryguy...@gmail.com wrote:

 There is a nice table in the cabal docs that explains how prefix gets
 used:


 http://www.haskell.org/ghc/docs/7.0.4/html/Cabal/builders.html#simple-paths

 For Vista and above C:\Documents and settings\myusername\ is
 C:\Users\myusername.  The equivalent to $HOME on Windows would be
 $USERPROFILE but the syntax of expanding an environment variable is
 going to depend on the shell you are using:

 cmd window:  cabal install --prefix=%USERPROFILE% --user
 PowerShell:  cabal install --prefix=${env:USERPROFILE} --user
 msys window:  cabal install --prefix=$USERPROFILE --user

 Note that msys does define $HOME and it is a different physical path
 than $USERPROFILE.


 Ryan, thanks!
 This win32 $HOME story is clear now.
 And why not just use:
 cabal install
 instead of:
 cabal install --prefix=%USERPROFILE% --user
 for win32 platform?
 Where in this case cabal install root will be?




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


Re: [Haskell-cafe] Data Type Inheritance ala OO - Inheritence -- howto best in Haskell ?

2011-06-16 Thread David Barbour
Look into Oleg's HList (heterogeneous list) and OOHaskell

http://homepages.cwi.nl/~ralf/HList/
http://homepages.cwi.nl/~ralf/OOHaskell/


On Thu, Jun 16, 2011 at 5:08 AM, kaffeepause73 kaffeepaus...@yahoo.dewrote:

 Dear all,

 I'm created a timeSignal datatype as container around a Vector Double
 data
 type (see simple code below) and subsequently started to instanciate Num 
 Eq to be able to perform operations on it. Additionally I want store ifno
 like an index, time information and eventually an inheritence log (the log
 is not yet in there).

 As I will in the end need up to 10 different datatypes, however using
 slightly different content (time signal, single value, distribution, ...) I
 ask myself, how I could define a super data-type with sub-data-types to
 inherit, but then also overload certain functions (like u would do in OO).

 What is best way in haskell to achieve this ? (I'm unsure wether haskell
 classes are what I'm looking for)

 Cheers Phil

 ## Code below

 import qualified Data.Vector.Unboxed as V

 data TimeSig = TimeSig Int Double (V.Vector Double) -- signal Index
 timeStep
 data

 getVect :: TimeSig - (V.Vector Double)
 getVect (TimeSig idx dt vect)= vect

 getIdx :: TimeSig - Int
 getIdx (TimeSig idx dt vect) = idx

 getdt :: TimeSig - Double
 getdt (TimeSig idx dt vect) = dt

 pzipWith :: (Double - Double - Double) - TimeSig - TimeSig - TimeSig
 pzipWith f p1 p2 =  TimeSig idx dt vect
  where
vect = V.zipWith f (getVect p1)  (getVect p2)
idx = getIdx p1
dt = getdt p1

 pmap :: (Double - Double) - TimeSig - TimeSig
 pmap f p = TimeSig (getIdx p) (getdt p) (V.map f (getVect p))

 instance Num TimeSig
  where
  (+) p1 p2 = pzipWith (+) p1 p2
  (-) p1 p2 = pzipWith (-) p1 p2
  negate p1 = pmap negate p1
  abs p1 = pmap abs p1
  (*) p1 p2 = pzipWith (*) p1 p2

 instance Eq TimeSig where
(==) p1 p2 = (==) (getVect p1) (getVect p2)


 instance Show TimeSig where
  show (TimeSig idx dt vect) = TimeSignal Nr:  ++ show idx ++   dt:  ++
 show dt ++  val: ++ show vect



 main = do

let p = TimeSig 5 0.1 (V.fromList [0..10::Double])
putStrLn (show p)
putStrLn (show (p+p))

 --
 View this message in context:
 http://haskell.1045720.n5.nabble.com/Data-Type-Inheritance-ala-OO-Inheritence-howto-best-in-Haskell-tp4494800p4494800.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

 ___
 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] Data.Map: Values to keys and keys to values

2011-06-16 Thread Brent Yorgey
On Thu, Jun 16, 2011 at 04:17:55PM +0200, Francesco Mazzoli wrote:
 On 16/06/11 15:01, Dmitri O.Kondratiev wrote:
 Hi,
 Data.Map has many great functions, yet I could not find the one that
 allows from one map create another map where keys are values and values
 are keys of the first one.
 Something like:
 transMap:: (Ord k, Ord a) = Map k a - Map a k
 
 Does such function exist?
 Thanks!
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 What about something like
 
 transMap :: (Ord k, Ord a) = Map k a - Map a k
 transMap = M.fromList . map swap . M.toList
 
 ?

Or, if you want to keep duplicates,

import qualified Data.Set as S
import Control.Arrow (second)

transMap = M.fromListWith S.union . map (second S.singleton . swap) . M.toList

-Brent

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


[Haskell-cafe] Haskell Parallel Digest 3

2011-06-16 Thread Nicolas Wu

Parallel Haskell Digest
===
Edition 3
2011-06-16
http://www.well-typed.com/blog/55

Hello Haskellers!

Welcome to the third edition of the Parallel Haskell Digest, bringing
you news, discussions and tasters of parallelism and concurrency in
Haskell. The digest is made possible by the Parallel GHC project.
More news about how we're doing below.

This digest is brought to you by Eric Kow and Nicolas Wu. Nick will
be taking over as maintainer of the Parallel Digest for the next few
months.

It's tutorial season in the Parallel Haskell world, with Simon
Marlow's [Parallel and Concurrent Programming in Haskell][1], and Don
Stewart's [Numeric Haskell: A Repa Tutorial][2]. The former gives a
broad tour of parallelism and concurrency techniques in Haskell and
the latter focuses on the Repa parallel array library. Both are very
concrete and focus on real working code. Give them a try!

News
--
* Haskell in the Economist! The Economist article [Parallel Bars][3]
discusses the rise of multicore computing, and the essential
obstacle that programs have to be specially written with parallelism
in mind. The article gives a tour of some problems (overhead and
dependencies between subtasks, programmers being trained for
sequential programming, debugging parallel programs) and possible
solutions, among which is functional programming:


Meanwhile, a group of obscure programming languages used in
academia seems to be making slow but steady progress, crunching
large amounts of data in industrial applications and behind the
scenes at large websites. Two examples are Erlang and Haskell,
both of which are “functional programming” languages.


Are we doomed to succeed?


Word of the Month
--
The word of the month (well, phrase really!) for this digest is
*parallel arrays*. Parallel array manipulation fits nicely into
Haskell's arsenal of parallel processing techniques. In fact, you
might have seen the Repa library, as mentioned above, in the news
a while back. And now there's a new tutorial on the [Haskell Wiki][2].
So what's all the fuss?

Parallel arrays manipulation is a particularly nice way of writing
parallel programs: it's pure and it has the potential to scale very
well to large numbers of CPUs. The main limitation is that not all
programs can be written in this style. Parallel arrays are a way of
doing *data parallelism* (as opposed to *control parallelism*).

Repa (REgular Parallel Arrays) is a Haskell library for high
performance, regular, multi-dimensional parallel arrays. All numeric
data is stored unboxed and functions written with the Repa combinators
are automatically parallel. This means that you can write simple array
code and get parallelism for free.

As an example, Repa has been used for real time edge detection using a
[Canny edge algorithm][12], which has resulted in performance
comparable to the standard OpenCV library, an industry standard
library of computer vision algorithms written in C and C++ (a single
threaded Haskell implementation is about 4 times slower than the
OpenCV implementation, but is on par when using 8 threads on large
images).

While the Canny algorithm written with Repa doesn't quite match the
speed of its procedural counterparts, it benefits from all of
Haskell's built in support for purity and type safety, and painlessly
scales to multiple cores. You can find more details on Ben Lippmeier's
[blog][10].


Parallel GHC project news
--
The Parallel GHC Project is an MSR-funded project to promote the
real-world use of parallel Haskell. Part of this project involves
effort by Well-Typed to provide tools for use by the general
community.

Last week, Well-Typed were excited to [announce][11] that we have
capacity to support another partner for the parallel project for at
least another 12 months. So, if you have a project that involves
scaling up to multiple cores, or that deals with some heavy duty
concurrency, then we'd love to hear from you. In return for your time
and commitment to the parallel project, we'll unleash our team of
expert programmers to help build tools and provide support that will
help you and the community towards making parallel Haskell even more
accessible.

For more information on the Parallel GHC project,
on the [Parallel GHC Project wiki page][27].

Blogs, papers and packages
--
* [Parallel and Concurrent Programming in Haskell (19 May)][1]

Simon Marlow released version 1.1 of his tutorial introducing the
main programming models available for concurrent and parallel
programming in Haskell. This tutorial takes a deliberately
practical approach: most of the examples are real Haskell programs
that you can compile, run, measure, modify and experiment with. The
tutorial covers a 

Re: [Haskell-cafe] Acquiring a random set of a specific size (w/o dups) from a range of Ints

2011-06-16 Thread michael rice
I seem to still be missing some things. I found mt19937 in GSL.Random.Gen, but 
there are two evalMCs, one in Control.Monad.MC and another in 
Control.Monad.MC.GSL. Which?
Michael
-
Registering monte-carlo-0.4.1...Installing library in 
/home/michael/.cabal/lib/monte-carlo-0.4.1/ghc-7.0.2Registering 
monte-carlo-0.4.1...[michael@sabal ~]$ ghciGHCi, version 7.0.2: 
http://www.haskell.org/ghc/  :? for helpLoading package ghc-prim ... linking 
... done.Loading package integer-gmp ... linking ... done.Loading package base 
... linking ... done.Prelude :m + Control.Monad.MC.ClassPrelude 
Control.Monad.MC.Class evalMC (sampleSubset [1..20] 5) (mt19937 0)
interactive:1:1: Not in scope: `evalMC'
interactive:1:34: Not in scope: `mt19937'Prelude Control.Monad.MC.Class
--- On Mon, 6/13/11, Felipe Almeida Lessa felipe.le...@gmail.com wrote:

From: Felipe Almeida Lessa felipe.le...@gmail.com
Subject: Re: [Haskell-cafe] Acquiring a random set of a specific size (w/o 
dups) from a range of Ints
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Monday, June 13, 2011, 9:38 PM

On Mon, Jun 13, 2011 at 8:56 PM, michael rice nowg...@yahoo.com wrote:
 Is there an (existing) way to select 5 Ints randomly (no duplicates) from a 
 population, say 1-20 (inclusive)?

Yes, already implemented in the monte-carlo package as sampleSubset [1],

  sampleSubset :: MonadMC m = [a] - Int - m [a]

Complete example code for your example:

  evalMC (sampleSubset [1..20] 5) (mt19937 0)

Cheers!

[1] 
http://hackage.haskell.org/packages/archive/monte-carlo/0.4.1/doc/html/Control-Monad-MC-Class.html#v:sampleSubset

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


Re: [Haskell-cafe] Acquiring a random set of a specific size (w/o dups) from a range of Ints

2011-06-16 Thread Felipe Almeida Lessa
On Thu, Jun 16, 2011 at 3:04 PM, michael rice nowg...@yahoo.com wrote:
 I seem to still be missing some things. I found mt19937 in GSL.Random.Gen, 
 but there are two evalMCs, one in Control.Monad.MC and another in 
 Control.Monad.MC.GSL. Which?

Both are actually the same, because Control.Monad.MC reexports from
Control.Monad.MC.GSL. =)

GHCi, version 6.12.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Prelude :m + Control.Monad.MC
Prelude Control.Monad.MC evalMC (sampleSubset [1..20] 5) (mt19937 0)
Loading package mtl-1.1.1.1 ... linking ... done.
Loading package primitive-0.3.1 ... linking ... done.
Loading package vector-0.7.0.1 ... linking ... done.
Loading package gsl-random-0.4.2 ... linking ... done.
Loading package monte-carlo-0.4.1 ... linking ... done.
[20,4,6,17,19]
Prelude Control.Monad.MC evalMC (sampleSubset [1..20] 5) (mt19937 42)
[8,16,18,4,12]
Prelude Control.Monad.MC evalMC (sampleSubset [1..20] 5) (mt19937 2938420)
[18,3,2,9,14]
Prelude Control.Monad.MC evalMC (sampleSubset [1..20] 5) (mt19937 0)
[20,4,6,17,19]

Cheers,

--
Felipe.

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


[Haskell-cafe] ANNOUNCE: doctest-0.3.0

2011-06-16 Thread Simon Hengel
I just uploaded a new version of doctest[1] to Hackage.


WHAT IS doctest?


doctest is a port of Python's doctest[2] to Haskell.  It can be used to
verify, that examples in Haddock comments[3] do still work.  This also
provides you with a simple mechanism to write unit test, without the
burden of maintaining a dedicated test suite.

A basic example of usage is at [4].


WHAT'S NEW IN THIS VERSION?
===

It is now possible to intersperse comments between a longer, continuing
example.  All examples within the same comment now share a namespace.
The following now works :

-- | Calculate Fibonacci number of given 'Num'.
--
-- First let's set `n` to ten:
--
--  let n = 10
--
-- And now calculate the 10th Fibonacci number:
--
--  fib n
-- 55
fib :: Integer - Integer
fib 0 = 0
fib 1 = 1
fib n = fib (n - 1) + fib (n - 2)

Thanks to Sakari Jokinen for this contribution!

In addition I changed the name from DocTest to doctest.  I think using
all lower-case package names is a good thing.  And as we will use
doctest as a library in the near future, this was the last chance for
this change.

Cheers,
Simon

[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/doctest
[2] http://docs.python.org/library/doctest.html
[3] http://www.haskell.org/haddock/doc/html/ch03s08.html#id566093
[4] http://haskell.org/haskellwiki/DocTest

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


Re: [Haskell-cafe] Data Type Inheritance ala OO - Inheritence -- howto best in Haskell ?

2011-06-16 Thread gutti
Hi David, 

thanks for the links. I had a lok at the OO-paper some time ago already,
heard however that its quite unusual and rather tricky to do OO-style
programming in Haskell. So I'm looking for suggestions how to tackle this
problem in a functional way.

Cheers Phil

--
View this message in context: 
http://haskell.1045720.n5.nabble.com/Data-Type-Inheritance-ala-OO-Inheritence-howto-best-in-Haskell-tp4494800p4496726.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] Simple CSV parser?

2011-06-16 Thread Dmitri O.Kondratiev
Hi,
This time I am looking for a simple CSV parser that supports commas and
quotes. I have no time now to learn Parsec, so I hope to find something
simple and easy to use.

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


Re: [Haskell-cafe] Simple CSV parser?

2011-06-16 Thread Daniel Patterson
Do any of the ones on hackage work for you?

http://hackage.haskell.org/package/csv-0.1.2

http://hackage.haskell.org/package/bytestring-csv

http://hackage.haskell.org/package/csv-enumerator

(note: hackage supports search via google it works reasonably well)

On Jun 16, 2011, at 5:21 PM, Dmitri O.Kondratiev wrote:

 Hi,
 This time I am looking for a simple CSV parser that supports commas and 
 quotes. I have no time now to learn Parsec, so I hope to find something 
 simple and easy to use.
 
 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] Simple CSV parser?

2011-06-16 Thread Felipe Almeida Lessa
On Thu, Jun 16, 2011 at 6:21 PM, Dmitri O.Kondratiev doko...@gmail.com wrote:
 This time I am looking for a simple CSV parser that supports commas and
 quotes. I have no time now to learn Parsec, so I hope to find something
 simple and easy to use.

1. Go to http://hackage.haskell.org/packages/archive/pkg-list.html

2. Press Ctrl+F, look for CSV.

3. Find many packages [1,2,3,4,5]

4. See which one suits better your needs.

[1] http://hackage.haskell.org/package/bytestring-csv
[2] http://hackage.haskell.org/package/csv-enumerator
[3] http://hackage.haskell.org/package/spreadsheet
[4] http://hackage.haskell.org/package/csv
[5] http://hackage.haskell.org/package/ssv

-- 
Felipe.

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


[Haskell-cafe] 8th Ghent Functional Programming Group Meeting on Thursday, the 30th of June, 2011

2011-06-16 Thread Jeroen Janssen
(apologies if you receive multiple postings)

Dear All,

We are pleased to announce the 8th Ghent Functional Programming Group 
(GhentFPG) meeting, which takes place on Thursday, the 30th of June, 2011 at 
19:30 in the Technicum building of Ghent University (Sint-Pietersnieuwstraat 
41, 9000 Gent). As before, the electronic sliding doors will be locked, but a 
phone number that you can call to get in will be provided at the doors on the 
far left of the building.

The structure of the meeting is a bit different than before: we begin with two 
short talks and end with a small problem solving activity where everyone tries 
to solve a given problem in his favorite functional language. The exact problem 
will be given at the meeting. The abstracts for the talks are as follows:

Pieter Wuille
-

I'll talk about the monadic constraint programming (MCP) framework, and in
particular the Finite Domain layer i've developed for it. As explained by Tom
Schrijvers in a previous talk, MCP is a general Haskell framework for Constraint
Programming (CP), allowing users to search for assignments to variables that
satisfy given constraints, while abstracting from the actual algorithm used to
find these solutions.

Finite Domain problems are a subset of CP where the variable's initial domains
are finite, typically small integers. Problems that can be expressed elegantly
in FD include Sudoku and N-Queens. MCP's FD layer provides an embedded Domain
Specific Language (DSL) to describe these problems declaratively, some backend
solvers, and an intermediate translation layer.  I'll introduce the features and
possibilities of the system by showing some examples, and explain some
implementation details along the way.

Jasper Van der Jeugt


I will give a talk about the techniques and patterns used in the Text library.
Text is quickly becoming the de-facto standard type for presenting
human-readable text in Haskell.  My current work focuses on improving the
performance of this library by porting the internally used encoding from UTF-16
to UTF-8.

The talk will present a high-level overview of some tools and techniques to
study and improve the performance of a Haskell program, including: strictness
analysis, pitfalls for benchmarking, fusion frameworks, unboxed type
representations, and GHC core.


If you would like to receive updates on our activities, you can follow us on 
twitter (@ghentfpg), google groups 
(http://groups.google.com/group/ghent-fpg?pli=1) or linked.in 
(http://t.co/cjXbGyT)


Hope to see you there!

Andy Georges
Jasper Van der Jeugt
Jeroen Janssen
The GhentFPG Organizing Committee
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple CSV parser?

2011-06-16 Thread Henning Thielemann


On Thu, 16 Jun 2011, Daniel Patterson wrote:


Do any of the ones on hackage work for you?
http://hackage.haskell.org/package/csv-0.1.2

http://hackage.haskell.org/package/bytestring-csv

http://hackage.haskell.org/package/csv-enumerator

(note: hackage supports search via google it works reasonably well)


How could it miss my lovely package named spreadsheet? It provides a 
lazy parser.


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


Re: [Haskell-cafe] Simple CSV parser?

2011-06-16 Thread Daniel Patterson
That was my (lazy) fault. I saw the name and (faultily) assumed that it 
provided functionality on top of another CSV parser.


On Jun 16, 2011, at 5:33 PM, Henning Thielemann wrote:

 
 On Thu, 16 Jun 2011, Daniel Patterson wrote:
 
 Do any of the ones on hackage work for you?
 http://hackage.haskell.org/package/csv-0.1.2
 http://hackage.haskell.org/package/bytestring-csv
 http://hackage.haskell.org/package/csv-enumerator
 (note: hackage supports search via google it works reasonably well)
 
 How could it miss my lovely package named spreadsheet? It provides a lazy 
 parser.


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


Re: [Haskell-cafe] Simple CSV parser?

2011-06-16 Thread Dmitri O.Kondratiev
On Fri, Jun 17, 2011 at 1:27 AM, Felipe Almeida Lessa 
felipe.le...@gmail.com wrote:

 On Thu, Jun 16, 2011 at 6:21 PM, Dmitri O.Kondratiev doko...@gmail.com
 wrote:
  This time I am looking for a simple CSV parser that supports commas and
  quotes. I have no time now to learn Parsec, so I hope to find something
  simple and easy to use.

 1. Go to http://hackage.haskell.org/packages/archive/pkg-list.html

 2. Press Ctrl+F, look for CSV.

 3. Find many packages [1,2,3,4,5]

 4. See which one suits better your needs.

 [1] http://hackage.haskell.org/package/bytestring-csv
 [2] http://hackage.haskell.org/package/csv-enumerator
 [3] http://hackage.haskell.org/package/spreadsheet
 [4] http://hackage.haskell.org/package/csv
 [5] http://hackage.haskell.org/package/ssv

 --
 Felipe.


Now I know where and how to search,  sorry for trivial questions )
Thanks!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple CSV parser?

2011-06-16 Thread Dmitri O.Kondratiev
On Fri, Jun 17, 2011 at 1:33 AM, Henning Thielemann 
lemm...@henning-thielemann.de wrote:

 How could it miss my lovely package named spreadsheet? It provides a lazy
 parser.



Installing spreadsheet:

cabal install
Resolving dependencies...
cabal: cannot configure explicit-exception-0.1.6. It requires transformers
==0.2.*
For the dependency on transformers ==0.2.* there are these packages:
transformers-0.2.0.0, transformers-0.2.1.0 and transformers-0.2.2.0. However
none of them are available.
transformers-0.2.0.0 was excluded because spreadsheet-0.1 requires
transformers ==0.0.*
transformers-0.2.1.0 was excluded because spreadsheet-0.1 requires
transformers ==0.0.*
transformers-0.2.2.0 was excluded because spreadsheet-0.1 requires
transformers ==0.0.*

How to make cabal install all the dependencies? I couldn't find this in the
docs at:
http://www.haskell.org/haskellwiki/Cabal-Install
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell on NUMA

2011-06-16 Thread Michael Lesniak
Hi,

what ist the current state of Haskell's parallel performance on NUMA
machines? I've (probably) run into some performance problems using a 2x8
cores machine and am unsure how to fix them (if it's possible at all at the
moment). I've only found two (helpful?) resources on the web, namely

- an old ticket which is closed [1]
- a current talk (13. May 2011) about a new runtime system for GHC7 for NUMA
machines [2]

Are any other informations available?


Kind regards,

Michael



[1] http://hackage.haskell.org/trac/summer-of-code/ticket/1123
[2] http://www.dcs.gla.ac.uk/~jsinger/mmnet11_talks/orczyk.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple CSV parser?

2011-06-16 Thread Henning Thielemann


On Fri, 17 Jun 2011, Dmitri O.Kondratiev wrote:


How to make cabal install all the dependencies? I couldn't find this in the 
docs at:
http://www.haskell.org/haskellwiki/Cabal-Install


Usually, 'cabal install' automatically installs all imported packages. But 
it will certainly not do, if a dependency problem cannot be solved by 
downloading packages. In your case it may be, that installed packages are 
compiled with respect to different versions of the same package, say 
'transformers'.


I found out, that you get more useful cabal messages if you force 
cabal-install to use a specific version of a package.


Say, run
$ ghc-pkg list transformers
transformers-0.2.2.0

Then call
$ cabal install spreadsheet --constraint=transformers==0.2.2.0

What does 'cabal' tell you?

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


Re: [Haskell-cafe] Simple CSV parser?

2011-06-16 Thread Jason Dagit
On Thu, Jun 16, 2011 at 3:05 PM, Henning Thielemann
lemm...@henning-thielemann.de wrote:

 On Fri, 17 Jun 2011, Dmitri O.Kondratiev wrote:

 How to make cabal install all the dependencies? I couldn't find this in
 the docs at:
 http://www.haskell.org/haskellwiki/Cabal-Install

 Usually, 'cabal install' automatically installs all imported packages. But
 it will certainly not do, if a dependency problem cannot be solved by
 downloading packages. In your case it may be, that installed packages are
 compiled with respect to different versions of the same package, say
 'transformers'.

 I found out, that you get more useful cabal messages if you force
 cabal-install to use a specific version of a package.

 Say, run
 $ ghc-pkg list transformers
 transformers-0.2.2.0

 Then call
 $ cabal install spreadsheet --constraint=transformers==0.2.2.0

Nicer still, is to use cabal-dev:
http://www.reddit.com/r/haskell/comments/f3ykj/psa_use_cabaldev_to_solve_dependency_problems/

Jason

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


Re: [Haskell-cafe] Simple CSV parser?

2011-06-16 Thread Dmitri O.Kondratiev
On Fri, Jun 17, 2011 at 2:05 AM, Henning Thielemann 
lemm...@henning-thielemann.de wrote:


 On Fri, 17 Jun 2011, Dmitri O.Kondratiev wrote:

  How to make cabal install all the dependencies? I couldn't find this in
 the docs at:
 http://www.haskell.org/haskellwiki/Cabal-Install


 Usually, 'cabal install' automatically installs all imported packages. But
 it will certainly not do, if a dependency problem cannot be solved by
 downloading packages. In your case it may be, that installed packages are
 compiled with respect to different versions of the same package, say
 'transformers'.

 I found out, that you get more useful cabal messages if you force
 cabal-install to use a specific version of a package.

 Say, run
 $ ghc-pkg list transformers

 transformers-0.2.2.0

 Then call
 $ cabal install spreadsheet --constraint=transformers==0.2.2.0

 What does 'cabal' tell you?


ghc-pkg list transformers
/Library/Frameworks/GHC.framework/Versions/612/usr/lib/ghc-6.12.3/package.conf.d:

/Users/user/.ghc/i386-darwin-6.12.3/package.conf.d:
transformers-0.2.2.0

cabal install spreadsheet --constraint=transformers==0.2.2.0
Resolving dependencies...
cabal: cannot configure spreadsheet-0.1. It requires transformers ==0.0.*
For the dependency on transformers ==0.0.* there are these packages:
transformers-0.0.0.0 and transformers-0.0.1.0. However none of them are
available.
transformers-0.0.0.0 was excluded because of the top level dependency
transformers ==0.2.2.0
transformers-0.0.1.0 was excluded because of the top level dependency
transformers ==0.2.2.0

Compilation exited abnormally with code 1 at Fri Jun 17 02:12:30
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple CSV parser?

2011-06-16 Thread Dmitri O.Kondratiev
On Fri, Jun 17, 2011 at 2:13 AM, Dmitri O.Kondratiev doko...@gmail.comwrote:



 On Fri, Jun 17, 2011 at 2:05 AM, Henning Thielemann 
 lemm...@henning-thielemann.de wrote:


 On Fri, 17 Jun 2011, Dmitri O.Kondratiev wrote:

  How to make cabal install all the dependencies? I couldn't find this in
 the docs at:
 http://www.haskell.org/haskellwiki/Cabal-Install


 Usually, 'cabal install' automatically installs all imported packages. But
 it will certainly not do, if a dependency problem cannot be solved by
 downloading packages. In your case it may be, that installed packages are
 compiled with respect to different versions of the same package, say
 'transformers'.

 I found out, that you get more useful cabal messages if you force
 cabal-install to use a specific version of a package.

 Say, run
 $ ghc-pkg list transformers

 transformers-0.2.2.0

 Then call
 $ cabal install spreadsheet --constraint=transformers==0.2.2.0

 What does 'cabal' tell you?


 ghc-pkg list transformers

 /Library/Frameworks/GHC.framework/Versions/612/usr/lib/ghc-6.12.3/package.conf.d:

 /Users/user/.ghc/i386-darwin-6.12.3/package.conf.d:

 transformers-0.2.2.0

 cabal install spreadsheet --constraint=transformers==0.2.2.0
 Resolving dependencies...
 cabal: cannot configure spreadsheet-0.1. It requires transformers ==0.0.*
 For the dependency on transformers ==0.0.* there are these packages:
 transformers-0.0.0.0 and transformers-0.0.1.0. However none of them are
 available.
 transformers-0.0.0.0 was excluded because of the top level dependency

 transformers ==0.2.2.0
 transformers-0.0.1.0 was excluded because of the top level dependency

 transformers ==0.2.2.0

 Compilation exited abnormally with code 1 at Fri Jun 17 02:12:30



I really have no choice, but install Data.Spreadsheet, because this is the
only library that allows split a _single_ CSV string into chunks (which is
exactly what I need). All other libs work with CSV files or provide a DSL to
do such a simple thing!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple CSV parser?

2011-06-16 Thread Henning Thielemann


On Fri, 17 Jun 2011, Dmitri O.Kondratiev wrote:


cabal install spreadsheet --constraint=transformers==0.2.2.0
Resolving dependencies...
cabal: cannot configure spreadsheet-0.1. It requires transformers ==0.0.*
For the dependency on transformers ==0.0.* there are these packages:
transformers-0.0.0.0 and transformers-0.0.1.0. However none of them are
available.
transformers-0.0.0.0 was excluded because of the top level dependency
transformers ==0.2.2.0
transformers-0.0.1.0 was excluded because of the top level dependency
transformers ==0.2.2.0


I see. I had fixed the problem locally long time ago, but somehow missed 
upload to Hackage. Try the updated package, please.


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


Re: [Haskell-cafe] Simple CSV parser?

2011-06-16 Thread Dmitri O.Kondratiev
On Fri, Jun 17, 2011 at 2:27 AM, Henning Thielemann 
lemm...@henning-thielemann.de wrote:

 I see. I had fixed the problem locally long time ago, but somehow missed
 upload to Hackage. Try the updated package, please.


Ok great! Installed (with some warnings, see below), thank you!
I'll try it tomorrow (now here is 2:34 am) on a file of about 4000 lines.
Thanks!

Compilation started at Fri Jun 17 02:29:59

cabal install
Resolving dependencies...
Downloading explicit-exception-0.1.6...
Configuring explicit-exception-0.1.6...
Preprocessing library explicit-exception-0.1.6...
Preprocessing executables for explicit-exception-0.1.6...
Building explicit-exception-0.1.6...
[1 of 9] Compiling Control.Monad.Label ( src/Control/Monad/Label.hs,
dist/build/Control/Monad/Label.o )
[2 of 9] Compiling Control.Monad.Exception.Synchronous (
src/Control/Monad/Exception/Synchronous.hs,
dist/build/Control/Monad/Exception/Synchronous.o )
[3 of 9] Compiling Control.Monad.Exception.Warning (
src/Control/Monad/Exception/Warning.hs,
dist/build/Control/Monad/Exception/Warning.o )
[4 of 9] Compiling Control.Monad.Exception.Label (
src/Control/Monad/Exception/Label.hs,
dist/build/Control/Monad/Exception/Label.o )
[5 of 9] Compiling System.IO.Straight ( src/System/IO/Straight.hs,
dist/build/System/IO/Straight.o )

src/System/IO/Straight.hs:61:9:
Warning: orphan instance:
  instance (MonadSIO m, ContainsIOException e) =
   MonadIO (ExceptionalT e m)
[6 of 9] Compiling System.IO.Exception.File (
src/System/IO/Exception/File.hs, dist/build/System/IO/Exception/File.o )
[7 of 9] Compiling System.IO.Exception.BinaryFile (
src/System/IO/Exception/BinaryFile.hs,
dist/build/System/IO/Exception/BinaryFile.o )
[8 of 9] Compiling Control.Monad.Exception.Asynchronous (
src/Control/Monad/Exception/Asynchronous.hs,
dist/build/Control/Monad/Exception/Asynchronous.o )
[9 of 9] Compiling System.IO.Exception.TextFile (
src/System/IO/Exception/TextFile.hs,
dist/build/System/IO/Exception/TextFile.o )

src/System/IO/Exception/TextFile.hs:8:0:
Warning: In the use of `Async.manySynchronousT'
 (imported from Control.Monad.Exception.Asynchronous):
 Deprecated: use manyMonoidT with appropriate Monad like LazyIO
and result Monoid like Endo instead
Registering explicit-exception-0.1.6...
Installing library in
/Users/user/.cabal/lib/explicit-exception-0.1.6/ghc-6.12.3
Registering explicit-exception-0.1.6...
Configuring spreadsheet-0.1.1...
Preprocessing library spreadsheet-0.1.1...
Building spreadsheet-0.1.1...
[1 of 3] Compiling Data.Spreadsheet.CharSource (
src/Data/Spreadsheet/CharSource.hs, dist/build/Data/Spreadsheet/CharSource.o
)
[2 of 3] Compiling Data.Spreadsheet.Parser ( src/Data/Spreadsheet/Parser.hs,
dist/build/Data/Spreadsheet/Parser.o )
[3 of 3] Compiling Data.Spreadsheet ( src/Data/Spreadsheet.hs,
dist/build/Data/Spreadsheet.o )
Registering spreadsheet-0.1.1...
Installing library in /Users/user/.cabal/lib/spreadsheet-0.1.1/ghc-6.12.3
Registering spreadsheet-0.1.1...

Compilation finished at Fri Jun 17 02:30:05
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple CSV parser?

2011-06-16 Thread Henning Thielemann


On Thu, 16 Jun 2011, Felipe Almeida Lessa wrote:


[1] http://hackage.haskell.org/package/bytestring-csv
[2] http://hackage.haskell.org/package/csv-enumerator
[3] http://hackage.haskell.org/package/spreadsheet
[4] http://hackage.haskell.org/package/csv
[5] http://hackage.haskell.org/package/ssv


I have updated
  http://www.haskell.org/haskellwiki/Spreadsheet


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


[Haskell-cafe] Can one drop GHC 7.0.4 into the Haskell Platform or does the platform need to be updated?

2011-06-16 Thread KC
-- 
--
Regards,
KC

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


Re: [Haskell-cafe] Data Type Inheritance ala OO - Inheritence -- howto best in Haskell ?

2011-06-16 Thread Evan Laforge
I've done something perhaps similar in that I have a couple of signal
types, backed by (X, Y) vectors with Y values of different types, but
the same X type.  So they can share a fair amount of implementation
that depends only on X.  Still more could be shared if I could know a
zero value for each Y, so I wrote a SignalBase module:

class (Eq y) = Y y where
zero_y :: y
-- anything else that lets you share code

class (Storable.Storable (X, y), Y y) = Signal y

type SigVec y = V.Vector (X, y)

Now the SignalBase functions take '(Signal y) = SigVec y'.  The
specific signals contain a SigVec, and the functions whose
implementations can be shared are just one line:

at :: X - Signal y - Y
at x sig = SignalBase.at x (sig_vec sig)

The 'y' parameter to Signal is unrelated, I use it for a phantom type
to distinguish between signals of the same implementation but
different logical meaning, but 'at' applies to all of them.

On Thu, Jun 16, 2011 at 2:16 PM, gutti philipp.guttenb...@gmx.net wrote:
 Hi David,

 thanks for the links. I had a lok at the OO-paper some time ago already,
 heard however that its quite unusual and rather tricky to do OO-style
 programming in Haskell. So I'm looking for suggestions how to tackle this
 problem in a functional way.

 Cheers Phil

 --
 View this message in context: 
 http://haskell.1045720.n5.nabble.com/Data-Type-Inheritance-ala-OO-Inheritence-howto-best-in-Haskell-tp4494800p4496726.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

 ___
 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] Haskell: The Craft of Functional Programming 3rd ed is out.

2011-06-16 Thread KC
http://www.haskellcraft.com/craft3e/Home.html

-- 
--
Regards,
KC

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


Re: [Haskell-cafe] ANNOUNCE: doctest-0.3.0

2011-06-16 Thread Luke Palmer
On Thu, Jun 16, 2011 at 12:22 PM, Simon Hengel simon.hen...@wiktory.orgwrote:

 I just uploaded a new version of doctest[1] to Hackage.


Sweet!


 I think using all lower-case package names is a good thing.


I'm just curious -- why?

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


Re: [Haskell-cafe] ANNOUNCE: doctest-0.3.0

2011-06-16 Thread Ivan Lazar Miljenovic
On 17 June 2011 14:36, Luke Palmer lrpal...@gmail.com wrote:
 On Thu, Jun 16, 2011 at 12:22 PM, Simon Hengel simon.hen...@wiktory.org
 wrote:

 I just uploaded a new version of doctest[1] to Hackage.

 Sweet!


 I think using all lower-case package names is a good thing.

 I'm just curious -- why?

One reason: if that's the convention, then you don't have the problem
of how do I list that package in my .cabal file, is it doctest,
Doctest or DocTest?

Also, some distro package managers prefer lowercase package names.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com

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


[Haskell-cafe] type signature of parsec functions and how to warp them up.

2011-06-16 Thread 吴兴博
I have some different parsers of Parsec to use in a project, and I
want to make a warp function to make the testing easy.

here is some of my body of parser : they all has type of parsecT ***
  stringSet :: ParsecT  String  u  Identity  [String]
  intSet  ::  ParsecT  String  u  Identity  [Integer]
  tupleSet ::  ParsecT  String  u  Identity  [(String, String)]

all of the returned type are instance of 'Show'.

then I write these warp function:
--
import System.IO
import Data.Functor.Identity (Identity)
import Text.Parsec.Prim (ParsecT, runParserT, parse, Stream)
runIOParse :: (Show a) = ParsecT String u Identity a - String - IO ()
runIOParse pa fn =
  do
inh - openFile fn ReadMode
outh - openFile (fn ++ .parseout) WriteMode
instr - hGetContents inh
let result = show $ parse pa fn instr
hPutStr outh result
hClose inh
hClose outh
---
 :l RunParse.hs
---
RunParse.hs:12:31:
Could not deduce (u ~ ())
from the context (Show a)
  bound by the type signature for
 runIOParse :: Show a =
   ParsecT String u Identity a - String - IO ()
  at RunParse.hs:(7,1)-(15,15)
  `u' is a rigid type variable bound by
  the type signature for
runIOParse :: Show a =
  ParsecT String u Identity a - String - IO ()
  at RunParse.hs:7:1
Expected type: Text.Parsec.Prim.Parsec String () a
  Actual type: ParsecT String u Identity a
In the first argument of `parse', namely `pa'
In the second argument of `($)', namely `parse pa fn instr'
Failed, modules loaded: none.
---

then I modify the type signature of 'runIOParse':
runIOParse :: (Show a) = ParsecT String () Identity a - String - IO ()
then load again
 :l RunParse.hs
---
RunParse.hs:12:25:
Could not deduce (Stream String Identity t0)
  arising from a use of `parse'
from the context (Show a)
  bound by the type signature for
 runIOParse :: Show a =
   ParsecT String () Identity a - String - IO ()
  at RunParse.hs:(7,1)-(15,15)
Possible fix:
  add (Stream String Identity t0) to the context of
the type signature for
  runIOParse :: Show a =
ParsecT String () Identity a - String - IO ()
  or add an instance declaration for (Stream String Identity t0)
In the second argument of `($)', namely `parse pa fn instr'
In the expression: show $ parse pa fn instr
In an equation for `result': result = show $ parse pa fn instr
Failed, modules loaded: none.
---

I also tried some 'possible fix' in the information, but it still
failed to pass the compiler.

Main Question:
  How can I warp a parsec function interface for do the IO test
with different 'ParsecT String u Identity a'?

-- 

吴兴博  Wu Xingbo

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


Re: [Haskell-cafe] type signature of parsec functions and how to warp them up.

2011-06-16 Thread 吴兴博
It seems weird:

first ghci failed to load this file:
file: RunParse.hs
---
module RunParse where
import System.IO
import Data.Functor.Identity (Identity)
import Text.Parsec first, no this
line---what about this line ???
import Text.Parsec.Prim (Parsec, parse, Stream)

runIOParse :: (Show a) = Parsec String () a - String - IO ()
runIOParse pa fn =
  do
inh - openFile fn ReadMode
outh - openFile (fn ++ .parseout) WriteMode
instr - hGetContents inh
let result = case parse pa fn instr of
   Right rs - show rs
   Left err - error
hPutStr outh result
hClose inh
hClose outh
--

ghci tell me:
-

RunParse.hs:13:23:
Could not deduce (Stream String Identity t0)
  arising from a use of `parse'
from the context (Show a)
  bound by the type signature for
 runIOParse :: Show a = Parsec String () a - String - IO ()
  at Sim/Std/RunParse.hs:(8,1)-(18,15)
Possible fix:
  add (Stream String Identity t0) to the context of
the type signature for
  runIOParse :: Show a = Parsec String () a - String - IO ()
  or add an instance declaration for (Stream String Identity t0)
In the expression: parse pa fn instr
In the expression:
  case parse pa fn instr of {
Right rs - show rs
Left err - error }
In an equation for `result':
result
  = case parse pa fn instr of {
  Right rs - show rs
  Left err - error }
--



I just add one line of import and ghci:

import Text.Parsec

then ghci loaded it succeed!

It seems I didn't uses any functions from this import.

what goes wrong?


2011/6/17 吴兴博 wux...@gmail.com:
 I have some different parsers of Parsec to use in a project, and I
 want to make a warp function to make the testing easy.




-- 

吴兴博  Wu Xingbo

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