Re: [Haskell-cafe] How to understand the 'forall' ?

2009-09-17 Thread Ryan Ingram
On Wed, Sep 16, 2009 at 11:58 AM, Cristiano Paris fr...@theshire.orgwrote: On Wed, Sep 16, 2009 at 7:12 PM, Ryan Ingram ryani.s...@gmail.com wrote: Here's the difference between these two types: test1 :: forall a. a - Int -- The caller of test1 determines the type for test1 test2 ::

Re: [Haskell-cafe] Can't install Haskell Platform (Ubuntu 9.02)

2009-09-17 Thread Gregory Propf
Yes that worked. --- On Wed, 9/16/09, Paulo Tanimoto tanim...@arizona.edu wrote: From: Paulo Tanimoto tanim...@arizona.edu Subject: Re: [Haskell-cafe] Can't install Haskell Platform (Ubuntu 9.02) To: Gregory Propf gregorypr...@yahoo.com Cc: Haskell-Cafe haskell-cafe@haskell.org Date: Wednesday,

[Haskell-cafe] Trouble installing leksah

2009-09-17 Thread Gregory Propf
I now have the Haskell platform install problem solved but I'm now trying to get the leksah IDE installed and I'm getting this. runhaskell Setup configure Configuring leksah-0.6.1... Setup: At least the following dependencies are missing: glib =0.10, gtk =0.10, gtksourceview2 =0.10.0 I am aware

Re: [Haskell-cafe] Trouble installing leksah

2009-09-17 Thread david48
On Thu, Sep 17, 2009 at 9:01 AM, Gregory Propf gregorypr...@yahoo.com wrote: I now have the Haskell platform install problem solved but I'm now trying to get the leksah IDE installed and I'm getting this. runhaskell Setup configure Configuring leksah-0.6.1... Setup: At least the following

[Haskell-cafe] Where can I find a non-fee-based version of Hudak's paper, Conception, evolution, and application of functional programming languages?

2009-09-17 Thread Benjamin L . Russell
Does anybody know where I can find a non-fee-based version of Paul Hudak's paper, Conception, evolution, and application of functional programming languages [1]? There used to be a version that did not require an ACM account available at

[Haskell-cafe] Suggested additions to System.FilePath.Posix/Windows

2009-09-17 Thread Marcus D. Gabriel
Hello Neil I used System.FilePath.Posix quite extensively recently, and I thank you for the package filepath. There were however two words that I needed which I could not construct from those in System.FilePath.Posix. They are maybe of interest to you and others. I submit these two words to

[Haskell-cafe] Re: Question about haskell.cs.yale.edu/

2009-09-17 Thread Magnus Therning
Today I received the request below. At first the URL confused me, but apparently www.haskell.org is known under two names :-) The request should probably be handled by someone involved in ICFP. /M On Wed, Sep 16, 2009 at 11:53 PM, Peter Green peter.gr...@frixo.com wrote: Hi, I was wondering

[Haskell-cafe] ANNOUNCE: graphviz-2999.5.1.0

2009-09-17 Thread Ivan Lazar Miljenovic
I'm pleased to announce version 2999.5.1.0 [1] of the graphviz library, which provides bindings to the GraphViz [2] suite of tools for drawing graphs. [1] http://hackage.haskell.org/package/graphviz-2999.5.1.0 [2] http://www.graphviz.org/ This is mainly a bug-fix release; as such, there is no

Re: [Haskell-cafe] Trouble installing leksah

2009-09-17 Thread Gregory Propf
There's no such named package in Hackage though.  That was the first thing I looked for.  All Hackage has with the string gtk2hs is this stuff gtk2hs-cast-glade library: A type class for cast functions of Gtk2hs: glade packagegtk2hs-cast-glib library: A type class for cast functions of Gtk2hs:

Re: [Haskell-cafe] Trouble installing leksah

2009-09-17 Thread Daniel Fischer
Am Donnerstag 17 September 2009 12:35:19 schrieb Gregory Propf: There's no such named package in Hackage though.  That was the first thing I looked for.  All Hackage has with the string gtk2hs is this stuff AFAIK, gtk2hs is not yet cabalized and not on Hackage, look at

[Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Andy Gimblett
Hi all. This email is in literate Haskell; you should be able to load it into ghci and verify what I'm saying (nb: it won't compile without alteration: see below). I'm trying to do something which may anyway be stupid / not the best approach to what I'm trying to achieve; however, it's not

Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread José Pedro Magalhães
Hey Andy, On Thu, Sep 17, 2009 at 15:40, Andy Gimblett hask...@gimbo.org.uk wrote: Now, some of those algebraic data type types happen to be enumerations; in this case, my idea is to list the constructors, with the rule that each constructor's position in the list is the Int which gets

