[Haskell-cafe] Linking against Sqlite3 on Windows problem

2012-07-09 Thread Eugene Dzhurinsky
Hi all!

I created simple application, which uses sqlite3 as it's datastore back-end. I
faced no problems when building and running it on Linux, but after I tried to
build it on Windows, I see weird linking error:

Linking dist\build\hnotes\hnotes.exe ...
C:\Documents and Settings\Admin\Application 
Data\cabal\sqlite-0.5.2.2\ghc-7.0.4/libHSsqlite-0.5.2.2.
a(sqlite3-local.o):sqlite3-local.c:(.text+0x21): undefined reference to 
`sqlite3_temp_directory'
C:\Documents and Settings\Admin\Application 
Data\cabal\sqlite-0.5.2.2\ghc-7.0.4/libHSsqlite-0.5.2.2.
a(sqlite3-local.o):sqlite3-local.c:(.text+0x40): undefined reference to 
`sqlite3_temp_directory'
collect2: v ld 1
cabal.EXE: Error: some packages failed to install:
hnotes-0.1 failed during the building phase. The exception was:
ExitFailure 1

What may be wrong there? I suspect that qalite3.dll has to be added to linking 
stage, 
but have no idea how to do that. Adding --extra-lib-dirs=path-to-sqlite-dll 
doesn't 
help either (perhaps because I need to update my cabal file somehow, to support 
this?).

Thank you for the help!

-- 
Eugene N Dzhurinsky


pgpQJzjGTBAjt.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] sample terms and interpreting program output from Tc Monad

2012-07-09 Thread Andres Löh
[Sorry, I forgot to reply to the list.]

Hi.

 I understand these to be Rank 0 terms:

 (\(x::Int) . x) (0 :: Int) :: (forall. Int) -- value

 (\(x::Int). x) :: (forall. Int - Int)

Yes.

 (\(x::a). x) :: (forall. a - a)

 Although the program prints forall, the absence of a type variable
 indicates Rank 0, correct?

It's a bit unclear what you mean, and the prototype implementation you
seem to be using deviates from Haskell conventions here. The prototype
checker sees a as a type constant here, so it plays the same role as
Int before. In particular, a isn't a type variable, and there's no
quantification.

 I understand these to be Rank 1 terms:

 (\x. x) :: (forall a. a - a) -- This is not the same as the third
 example above, right? This one identifies the type variable a, the one
 above does not. Also, there's no explicit annotation, it's inferred.

The implementation indeed considers them to be different. Before a
was a concrete type, and the function was the monomorphic identity
function on that type. Now, a is a type variable, and the function
is the polymorphic identity function.

[...]

 I understand these to be Rank 2 terms:

 (\(x::(forall a. a)). 0) :: (forall. (forall a. a) - Int)

 The explicit forall annotation on the bound and binding variable x
 causes the program to infer a Rank 2 polytype as indicated by the -
 Int following the (forall a. a), while noting the absence of a type
 variable following the left-most forall printed by the program, correct?

Your description here is a bit strange. It's a rank-2 type because
there's a rank-1 type occurring to the left of the function arrow.


 (\(x::(forall a. a - a)). x) :: (forall b. (forall a. a - a) - b -
 b)

 Also Rank 2, only one arrow to the right of (forall a. a - a) counts.

It's rank 2, yes. I'm not sure what you mean here by saying that only
one arrow counts.

 The universal quantifier on type variable b ranges over the type
 variable a, correct?

No. The universal quantifier ranges over all (mono)types.

 I understand this to be a Rank 3 term:

 (\(f::(forall a. a - a)). \(x::(forall b. b)). f (f x)) :: (forall c.
 (forall a. a - a) - (forall b. b) - c)

No, this is still rank 2. It uses two rank 1 types as function
arguments. For it to be rank 3, it'd have to use a rank 2 type in the
argument position of a function type. Note that the function arrow
associates to the right:

