Re: [Haskell-cafe] ghc 7.2.1 and super simple DPH

2011-10-02 Thread Erik de Castro Lopo
Erik de Castro Lopo wrote: > The code you posted had some wrapping issues and was missing an > import. I should have also mentioned how I figured out what the missing import was. Firstly, I tried hoogle [0] but couldn't find it. I then realised that it must be part of DPH and that I had a copy o

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread sdiyazg
Quoting Richard O'Keefe : On 3/10/2011, at 7:15 AM, Du Xi wrote: I guess this is what I want, thank you all. Although I still wonder why something so simple in C++ is actually more verbose and requires less known features in Haskell...What was the design intent to disallow simple ove

Re: [Haskell-cafe] ghc 7.2.1 and super simple DPH

2011-10-02 Thread Erik de Castro Lopo
Peter Braam wrote: > Hi - > > I'm trying to compile DotP.hs from > http://www.haskell.org/haskellwiki/GHC/Data_Parallel_Haskell#A_simple_example > (see > below) > > The compiler complains and says (twice in fact): > > DotP.hs:17:33: Not in scope: `fromPArrayP' > > Could someone help me out ple

[Haskell-cafe] How to compile this example code?

2011-10-02 Thread Magicloud Magiclouds
Hi, I am learning to use data-flags, and got this example code: import Data.Flags newtype MyFlags = MyFlags CInt deriving (Eq, Flags) #{enum MyFlags, MyFlags , myFlag1 = C_FLAG1 , myFlag2 = C_FLAG2 , myFlag3 = C_FLAG3 } I modified it trying to compile it. Well, I got illegal syntax at "#{e

Re: [Haskell-cafe] Problem on using template haskell.