Re: [Haskell-cafe] How to understand the 'forall' ?

2009-09-17 Thread Cristiano Paris
On Thu, Sep 17, 2009 at 8:36 AM, Ryan Ingram ryani.s...@gmail.com wrote: ... Explicitly: Haskell: test1 :: forall a. a - Int test1 _ = 1 test2 :: (forall a. a) - Int test2 x = x explicitly in System F: test1 = /\a \(x :: a). 1 test2 = \(x :: forall a. a). x @Int /\ is type-level

Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Daniel Fischer
Am Donnerstag 17 September 2009 15:56:03 schrieb José Pedro Magalhães: Hey Andy, On Thu, Sep 17, 2009 at 15:40, Andy Gimblett hask...@gimbo.org.uk wrote: Now, some of those algebraic data type types happen to be enumerations; in this case, my idea is to list the constructors, with the

Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread José Pedro Magalhães
Hello, On Thu, Sep 17, 2009 at 16:05, Daniel Fischer daniel.is.fisc...@web.dewrote: Am Donnerstag 17 September 2009 15:56:03 schrieb José Pedro Magalhães: Hey Andy, On Thu, Sep 17, 2009 at 15:40, Andy Gimblett hask...@gimbo.org.uk wrote: Now, some of those algebraic data type types

Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Andy Gimblett
On 17 Sep 2009, at 15:21, José Pedro Magalhães wrote: E.g. here's a type Bar with three constructors: data Bar = X | Y | Z deriving (Show) instance Enumerated Bar where constructors = [X, Y, Z] (This is certainly ugly. Any suggestions?) |constructors| is expressible in

Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Daniel Fischer
Am Donnerstag 17 September 2009 16:30:14 schrieb Andy Gimblett: On 17 Sep 2009, at 15:21, José Pedro Magalhães wrote: E.g. here's a type Bar with three constructors: data Bar = X | Y | Z deriving (Show) instance Enumerated Bar where constructors = [X, Y, Z] (This is

[Haskell-cafe] Re: [Haskell-beginners] map question

2009-09-17 Thread Gregory Propf
Remember that there is asymmetry between (+) and (-).  The former has the commutative property and the latter does not so: (+) 3 4 = 7 and (+) 4 3 = 7 but (-) 3 4 = -1 and (-) 4 3 = 1 --- On Thu, 9/17/09, Tom Doris tomdo...@gmail.com wrote: From: Tom Doris tomdo...@gmail.com Subject:

[Haskell-cafe] Re: Where can I find a non-fee-based version of Hudak's paper, Conception, evolution, and application of functional programming languages?

2009-09-17 Thread jean legrand
Does anybody know where I can find a non-fee-based version of Paul Hudak's paper, Conception, evolution, and application of functional programming languages [1]? There used to be a version that did not seems you can get a djvu copy here http://lib.org.by/info/Cs_Computer

Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Daniel Fischer
Am Donnerstag 17 September 2009 15:40:10 schrieb Andy Gimblett: instance (Enumerated a) = Target a where convert n | n `elem` [0..len-1] = Just $ constructors !! n | otherwise = Nothing where len = length constructors Yes, the second appearance of

Re: [Haskell-cafe] Where can I find a non-fee-based version of Hudak's paper, Conception, evolution, and application of functional programming languages?

2009-09-17 Thread John Melesky
On 2009-09-17, at 1:41 AM, Benjamin L.Russell wrote: Does anybody know where I can find a non-fee-based version of Paul Hudak's paper, Conception, evolution, and application of functional programming languages [1]? When in doubt, check citeseer.

Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Andy Gimblett
On 17 Sep 2009, at 16:50, Daniel Fischer wrote: Yes, the second appearance of 'constructors' is at an unspecified type. instance (Enumerated a) = Target a where convert n | n 0 = Nothing | otherwise = case drop n constructors of (x:_) - Just x

Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-09-17 Thread Job Vranish
(-) happens to be the only prefix operator in haskell, it also an infix operator. so: 4 - 2 2 -3 -3 ((-) 5) 3 -- note that in this case (-) is treated like any regular function so 5 is the first parameter 2 (5 - ) 3 2 (-5 ) -5 (flip (-) 5) 3 -2 It's a little wart brought about by the

Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-09-17 Thread Deniz Dogan
2009/9/17 Joost Kremers joostkrem...@fastmail.fm Hi all, I've just started learning Haskell and while experimenting with map a bit, I ran into something I don't understand. The following commands do what I'd expect: Prelude map (+ 1) [1,2,3,4] [2,3,4,5] Prelude map (* 2) [1,2,3,4]