forall c. (forall a. a - a) - ((forall b. b) - c)  -- rank 2
(forall c. ((forall a. a - a) - (forall b. b)) - c) -- rank 3

 The arrows to the right of the universally quantified a and b
 expressions qualify this as Rank 3.

No, you seem to be applying a wrong definition of rank. The correct
definition is given in Section 3.1 of the paper.

Here's how you can derive the type above as a sigma_2:

sigma_2
  ~  forall c. sigma_2
  ~  forall c. sigma_1 - sigma_2
  ~  forall c. sigma_1 - sigma_1 - sigma_2
  ~  forall c. sigma_1 - sigma_1 - sigma_1
  ~  forall c. sigma_1 - sigma_1 - sigma_0
  ~  forall c. sigma_1 - sigma_1 - c
  ~  forall c. (forall a. sigma_1) - sigma_1 - c
  ~  forall c. (forall a. sigma_0) - sigma_1 - c
  ~  forall c. (forall a. tau - tau) - sigma_1 - c
  ~  forall c. (forall a. a - a) - sigma_1 - c
  ~  forall c. (forall a. a - a) - (forall b. sigma_1) - c
  ~  forall c. (forall a. a - a) - (forall b. sigma_0) - c
  ~  forall c. (forall a. a - a) - (forall b. b) - c

 Type variable c ranges over type
 variables a and b, correct?

No. Each of the type variables ranges over all (mono)types. (Or do you
mean what the scope of c is? If so, then the scope of c is the
complete type signature.)

Cheers,
  Andres

--
Andres Löh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com

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


Re: [Haskell-cafe] [Haskell] ANNOUNCE: control-monad-loop 0.1

2012-07-09 Thread Roman Cheplyaka
* Joey Adams joeyadams3.14...@gmail.com [2012-07-09 01:38:06-0400]
 This package provides imperative-style loops supporting continue and
 break.  For example:
 
 import Control.Monad
 import Control.Monad.IO.Class
 import Control.Monad.Trans.Loop
 import Control.Monad.Trans.Class
 
 main :: IO ()
 main =
 foreach [0..] $ \i -
 foreach [0..] $ \j - do
 when (j == 0) $
 continue-- skip to next iteration
 when (j = 5) $
 exit-- exit the loop
 when (i = 5) $
 lift exit   -- exit the outer loop by calling 'exit'
 in the parent monad
 liftIO $ print (i, j)

Very nice!

Here's a patch to generalize foreach to any Foldable:
https://github.com/joeyadams/haskell-control-monad-loop/pull/1

Also, it's not obvious how your tests work. Please consider using HUnit
and test-framework (or similar) to organize them.

-- 
Roman I. Cheplyaka :: http://ro-che.info/

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


Re: [Haskell-cafe] Best way to build a GHC backend?

2012-07-09 Thread Brent Yorgey
On Sun, Jul 08, 2012 at 09:21:08AM -0600, Jonathan Geddes wrote:
 I agree that the Raison d'être for a .NET or JVM backend is interop.
 Perhaps that's not worth the effort of an entirely new backend. JavaScript
 is a different beast, however.  I said before:
 
 From my point of view, languages that cannot run on one of the 3
  aforementioned platforms will become irrelevant. (with the exception of
 C,
  of course).
 
 I'll take that one step further and say that for web applications it is
 becoming increasingly difficult to justify using a language that WILL NOT
 run both client and server. JavaScript (with NodeJS), Clojure (with
 ClojureScript), and Dart are just a few examples.
 
 I really believe that with a solid JavaScript backend, Haskell would be an
 ideal web application language. Am I alone in that belief? What can I do to
 get the ball rolling on that?

I should point out that the ball already IS rolling -- ranging from
EDSLs that compile to JavaScript [1,2] to macro systems [3] to more
serious full-featured efforts [4,5].  There's even a wiki page listing
all these and more [6].  The yesod developers share your view that
Haskell would benefit from some sort of JavaScript backend; see [7] as
well as the ensuing discussion on Reddit [8]. See also Elm [9], which
compiles to HTML+CSS+JavaScript and has some Haskell integration [10].