2011-10-02 Thread Magicloud Magiclouds
On Mon, Oct 3, 2011 at 1:44 PM, Magicloud Magiclouds wrote: > Hi, >  I am trying to use data-flags library. And failed on compiling the test code. > >  The code is like following, and the compiling error is > "test.hs:4:24: parse error on input `{'" > {-# LANGUAGE TemplateHaskell #-} > import Data

[Haskell-cafe] Problem on using template haskell.

2011-10-02 Thread Magicloud Magiclouds
Hi, I am trying to use data-flags library. And failed on compiling the test code. The code is like following, and the compiling error is "test.hs:4:24: parse error on input `{'" {-# LANGUAGE TemplateHaskell #-} import Data.Flags.TH $(bitmaskWrapper "Severity" ''Int [] False [ ("NotClassified

[Haskell-cafe] ghc 7.2.1 and super simple DPH

2011-10-02 Thread Peter Braam
Hi - I'm trying to compile DotP.hs from http://www.haskell.org/haskellwiki/GHC/Data_Parallel_Haskell#A_simple_example (see below) The compiler complains and says (twice in fact): DotP.hs:17:33: Not in scope: `fromPArrayP' Could someone help me out please? Thanks a lot! Peter {-# LANGUAGE Pa

Re: [Haskell-cafe] Parameters and patterns

2011-10-02 Thread Richard O'Keefe
On 2/10/2011, at 3:27 AM, José Romildo Malaquias wrote: > Hello. > > When studing programming languages I have learned that parameter is a > variable (name) that appears in a function definition and denotes the > value to which the function is applied when the function is called. Who told you t

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Richard O'Keefe
On 3/10/2011, at 7:15 AM, Du Xi wrote: > > I guess this is what I want, thank you all. Although I still wonder why > something so simple in C++ is actually more verbose and requires less known > features in Haskell...What was the design intent to disallow simple > overloading? It's not "SIMPL

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Yves Parès
Yes, do you have a Python background? Because I've often see misunderstanding about the utility of tuples with persons who were used to Python, because Python tutorials usually induce * BAD* practices in this respect (considering tuples and lists equivalent, for instance). Add to this the dynamic t

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Scott Turner
On 2011-10-02 14:15, Du Xi wrote: > I guess this is what I want, thank you all. Although I still wonder why > something so simple in C++ is actually more verbose and requires less > known features in Haskell...What was the design intent to disallow > simple overloading? "Simple overloading" is kno

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Andrew Coppin
On 02/10/2011 07:15 PM, Du Xi wrote: > I guess this is what I want, thank you all. Although I still wonder why > something so simple in C++ is actually more verbose and requires less > known features in Haskell...What was the design intent to disallow > simple overloading? In C++, the code is

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Tom Murphy
Assuming that z :: Int, you can declare an algebraic datatype data TwoOrThree a b = Three (a, b, Int) | Two (a, b) deriving(Show, Eq) -- so you can experiment And then define expand as expand :: TwoOrThree a b -> (a, b, Int) expand (Three tuple) = tuple expand (Two (a, b))

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Antoine Latter
On Sun, Oct 2, 2011 at 2:17 PM, wrote: > Finally I got what I meant: > > > class ExpandTuple t where >        type Result t >        expand :: t->Result t > > instance (Integral a)=>ExpandTuple (a,a) where >        type Result (a,a) = (a,a,a) >        expand (x,y) = (x,y,1) > > instance (Integral

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Brandon Allbery
On Sun, Oct 2, 2011 at 15:17, wrote: > But it's so verbose (even more so than similar C++ template code I guess), > introduces an additional name (the typeclass) into the current scope, and > requires 2 extensions: TypeFamilies and FlexibleInstances.Is there a cleaner > way to do this? Not for

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Felipe Almeida Lessa
On Sun, Oct 2, 2011 at 4:26 PM, Edward Z. Yang wrote: > What are you actually trying to do?  This seems like a rather > unusual function. If you're new to the language, most likely you're doing something wrong if you need this kind of function. =) -- Felipe. __

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Edward Z. Yang
What are you actually trying to do? This seems like a rather unusual function. Edward Excerpts from sdiyazg's message of Sun Oct 02 15:17:07 -0400 2011: > Finally I got what I meant: > > > class ExpandTuple t where > type Result t > expand :: t->Result t > > instance (Integral a)=>Exp

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread sdiyazg
Finally I got what I meant: class ExpandTuple t where type Result t expand :: t->Result t instance (Integral a)=>ExpandTuple (a,a) where type Result (a,a) = (a,a,a) expand (x,y) = (x,y,1) instance (Integral a)=>ExpandTuple (a,a,a) where type Result (a,a,

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Du Xi
Quoting Victor Gorokgov : 02.10.2011 19:55, David Barbour пишет: Use TypeFamilies. {-# LANGUAGE TypeFamilies #} ... type family FType a :: * type instance FType Char = Float type instance FType Double = Int class ExampleClass a where f :: a -> FType a Better to include type in class. cla

Re: [Haskell-cafe] Installing hledger-web

2011-10-02 Thread Arnaud Bailly
No problem ! BTW, have you ever thought of coupling hledger with git for saving a ledger ? There is ongoing work to provide a "native" git interface. Regards Arnaud On Sun, Oct 2, 2011 at 6:32 PM, Simon Michael wrote: > I have reopened > http://code.google.com/p/**hledger/issues/detail?id=63

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Victor Gorokgov
02.10.2011 19:55, David Barbour пишет: Use TypeFamilies. {-# LANGUAGE TypeFamilies #} ... type family FType a :: * type instance FType Char = Float type instance FType Double = Int class ExampleClass a where f :: a -> FType a Better to include type in class. class ExampleClass a where type

Re: [Haskell-cafe] Installing hledger-web

2011-10-02 Thread Simon Michael
I have reopened http://code.google.com/p/hledger/issues/detail?id=63 . Sorry for the breakage. I thought I had this working once but I'm not sure how! -Simon On 10/1/11 10:36 PM, Arnaud Bailly wrote: Thanks Simon. Unfortunately, I got the same error. On Sun, Oct 2, 2011 at 2:50 AM, Simon Mich

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread David Barbour
On Sun, Oct 2, 2011 at 8:45 AM, Du Xi wrote: > Then again , in typeclass definition how can I express the type "a->b" > where "a" is the type parameter of the class and "b" is a type deduced from > the rules defined in each instance of the class, which varies on a > per-instance basis? e.g. > > i

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Du Xi
Quoting Andrew Coppin : On 02/10/2011 02:04 PM, Du Xi wrote: --It still didn't compile. I think the reason is that the following is disallowed: f::a->b f x = x The type "a -> b" doesn't mean what you think it does. It does /not/ mean that f is allowed to return any type it wants to. It mea

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread David Barbour
On Sun, Oct 2, 2011 at 6:04 AM, Du Xi wrote: > --Is it possible to get around this and write the "expand" function? Of > course, x and y may be of different types > Not as written, but try HList. http://hackage.haskell.org/package/HList ___ Haskell-Caf

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Andrew Coppin
On 02/10/2011 02:04 PM, Du Xi wrote: --It still didn't compile. I think the reason is that the following is disallowed: f::a->b f x = x The type "a -> b" doesn't mean what you think it does. It does /not/ mean that f is allowed to return any type it wants to. It means that f must be prepair

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Yves Parès
2-tuple and 3-tuple *are not the same type*. So to do this you must use typeclasses. Plus you have to deal with the type parameters class To3Tuple a where expand :: a -> (Int, Int, Int) instance To3Tuple (Int, Int, Int) where expand = id instance To3Tuple (Int, Int) where expand (x,y) =

[Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Du Xi
--I tried to write such polymorphic function: expand (x,y,z) = (x,y,z) expand (x,y) = (x,y,1) --And it didn't compile. Then I added a type signature: expand::a->b expand (x,y,z) = (x,y,z) expand (x,y) = (x,y,1) --It still didn't compile. I think the reason is that the following is disallowed

Re: [Haskell-cafe] ANN: Peggy 0.2.1

2011-10-02 Thread Issac Trotts
I love the concise syntax and useful examples. Thank you! On Wed, Sep 28, 2011 at 12:53 PM, Hideyuki Tanaka wrote: > Hello, all. > > I have released 'Peggy' a new parser generator . > It is based on Parsing Expression Grammer (PEG) [1], > and generates efficient packrat parsers. > > # Where to ge

Re: [Haskell-cafe] Really Simple explanation of Continuations Needed

2011-10-02 Thread Heinrich Apfelmus
Ozgur Akgun wrote: On 1 October 2011 11:55, Yves Parès wrote: BTW Heinrich, the evalState (sequence . repeat . State $ \s -> (s,s+1)) 0 at the end doesn't work anymore. It should be replaced by : evalState (sequence . repeat . StateT $ \s -> Identity (s,s+1)) 0 Or equivalently: evalState

Re: [Haskell-cafe] Static linking for machines that don't have Haskell

2011-10-02 Thread Ketil Malde
Roshan James writes: > This gives me several warnings of the form: > */usr/lib/haskell-packages/ghc6/lib/network-2.2.1.7/ghc-6.12.3/libHSnetwork-2.2.1.7.a(BSD.o): > In function `sw4B_info':* > *(.text+0x584c): warning: Using 'getservbyport' in statically linked > applications requires at runtime