Re: [Haskell-cafe] How to understand the 'forall' ?

2009-09-17 Thread Ryan Ingram
On Thu, Sep 17, 2009 at 6:59 AM, Cristiano Paris fr...@theshire.org wrote: On Thu, Sep 17, 2009 at 8:36 AM, Ryan Ingram ryani.s...@gmail.com wrote: ... Explicitly: Haskell: test1 :: forall a. a - Int test1 _ = 1 test2 :: (forall a. a) - Int test2 x = x explicitly in System F:

Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Daniel Fischer
Am Donnerstag 17 September 2009 18:01:36 schrieb Andy Gimblett: On 17 Sep 2009, at 16:50, Daniel Fischer wrote: Yes, the second appearance of 'constructors' is at an unspecified type. instance (Enumerated a) = Target a where convert n | n 0 = Nothing |

Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Ryan Ingram
Here's a way that works more closely to your original version: instance Enumerated a = Target a where convert n | n = 0 n numConstrs = Just (constrs !! n) | otherwise = Nothing where constrs = constructors numConstrs = length constrs Alternatively: instance

Re: [Haskell-cafe] weak pointers and memoization (was Re: memoization)

2009-09-17 Thread Job Vranish
What are you trying to use this for? It seems to me that for memo tables you almost never have references to they keys outside the lookup table since the keys are usually computed right at the last minute, and then discarded (otherwise it might be easier to just cache stuff outside the function).

[Haskell-cafe] Peano axioms

2009-09-17 Thread pat browne
Hi, Below are two attempts to define Peano arithmetic in Haskell. The first attempt, Peano1, consists of just a signature in the class with the axioms in the instance. In the second attempt, Peano2, I am trying to move the axioms into the class. The reason is, I want to put as much specification

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-17 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 11:31 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: ... Yeah, you do *not* want the whole file to be read here, except above for testing purposes. That's not true. Sometimes I want to, sometimes don't. But I want to use the same code for reading files and exploit

Re: [Haskell-cafe] Peano axioms

2009-09-17 Thread Job Vranish
The problem is that you are using 'suc' as if it is a constructor: ((suc m) `eq` (suc n) = m `eq` n) You'll have to change it to something else, and it will probably require adding an unpacking function to your class and it will probably be messy. I'd suggest you make use of the Eq typeclass and

[Haskell-cafe] Composition, delegation and interfaces -- a 20K ft critique of Noop

2009-09-17 Thread Greg Meredith
Dear Programmers, Someone just asked me to give my opinion on Noop's composition proposalhttp://code.google.com/p/noop/wiki/ProposalForComposition. It reminds me a little bit of Selfhttp://en.wikipedia.org/wiki/Self_%28programming_language%29which found its way into JavaScript. It also reminds me

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-17 Thread Daniel Fischer
Am Donnerstag 17 September 2009 21:07:28 schrieb Cristiano Paris: On Tue, Sep 15, 2009 at 11:31 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: ... Yeah, you do *not* want the whole file to be read here, except above for testing purposes. That's not true. Sometimes I want to,

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-17 Thread Cristiano Paris
On Thu, Sep 17, 2009 at 10:01 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: ... readBit fn = do    txt - readFile fn    let (l,_:bdy) = span (/= '\n') txt    return $ Bit (read l) bdy ? With main = do    args - getArgs    let n = case args of                (a:_) - read a      

Re: [Haskell-cafe] algebra/grammar/language for expressing time intervals

2009-09-17 Thread Magnus Therning
Iain Alexander wrote: You might want to take a look at RFC 2445 Internet Calendaring and Scheduling Core Object Specification Section 4.8.5.4 Recurrence Rule Another source of inspiration might be the syntax used in remind[1]. /M [1]: http://www.roaringpenguin.com/products/remind -- Magnus

Re: [Haskell-cafe] Peano axioms

2009-09-17 Thread John D. Ramsdell
I don't understand your goal. Isn't Peano arithmetic summarized in Haskell as: data Peano = Zero | Succ Peano deriving Eq This corresponds to a first-order logic over a signature that has equality, a constant symbol 0, and a one-place successor function symbol S. Function symbols such as and