Rather than trying to start yet another effort, what about
contributing to one of these ongoing ones?

-Brent

[1] http://www.ittc.ku.edu/csdlblog/?p=88
[2] http://www.ittc.ku.edu/csdl/fpg/node/125
[3] http://www.haskell.org/haskellwiki/JMacro
[4] http://uu-computerscience.github.com/uhc-js/
[5] https://github.com/ghcjs/ghcjs
[6] http://www.haskell.org/haskellwiki/The_JavaScript_Problem
[7] http://www.yesodweb.com/blog/2012/04/client-side
[8] 
http://www.reddit.com/r/haskell/comments/sm72n/client_side_yesod_an_frpinspired_approach/
[9] http://elm-lang.org/
[10] 
http://www.reddit.com/r/haskell/comments/uugne/announcing_elm_02_haskell_integration_yesod/

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


Re: [Haskell-cafe] combining predicates, noob question

2012-07-09 Thread Brent Yorgey
On Sat, Jul 07, 2012 at 09:42:01PM -0300, Sebastián Krynski wrote:
 Ok , thanks for the answers, I understand now what  liftM2 does.
  In this case would it be silly to  use  combinerPred (and maybe a newType
  Predicate a = a - Bool) for the sake of readability or shoud I stick with
 a - Bool  and  liftM2?

No, not silly.  Use whatever you find most readable.

-Brent




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


Re: [Haskell-cafe] Haskell Implementors' Workshop talk proposals due in one week!

2012-07-09 Thread Johan Tibell
Reminder. The deadline is end-of-day this Tuesday.

On Tue, Jul 3, 2012 at 7:17 AM, Johan Tibell johan.tib...@gmail.com wrote:
  Call for Talks
ACM SIGPLAN Haskell Implementors' Workshop

 http://haskell.org/haskellwiki/HaskellImplementorsWorkshop/2012
Copenhagen, Denmark, September 14th, 2012
 The workshop will be held in conjunction with ICFP 2012
 http://www.icfpconference.org/icfp2012/

 Important dates

 Proposal Deadline:  10th July  2012
 Notification:   27th July  2012
 Workshop:   14th September 2012

 The Haskell Implementors' Workshop is to be held alongside ICFP 2012
 this year in Copenhagen, Denmark. There will be no proceedings; it is an
 informal gathering of people involved in the design and development of
 Haskell implementations, tools, libraries, and supporting
 infrastructure.

 This relatively new workshop reflects the growth of the user community:
 there is a clear need for a well-supported tool chain for the
 development, distribution, deployment, and configuration of Haskell
 software. The aim is for this workshop to give the people involved with
 building the infrastructure behind this ecosystem an opportunity to bat
 around ideas, share experiences, and ask for feedback from fellow
 experts.

 We intend the workshop to have an informal and interactive feel, with a
 flexible timetable and plenty of room for ad-hoc discussion, demos, and
 impromptu short talks.


 Scope and target audience
 -

 It is important to distinguish the Haskell Implementors' Workshop from
 the Haskell Symposium which is also co-located with ICFP 2012. The
 Haskell Symposium is for the publication of Haskell-related research. In
 contrast, the Haskell Implementors' Workshop will have no proceedings --
 although we will aim to make talk videos, slides and presented data
 available with the consent of the speakers.

 In the Haskell Implementors' Workshop, we hope to study the underlying
 technology. We want to bring together anyone interested in the
 nitty-gritty details behind turning plain-text source code into a
 deployed product. Having said that, members of the wider Haskell
 community are more than welcome to attend the workshop -- we need your
 feedback to keep the Haskell ecosystem thriving.

 The scope covers any of the following topics. There may be some topics
 that people feel we've missed, so by all means submit a proposal even if
 it doesn't fit exactly into one of these buckets:

   * Compilation techniques
   * Language features and extensions
   * Type system implementation
   * Concurrency and parallelism: language design and implementation
   * Performance, optimisation and benchmarking
   * Virtual machines and run-time systems
   * Libraries and tools for development or deployment


 Talks
 -

 At this stage we would like to invite proposals from potential speakers
 for a relatively short talk. We are aiming for 20 minute talks with 10
 minutes for questions and changeovers. We want to hear from people
 writing compilers, tools, or libraries, people with cool ideas for
 directions in which we should take the platform, proposals for new
 features to be implemented, and half-baked crazy ideas. Please submit a
 talk title and abstract of no more than 200 words to:
 johan.tib...@gmail.com

 We will also have a lightning talks session which will be organised on
 the day. These talks will be 2-10 minutes, depending on available time.
 Suggested topics for lightning talks are to present a single idea, a
 work-in-progress project, a problem to intrigue and perplex Haskell
 implementors, or simply to ask for feedback and collaborators.


 Organisers
 --

   * Lennart Augustsson (Standard Chartered Bank)
   * Manuel M T Chakravarty (University of New South Wales)
   * Gregory Collins - co-chair (Google)
   * Simon Marlow   (Microsoft Research)
   * David Terei(Stanford University)
   * Johan Tibell - co-chair(Google)

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


Re: [Haskell-cafe] Best way to build a GHC backend?

2012-07-09 Thread Jonathan Geddes
Thanks for all the Info, Brent! I wasn't aware of many of those projects.

I agree that contributing to an existing project is a better idea than
doing something new. I suppose I was hoping there would be an official GHC
JavaScript backend so that it would be clear which of the efforts to
contribute to (and use).

-J Arthur

On Mon, Jul 9, 2012 at 8:38 AM, Brent Yorgey byor...@seas.upenn.edu wrote:

 On Sun, Jul 08, 2012 at 09:21:08AM -0600, Jonathan Geddes wrote:
  I agree that the Raison d'être for a .NET or JVM backend is interop.
  Perhaps that's not worth the effort of an entirely new backend.
 JavaScript
  is a different beast, however.  I said before:
 
  From my point of view, languages that cannot run on one of the 3
   aforementioned platforms will become irrelevant. (with the exception of
  C,
   of course).
 
  I'll take that one step further and say that for web applications it is
  becoming increasingly difficult to justify using a language that WILL NOT
  run both client and server. JavaScript (with NodeJS), Clojure (with
  ClojureScript), and Dart are just a few examples.
 
  I really believe that with a solid JavaScript backend, Haskell would be
 an
  ideal web application language. Am I alone in that belief? What can I do
 to
  get the ball rolling on that?

 I should point out that the ball already IS rolling -- ranging from
 EDSLs that compile to JavaScript [1,2] to macro systems [3] to more
 serious full-featured efforts [4,5].  There's even a wiki page listing
 all these and more [6].  The yesod developers share your view that
 Haskell would benefit from some sort of JavaScript backend; see [7] as
 well as the ensuing discussion on Reddit [8]. See also Elm [9], which
 compiles to HTML+CSS+JavaScript and has some Haskell integration [10].

 Rather than trying to start yet another effort, what about
 contributing to one of these ongoing ones?

 -Brent

 [1] http://www.ittc.ku.edu/csdlblog/?p=88
 [2] http://www.ittc.ku.edu/csdl/fpg/node/125
 [3] http://www.haskell.org/haskellwiki/JMacro
 [4] http://uu-computerscience.github.com/uhc-js/
 [5] https://github.com/ghcjs/ghcjs
 [6] http://www.haskell.org/haskellwiki/The_JavaScript_Problem
 [7] http://www.yesodweb.com/blog/2012/04/client-side
 [8]
 http://www.reddit.com/r/haskell/comments/sm72n/client_side_yesod_an_frpinspired_approach/
 [9] http://elm-lang.org/
 [10]
 http://www.reddit.com/r/haskell/comments/uugne/announcing_elm_02_haskell_integration_yesod/

 ___
 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] Best way to build a GHC backend?