[Haskell-cafe] ANN: Unification in a Commutative Monoid (cmu 1.1) and a new release of Abelian group unification and matching (agum 2.2)

2009-09-17 Thread John D. Ramsdell
Package cmu 1.1 provides unification in a commutative monoid, also know as ACU-unification. The core computation finds the minimal non-zero solutions to homogeneous linear Diaphantine equations. The linear equation solver has been place in a separate module so it can be used for other

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-17 Thread Daniel Fischer
Am Donnerstag 17 September 2009 22:20:55 schrieb Cristiano Paris: On Thu, Sep 17, 2009 at 10:01 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: ... readBit fn = do    txt - readFile fn    let (l,_:bdy) = span (/= '\n') txt    return $ Bit (read l) bdy ? With main = do

[Haskell-cafe] help with FFI

2009-09-17 Thread José Prous
Hello Lets say I have a library in C with a header like this: #include stdio.h /*really big structure*/ typedef struct { int *a; int *b; /*lots of stuff ... */ int *z; } foo; /*this function allocate memory and fill the structure, reading from a file*/ int create_foo(foo *f,FILE *file,int

Re: [Haskell-cafe] weak pointers and memoization (was Re: memoization)

2009-09-17 Thread Rodney Price
In my case, the results of each computation are used to generate a node in a graph structure (dag). The key, oddly, is a hash of a two-tuple that gets stored in the data structure after the computation of the node finishes. If I don't memoize the function to build a node, the cost of generating

[Haskell-cafe] Re: help with FFI

2009-09-17 Thread Maurí­cio CA
typedef struct { int *a; int *b; /*lots of stuff ... */ int *z; } foo; int create_foo(foo *f,FILE *file,int x,int y); int use_foo(foo *f,int w); int destroy_foo(foo *f); newtype Foo = Foo () foreign import ccall static foo.h create_foo c_create_foo :: Ptr (Foo) - Ptr (CFile) - CInt - CInt - IO

[Haskell-cafe] About the parse error (possibly incorrect indentation)

2009-09-17 Thread xu zhang
Hi, I am trying to get the function showMinProp to return String, but I always get an error of parse error (possibly incorrect indentation) Who can help with this? any idea? Thank u in advance! data Prop = Var String | Negation Prop | BinOp Op Prop Prop data Op = And | Or | Implies | Equiv

Re: [Haskell-cafe] About the parse error (possibly incorrect indentation)

2009-09-17 Thread Daniel Fischer
Am Freitag 18 September 2009 02:17:22 schrieb xu zhang: showMinProp :: Int - Prop - String showMinProp preNo (BinOp op p q) =        case op of          And - let a = 4          Or  - let a = 3          Implies - let a = 2          Equiv   - let a = 1        if (a preNo)          then

Re: [Haskell-cafe] How to understand the 'forall' ?

2009-09-17 Thread wren ng thornton
Cristiano Paris wrote: On Wed, Sep 16, 2009 at 7:12 PM, Ryan Ingram ryani.s...@gmail.com wrote: Here's the difference between these two types: test1 :: forall a. a - Int -- The caller of test1 determines the type for test1 test2 :: (forall a. a) - Int -- The internals of test2 determines what

[Haskell-cafe] ∀ lexing in ghc and ghci

2009-09-17 Thread Sean McLaughlin
Hi, I'm getting different behavior in ghci and ghc with the identifier ∀. In ghc I need to wrap it with parens, as in (∀) :: Var - Base - Formula - Formula (∀) = All In ghci, I get an error this way Formula.lhs:112:2: Invalid type signature In ghci I can do ∀ :: Var - Base -

Re: [Haskell-cafe] ∀ lexing in ghc and ghci

2009-09-17 Thread Daniel Fischer
Am Freitag 18 September 2009 03:31:13 schrieb Sean McLaughlin: Hi, I'm getting different behavior in ghci and ghc with the identifier ∀. In ghc I need to wrap it with parens, as in (∀) :: Var - Base - Formula - Formula (∀) = All In ghci, I get an error this way Formula.lhs:112:2:

Re: [Haskell-cafe] ∀ lexing in ghc and ghci

2009-09-17 Thread Sean McLaughlin
Hi Daniel, Would you try putting that in a file and loading it in ghci? Your example also works for me. Prelude let (∀) = 5 Prelude (∀) 5 Sean On Thu, Sep 17, 2009 at 9:41 PM, Daniel Fischer daniel.is.fisc...@web.dewrote: Am Freitag 18 September 2009 03:31:13 schrieb Sean McLaughlin: Hi,