2012-07-09 Thread Stephen Tetley
On 9 July 2012 15:38, Brent Yorgey byor...@seas.upenn.edu wrote:
 I should point out that the ball already IS rolling -- ranging from
 EDSLs that compile to JavaScript [1,2] to macro systems [3] to more
 serious full-featured efforts [4,5].

Also, a JavaScript backend has recently been developed for Clean, the
other major lazy functional language.

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


Re: [Haskell-cafe] combining predicates, noob question

2012-07-09 Thread Paolino
You can still use the monadic combinators, with the price of wrapping and
unwrapping in case of newtype.

newtype P a = P {unP :: a - Bool}
liftM2'P :: (Bool - Bool - Bool) - P a - P a - P a
liftM2'P  op = (P .) . on (liftM2 op) unP

paolino


2012/7/8 Sebastián Krynski skryn...@gmail.com

 Ok , thanks for the answers, I understand now what  liftM2 does.
  In this case would it be silly to  use  combinerPred (and maybe a newType
  Predicate a = a - Bool) for the sake of readability or shoud I stick with
 a - Bool  and  liftM2?

 thanks, Sebastián



 2012/7/6 Brent Yorgey byor...@seas.upenn.edu

 On Fri, Jul 06, 2012 at 03:17:54PM -0300, Felipe Almeida Lessa wrote:
  On Fri, Jul 6, 2012 at 2:11 PM, Sebastián Krynski skryn...@gmail.com
 wrote:
   As I was using predicates (a - bool) , it appeared the need for
 combining
   them with a boolean operator (bool - bool - bool)  in order to get
 a new
   predicate
   combining the previous two. So I wrote my function combinerPred (see
 code
   below). While I think this is JUST ok, i'm feeling a monad in the air.
So.. where is the monad?
  
   combinerPred ::  (a - Bool)  - (a - Bool) - (Bool - Bool -
 Bool) -
   (a - Bool)
   combinerPred pred1 pred2 op = \x - op (pred1 x) (pred2 x)
 
  That's the `(-) a` monad:
 
import Control.Applicative
 
combinerPred ::  (a - Bool)  - (a - Bool) - (Bool - Bool -
  Bool) - (a - Bool)
combinerPred pred1 pred2 op = op $ pred1 * pred2

 By the way, I find it more natural to make 'op' the first argument,
 because it is more useful to partially apply combinerPred to an
 operation that it is to some predicates.  Also, in that case
 combinerPred is simply liftA2:

   import Control.Applicative

   combinerPred :: (Bool - Bool - Bool) - (a - Bool) - (a - Bool) -
 (a - Bool)
   combinerPred = liftA2

 -Brent

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



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


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


[Haskell-cafe] Sifflet type checker [from Re: [Haskell] ANNOUNCE: Sifflet visual programming language, release 2.0.0.0]

2012-07-09 Thread gdweber
On 2012-Jul-07, Henning Thielemann wrote:
 
 On Thu, 5 Jul 2012, gdwe...@iue.edu wrote:
 
 Sifflet and sifflet-lib 2.0.0.0, now available on Hackage!
 
 This version introduces a type checker and partial support
 for higher order functions in Sifflet, the visual, functional
 programming language and support system for students learning
 about recursion.
 
 You have implemented your own type-checker, right?

It is my code implementing the type checker from Simon Peyton-Jones's
book The Implementation of Functional Programming Languages (1987).

 I plan to add a
 type-checker to our live-sequencer project. [1] So far I have
 thought about using the Helium type checker but I have not done it
 so far. If you want to make your type-checker useful for other
 projects, you may put it into a separate package without the hard to
 install dependencies on cairo and glib.
 

I am very interested in receiving suggestions for modularizing
my packages, and I thank you for this one.