Re: [Haskell-cafe] ∀ lexing in ghc and ghci

2009-09-17 Thread Daniel Fischer
Am Freitag 18 September 2009 03:51:40 schrieb Sean McLaughlin: Hi Daniel, Would you try putting that in a file and loading it in ghci? Your example also works for me. Prelude let (∀) = 5 Prelude (∀) 5 Sean Sure: da...@linux-mkk1:~/Haskell/CafeTesting cat Forall.hs module Forall where

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-17 Thread Ryan Ingram
I am confused about why this thread is talking about unsafePerformIO at all. It seems like everything you all want to do can be accomplished with the much less evil unsafeInterleaveIO instead. (Which is still a bit evil; but it's the difference between stealing cookies from the cookie jar and

Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-09-17 Thread Gregory Propf
Heh, perhaps we should petition to have a new computer key and symbol added to the world's way of writing maths, something like maybe a downward angled slash to mean prefix (-) :) --- On Thu, 9/17/09, Job Vranish jvran...@gmail.com wrote: From: Job Vranish jvran...@gmail.com Subject: Re:

[Haskell-cafe] Re: Where can I find a non-fee-based version of Hudak's paper, Conception, evolution, and application of functional programming languages?

2009-09-17 Thread Benjamin L . Russell
On Thu, 17 Sep 2009 08:55:19 -0700, John Melesky l...@phaedrusdeinus.org wrote: On 2009-09-17, at 1:41 AM, Benjamin L.Russell wrote: Does anybody know where I can find a non-fee-based version of Paul Hudak's paper, Conception, evolution, and application of functional programming languages [1]?

Re: [Haskell-cafe] ∀ lexing in ghc and ghci

2009-09-17 Thread Sean McLaughlin
Weird. OK, thanks a lot! I'm switching to ¥ until I get this figured out. Sean On Thu, Sep 17, 2009 at 10:00 PM, Daniel Fischer daniel.is.fisc...@web.dewrote: Am Freitag 18 September 2009 03:51:40 schrieb Sean McLaughlin: Hi Daniel, Would you try putting that in a file and loading it

[Haskell-cafe] code-build-test cycle

2009-09-17 Thread Michael Mossey
I'm working on a GUI application in qtHaskell, and I have a bit of a bind. Using ghci, it launches quickly but runs slowly. On the other hand, compiling (mainly linking) takes a while---several minutes. The truth is that I can compile it much faster if I selectively import the needed modules,

Re: [Haskell-cafe] ∀ lexing in ghc and ghci

2009-09-17 Thread Daniel Fischer
Am Friday 18 September 2009 04:41:13 schrieben Sie: Weird. OK, thanks a lot! I'm switching to ¥ until I get this figured out. Sean What does your ghci say for Data.Char.isSymbol (toEnum 8704) ? ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-17 Thread Daniel Fischer
Am Freitag 18 September 2009 04:06:11 schrieb Ryan Ingram: I am confused about why this thread is talking about unsafePerformIO at all.  It seems like everything you all want to do can be accomplished with the much less evil unsafeInterleaveIO instead.  (Which is still a bit evil; but it's the

Re: [Haskell-cafe] code-build-test cycle

2009-09-17 Thread Daniel Fischer
Am Freitag 18 September 2009 04:42:32 schrieb Michael Mossey: I'm working on a GUI application in qtHaskell, and I have a bit of a bind. Using ghci, it launches quickly but runs slowly. On the other hand, compiling (mainly linking) takes a while---several minutes. The truth is Is the library

Re: [Haskell-cafe] About the parse error (possibly incorrect indentation)

2009-09-17 Thread Brandon S. Allbery KF8NH
On Sep 17, 2009, at 20:17 , xu zhang wrote: case op of And - let a = 4 Or - let a = 3 Implies - let a = 2 Equiv - let a = 1 let isn't an assignment command, it's a scoping command. That is, let a = 3 in ... is equivalent to something like {

Re: [Haskell-cafe] code-build-test cycle

2009-09-17 Thread Bulat Ziganshin
Hello Michael, Friday, September 18, 2009, 6:42:32 AM, you wrote: Now I'm wondering if Hugs is a faster interpreter. 2x slower, and incompatib;e with qtHaskell meaningful way without compilation. Any advice welcome. Maybe there is a way to speed up the interpretation. if compilation is