I should point out that the Sifflet type checker (unlike Helium's)
is not a type checker for Haskell, or even a reduced version of Haskell,
but for a very small language consisting of these expressions 
(from Language.Sifflet.Expr):

data Expr = EUndefined
  | ESymbol Symbol 
  | EBool Bool
  | EChar Char
  | ENumber Number
  | EString String
  | EIf Expr Expr Expr -- ^ if test branch1 branch2
  | EList [Expr]
  | ELambda Symbol Expr 
  | EApp Expr Expr -- ^ apply function to argument
  | ECall Symbol [Expr] -- ^ function name, arglist
  | EOp Operator Expr Expr -- ^ binary operator application
  | EGroup Expr-- ^ grouping parentheses
deriving (Eq, Show)

(there are some redundant variants there, because I
designed Expr before thinking about type checking and then
augmented it to add the type checker)

and these types

data Type = TypeVar TypeVarName  -- named type variable
  | TypeCons TypeConsName [Type] -- constructed type
deriving (Eq)

Do you still think my type checker would be useful to you,
or to Haskellers generally?

 [1] http://www.youtube.com/watch?v=sXywCHR9WwE

Ah, I enjoyed the performance!

Greg

-- 
Gregory D. Weber, Ph. D.:
Associate Professor of Informatics / \
Indiana University East   0   :
Tel. (765) 973-8420; FAX (765) 973-8550  / \
http://mypage.iu.edu/~gdweber/  1  []

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


Re: [Haskell-cafe] [Haskell] ANNOUNCE: control-monad-loop 0.1

2012-07-09 Thread Joey Adams
On Mon, Jul 9, 2012 at 8:28 AM, Roman Cheplyaka r...@ro-che.info wrote:
 Very nice!

 Here's a patch to generalize foreach to any Foldable:
 https://github.com/joeyadams/haskell-control-monad-loop/pull/1

Thanks for the patch!  I merged it, but I plan to wait a little while
before uploading another release to Hackage.  This changes the
signature of an existing function, so I'll have to bump the major
version number.

 Also, it's not obvious how your tests work. Please consider using HUnit
 and test-framework (or similar) to organize them.

The tests currently aren't automated.  It's hard to write an automated
test to make sure a program doesn't leak.  Not impossible (thanks to
GHC.Stats), but hard.

Thanks for pointing out test-framework, though.

-Joey

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


Re: [Haskell-cafe] Sifflet type checker

2012-07-09 Thread Henning Thielemann


On Mon, 9 Jul 2012, gdwe...@iue.edu wrote:


data Type = TypeVar TypeVarName  -- named type variable
 | TypeCons TypeConsName [Type] -- constructed type
   deriving (Eq)

Do you still think my type checker would be useful to you,
or to Haskellers generally?


I see. Then it is probably not very useful for me. :-(



[1] http://www.youtube.com/watch?v=sXywCHR9WwE


Ah, I enjoyed the performance!


Nice to hear that you like it!

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


Re: [Haskell-cafe] Linking against Sqlite3 on Windows problem

2012-07-09 Thread Joey Adams
On Mon, Jul 9, 2012 at 3:56 AM, Eugene Dzhurinsky jdeve...@gmail.com wrote:
 Hi all!

 I created simple application, which uses sqlite3 as it's datastore back-end. I
 faced no problems when building and running it on Linux, but after I tried to
 build it on Windows, I see weird linking error:

You could use the bundled sqlite3.c instead:

cabal install --flags=builtin-sqlite3

Unfortunately, the sqlite3 package currently ships with a very old
version of sqlite3.c (version 3.5.9).  I submitted a bug report:

https://github.com/GaloisInc/sqlite/issues/1

Until a fix is pushed, you can try downloading the latest sqlite3.c
yourself, and placing it at sqlite3.6/sqlite3.c .  I don't know if you
will encounter any compatibility issues or not.

Hope this helps,
-Joey

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