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 :: (forall a. a) - Int
  -- The internals of test2 determines what type, or types, to instantiate
 the
  argument at

 I can easily understand your explanation for test2: the type var a is
 closed under existential (?) quantification. I can't do the same for
 test1, even if it seems that a is closed under universal (?)
 quantification as well.


Both are universally quantified, but at a different level.  To look at it in
System F-land, you have two levels of types that can get passed in lambdas.
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 lambda, and @ is type-level application.

In test1, the caller specifies a and then passes in an object of that
type.
In test2, the caller must pass in an object which is of all types, and test2
asks for that object to be instantiated at the type Int

 Or, to put it another way, since there are no non-bottom objects of type
  (forall a. a):

 Why?


Informally, because you can't create something that can be any type.  For
example, what could the result of

test3 :: (forall a. a) - Int
test3 x = length (x `asTypeOf` [()])

be?  How could you call it?

 test1 converts *anything* to an Int.

 Is the only possible implementation of test1 the one ignoring its
 argument (apart from bottom of course)?


There's one way that doesn't entirely ignore its argument.

test4 x = seq x 1

But I don't like to talk about that one :)

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


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, September 16, 2009, 7:24 PM

Hi Gregory,

On Wed, Sep 16, 2009 at 6:51 PM, Gregory Propf gregorypr...@yahoo.com wrote:

 I'm trying to install the Haskell Platform.  I'm using Ubuntu 9.02 and GHC 
 6.10.4 on a 64 bit AMD and keep getting this crap when I do 'make install'.  
 The stuff builds OK and the script in question does indeed exist.  Anybody 
 know what this is.  I've looked online and none of the other people with this 
 issue seem to know the fix.

 Error:
 The mtl-1.1.0.2/Setup script does not exist or cannot be run



Can you try this:

http://trac.haskell.org/haskell-platform/ticket/84

Let us know if you need help applying the patch.

Paulo



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


[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 that these are actually C development libraries, not Haskell 
modules.  The thing is that they are all installed, using the Ubuntu synaptic 
tool.  This is Ubuntu 9.04.  Is there something I need to tell cabal about 
where these libraries are?



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


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 dependencies are missing:
 glib =0.10, gtk =0.10, gtksourceview2 =0.10.0

 I am aware that these are actually C development libraries, not Haskell 
 modules.  The thing is that they are all installed, using the Ubuntu synaptic 
 tool.  This is Ubuntu 9.04.  Is there something I need to tell cabal about 
 where these libraries are?

You need to install gtk2hs, a haskell binding to gtk libraries. When
you build it, make sure to build the gtksourceview component as well.
On (K)ubuntu you will need to download the gtk2hs tarball, install gtk
dev libraries, and the usual configure, make and make install.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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
http://www.cs.berkeley.edu/~jcondit/pl-prelim/hudak89functional.pdf ,
but when I try to download that file, the following error message
appears:

The server has encountered a problem because access is restricted.

Your request was :
http://www.cs.berkeley.edu/~jcondit/pl-prelim/hudak89functional.pdf 

-- Benjamin L. Russell

[1] Hudak, Paul. Conception, Evolution and Application of Functional
Programming Languages. New York, NY: _ACM Computing Surveys (CSUR)_
21(3) (September 1989): 359-411.
http://portal.acm.org/citation.cfm?id=72551.72554coll=ACMdl=ACMidx=J204part=journalWantType=Journalstitle=ACM%20Computing%20Surveys%20%28CSUR%29CFID=52128875CFTOKEN=48215788.
Also available at
http://www.cs.berkeley.edu/~jcondit/pl-prelim/hudak89functional.pdf.
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
Furuike ya, kawazu tobikomu mizu no oto. 
-- Matsuo Basho^ 

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


[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 you for consideration for inclusion in
System.FilePath.Posix.  Please change the names as you see fit.

I do not know if they make sense for System.FilePath.Windows.  If
the do not make sense, then please feel free to drop them so as to
preserve the interface.

As requested, I Cc'ed the haskell-cafe, but I am not at the moment
following these threads, so if anyone else responds, please Cc me
if you wish.

Thanks again and cheers,
- Marcus

P.S. Here they are.  Although I use ksh(1) as an example, this is a
feature of POSIX shells.

 -- | 'reduceFilePath' returns a pathname that is reduced to canonical
 -- form equivalent to that of ksh(1), that is, symbolic link names are
 -- treated literally when finding the directory name.  See @cd -L@ of
 -- ksh(1).  Specifically, extraneous separators @(\/\)@, dot
 -- @(\.\)@, and double-dot @(\..\)@ directories are removed.

 reduceFilePath :: FilePath - FilePath
 reduceFilePath = joinPath . filePathComponents

This is in turn built on filePathComponents that does all the work.

 filePathComponents :: FilePath - [FilePath]
 filePathComponents  = []
 filePathComponents (c:cs) =
 reverse $ snd $ foldl accumulate
   (if c == pathSeparator then ([],[/]) else
 ([c],[]))
   (cs++[pathSeparator])
 where
 accumulate :: (String,[String]) - Char - (String,[String])
 accumulate (cs, css) c =
 if c == pathSeparator
 then ([],(if null cs then id else cons cs) css)
 else (cs++[c],css)
 cons :: String - [String] - [String]
 cons cs css
 | cs == . = css
 | cs /= .. || null css = cs : css
 | otherwise =
   let hd = head css
   tl = tail css
   in if hd == [pathSeparator]
  then css
  else if hd == ..
   then cs : css
   else if null tl
then [.]
else tl

//

-- 
  Marcus D. Gabriel, Ph.D. Saint Louis, FRANCE
  http://www.marcus.gabriel.namemailto:mar...@gabriel.name
  Tel: +33.3.89.69.05.06   Portable: +33.6.34.56.07.75


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


[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 whether you would be interested in linking to my website 
 http://www.frixo.com from your page?

 http://haskell.cs.yale.edu/haskellwiki/icfp_2009_local_arrangements

 Frixo is a road traffic reporting site and think it may be a useful resource 
 for your readers. It provides users with live traffic information and gets 
 updated every 3 minutes using various road sensors.

 Thank you for your consideration.

 Kind Regards,
 Peter
 http://www.frixo.com





-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 API change
(though if you use the graphvizWithHandle function in
Data.GraphViz.Commands, you should ensure that your Handle - IO a
function closes the Handle when done).  Changes in this release are:

* Potentially fixed the graphvizWithHandle bug where warnings would be
  emitted about Handles not being closed correctly or too early; correct
  approach spotted by Nikolas Mayr.

* Fixed up Parsing of various Attribute sub-values, especially Point and
  Spline (and hence Pos, which uses them).

* Pre-process out comments and join together multi-line strings before
  parsing.

* Properly parse Doubles like .2.

-- 
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


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: 
glib packagegtk2hs-cast-gnomevfs library: A type class for cast functions of 
Gtk2hs: gnomevfs packagegtk2hs-cast-gtk library: A type class for cast 
functions of Gtk2hs: gtk packagegtk2hs-cast-gtkglext library: A type class for 
cast functions of Gtk2hs: gtkglext packagegtk2hs-cast-gtksourceview2 library: A 
type class for cast functions of Gtk2hs: gtksourceview2 packagegtk2hs-cast-th 
library: A type class for cast functions of Gtk2hs: TH packagegtk2hs-rpn 
library: Adds a module to gtk2hs allowing layouts to be defined using
reverse polish notation.

--- On Thu, 9/17/09, david48 dav.vire+hask...@gmail.com wrote:

From: david48 dav.vire+hask...@gmail.com
Subject: Re: [Haskell-cafe] Trouble installing leksah
To: Gregory Propf gregorypr...@yahoo.com
Cc: Haskell-Cafe haskell-cafe@haskell.org
Date: Thursday, September 17, 2009, 12:39 AM

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 dependencies are missing:
 glib =0.10, gtk =0.10, gtksourceview2 =0.10.0

 I am aware that these are actually C development libraries, not Haskell 
 modules.  The thing is that they are all installed, using the Ubuntu synaptic 
 tool.  This is Ubuntu 9.04.  Is there something I need to tell cabal about 
 where these libraries are?

You need to install gtk2hs, a haskell binding to gtk libraries. When
you build it, make sure to build the gtksourceview component as well.
On (K)ubuntu you will need to download the gtk2hs tarball, install gtk
dev libraries, and the usual configure, make and make install.



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


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

http://haskell.org/gtk2hs/


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


[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 working and
I can't see why not.  So I'm asking for help on two fronts:

1) Why is this failing?

2) Maybe more usefully, how should I actually be doing this?  It seems
   an ugly approach; a voice in my head is saying scrap your
   boilerplate, but I've no idea yet if that's actually applicable
   here; should I look at it?

On with the show...

I need these for subclass stuff later on...

 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE OverlappingInstances #-}
 {-# LANGUAGE UndecidableInstances #-}

 module Ambig where

I wish to define a number of algebraic data types with the ability to
turn Int values into instances of those types.  So I define a
typeclass saying this is possible.  I use Maybe so I can encode the
existence of out-of-range Int values, which will vary from target type
to target type.

 class Target a where
 convert :: Int - Maybe a

E.g. here's a type Foo which only wants values between 1 and 10:

 data Foo = Foo Int deriving (Show)
 instance Target Foo where
 convert n | n `elem` [1..10] = Just $ Foo n
   | otherwise = Nothing

(That's a simple example; some are rather more complex.  How to do
this isn't what I'm asking about, really.)

So we have, for example:

*Ambig (convert 1) :: Maybe Foo
Just (Foo 1)
*Ambig (convert 11) :: Maybe Foo
Nothing

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 converted into that constructor.

 class Enumerated a where
 constructors :: [a]

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?)

Now we get to the crux.  If a type is an instance of Enumerated, it
should also be a Target, because we should be able to convert from Int
just by list lookup.  But we include a bounds check, naturally...

 instance (Enumerated a) = Target a where
 convert n | n `elem` [0..len-1] = Just $ constructors !! n
   | otherwise = Nothing
 where len = length constructors

So I would _hope_ that then, e.g., we'd have:

*Ambig (convert 0) :: Maybe Bar
Just X
*Ambig (convert 1) :: Maybe Bar
Just Y
*Ambig (convert 3) :: Maybe Bar
Nothing

Sadly, this function doesn't compile, dying with an Ambiguous type
variable error:

Ambig.lhs:75:29:
Ambiguous type variable `a' in the constraint:
  `Enumerated a'
arising from a use of `constructors' at Ambig.lhs:74:29-40
Probable fix: add a type signature that fixes these type  
variable(s)


If we replace length constructors with 3 (say), it compiles (but
is useless).  Adding a type signature doesn't help: it's misplaced
in that context.  If I break it out of the instance declaration so I
can add one, I still get the same problem:

 convert' :: (Enumerated a, Target a) = Int - Maybe a
 convert' n | n `elem` [0..len-1] = Just $ constructors !! n
| otherwise = Nothing
 where len = length constructors

I guess I see roughly what's going on; the question is which
constructors instance is meant?, right?  In the Just part it's OK,
because it can be inferred from the function's return type (right?).
But in the guard we don't have that help, so it could be any
Enumerated instance?

Any advice appreciated!  Particularly if this is just a dumb approach.
For context, this is related to deserialisation of binary data (they'll
actually be Word8's, not Int's) into a variety of data structures.

Hmmm, maybe I should just be using Data.Binary...

Many thanks,

-Andy

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


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 converted into that constructor.

  class Enumerated a where
  constructors :: [a]

 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 SYB:

{-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE FlexibleContexts #-}

 module Test where

 import Data.Data
 import Data.Generics.Aliases (extB)

 -- | Construct the empty value for a datatype. For algebraic datatypes, the
 -- leftmost constructor is chosen.
 empty :: forall a. Data a = a
 empty = general
   `extB` char
   `extB` int
   `extB` integer
   `extB` float
   `extB` double where
   -- Generic case
   general :: Data a = a
   general = fromConstrB empty (indexConstr (dataTypeOf general) 1)

   -- Base cases
   char= '\NUL'
   int = 0  :: Int
   integer = 0  :: Integer
   float   = 0.0:: Float
   double  = 0.0:: Double

 -- | Return a list of values of a datatype. Each value is one of the
 possible
 -- constructors of the datatype, populated with 'empty' values.
 constrs :: forall a. Data a = [a]
 constrs = general
   `extB` char
   `extB` int
   `extB` integer
   `extB` float
   `extB` double where
   -- Generic case
   general :: Data a = [a]
   general = map (fromConstrB empty)
   (dataTypeConstrs (dataTypeOf (unList general))) where
 unList :: Data a = [a] - a
 unList = undefined

   -- Base cases
   char= \NUL
   int = [0   :: Int]
   integer = [0   :: Integer]
   float   = [0.0 :: Float]
   double  = [0.0 :: Double]


|constrs| is similar to your |constructors|, but in this way you get it for
free for any datatype with a |Data| instance. Then I guess your |convert|
is:

convert :: forall a. Data a = Int - Maybe a
 convert n = let cs :: [a]
 cs = constrs
 in if (length cs  n) then (Just (cs !! n)) else Nothing


Note that ScopedTypeVariables are essential to typecheck this code.


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


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 lambda, and @ is type-level application.

Ok. But let me be pedantic: where is the universal quantification in
test1? It seems to me the a is a free variable in test1 while being
closed under universal quantification in test2.

 In test1, the caller specifies a and then passes in an object of that
 type.

The witness?

 In test2, the caller must pass in an object which is of all types, and test2
 asks for that object to be instantiated at the type Int

of all types means a value which belongs to all the sets of all the
types, i.e. bottom?

  Or, to put it another way, since there are no non-bottom objects of type
  (forall a. a):

 Why?

 Informally, because you can't create something that can be any type.

Yes, I misread the initial statement. I missed the non-bottom part :)

 There's one way that doesn't entirely ignore its argument.

 test4 x = seq x 1

 But I don't like to talk about that one :)

:) Thank you Ryan, you were very explicative. I may say that the use
of the System-F's notation, making everything explicit, clarifies this
a bit.

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


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 rule that each constructor's position in the list is the Int which
  gets converted into that constructor.
 
   class Enumerated a where
   constructors :: [a]
 
  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 SYB:
Wow.

What about

data Bar = X | Y | Z deriving (Show, Eq, Ord, Enum, Bounded)

instance Enumerated Bar where
constructors = [minBound .. maxBound]

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


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 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 converted into that constructor.
  
class Enumerated a where
constructors :: [a]
  
   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 SYB:
 Wow.

 What about

 data Bar = X | Y | Z deriving (Show, Eq, Ord, Enum, Bounded)

 instance Enumerated Bar where
constructors = [minBound .. maxBound]

 ?


Oh yes, that will certainly work for this very simple datatype. However, one
cannot automatically derive instances of |Bounded| for datatypes with
non-nullary constructors.


Cheers,
Pedro


 ___
 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] 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 SYB:
Wow.

What about

data Bar = X | Y | Z deriving (Show, Eq, Ord, Enum, Bounded)

instance Enumerated Bar where
   constructors = [minBound .. maxBound]

?

Oh yes, that will certainly work for this very simple datatype.  
However, one cannot automatically derive instances of |Bounded| for  
datatypes with non-nullary constructors.


That would be OK in this instance, I think; I'm already dealing with  
some of those cases by hand, but there were enough purely nullary ones  
that this seemed worth doing.


I don't know if that will work any better with Foo/convert,  
though... :-)


Thanks though Daniel - it's good to meet Enum and Bounded.

-Andy

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


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 certainly ugly.  Any suggestions?)
   
   |constructors| is expressible in SYB:
 
  Wow.
 
  What about
 
  data Bar = X | Y | Z deriving (Show, Eq, Ord, Enum, Bounded)
 
  instance Enumerated Bar where
 constructors = [minBound .. maxBound]
 
  ?
 
  Oh yes, that will certainly work for this very simple datatype.
  However, one cannot automatically derive instances of |Bounded| for
  datatypes with non-nullary constructors.

Andy's original message hasn't found its way into my inbox yet (neither has 
yours which 
Andy here quotes), so I don't know what Andy wants to do.
From the part you quoted, I drew the conclusion that one thing Andy wanted was 
a more 
elegant way for the case of nullary constructors. For that, SYB is certainly 
overkill.
I haven't looked at your code, I suppose it also does something reasonable in 
the presence 
of non-nullary constructors, in which case the separate treatment of only 
nullary 
constructors would of course be unnecessary.


 That would be OK in this instance, I think; I'm already dealing with
 some of those cases by hand, but there were enough purely nullary ones
 that this seemed worth doing.

 I don't know if that will work any better with Foo/convert,
 though... :-)

I'll probably understand that when your original message arrives :-)


 Thanks though Daniel - it's good to meet Enum and Bounded.

 -Andy

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


[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: Re: [Haskell-beginners] map question
To: Joost Kremers joostkrem...@fastmail.fm
Cc: beginn...@haskell.org
Date: Thursday, September 17, 2009, 6:06 AM

This works:

map (+ (-1)) [1,2,3,4]


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]

[2,4,6,8]

Prelude map (/ 2) [1,2,3,4]

[0.5,1.0,1.5,2.0]

Prelude map (2 /) [1,2,3,4]

[2.0,1.0,0.,0.5]



But I can't seem to find a way to get map to substract 1 from all members of the

list. The following form is the only one that works, but it doesn't give the

result I'd expect:



Prelude map ((-) 1) [1,2,3,4]

[0,-1,-2,-3]



I know I can use an anonymous function, but I'm just trying to understand the

result here... I'd appreciate any hints to help me graps this.



TIA



Joost





--

Joost Kremers, PhD

University of Frankfurt

Institute for Cognitive Linguistics

Grüneburgplatz 1

60629 Frankfurt am Main, Germany

___

Beginners mailing list

beginn...@haskell.org

http://www.haskell.org/mailman/listinfo/beginners




-Inline Attachment Follows-

___
Beginners mailing list
beginn...@haskell.org
http://www.haskell.org/mailman/listinfo/beginners



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


[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 science/CsPl_Programming languages/Hudak P. 
Conception, evolution, and application of functional programming languages (ACM 
comp.surveys 21, 1989)(T)(53s).djvu

the site is in Russian and you wait 30s before a link to the file appears.




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


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 '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
_ - Nothing

would make it compile.
But there'd be a risk that Target is unusable, depending on how instance 
resolution is 
done.


 I guess I see roughly what's going on; the question is which
 constructors instance is meant?, right?  In the Just part it's OK,
 because it can be inferred from the function's return type (right?).
 But in the guard we don't have that help, so it could be any
 Enumerated instance?

Exactly.


 Any advice appreciated!  Particularly if this is just a dumb approach.
 For context, this is related to deserialisation of binary data (they'll
 actually be Word8's, not Int's) into a variety of data structures.

 Hmmm, maybe I should just be using Data.Binary...

 Many thanks,

 -Andy


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


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.

http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.83.6505

-joh

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


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
   _ - Nothing

would make it compile.


Neat trick.  It works: thanks!

But there'd be a risk that Target is unusable, depending on how  
instance resolution is

done.


Unusable?  How so?  Sorry, but I don't follow...

-Andy

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


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 ambiguity in common mathematical
syntax.
If you play around in ghci you should get the hang of it pretty quick.

- Job



On Thu, Sep 17, 2009 at 11:08 AM, Gregory Propf gregorypr...@yahoo.comwrote:

 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: Re: [Haskell-beginners] map question
 To: Joost Kremers joostkrem...@fastmail.fm
 Cc: beginn...@haskell.org
 Date: Thursday, September 17, 2009, 6:06 AM

 This works:

 map (+ (-1)) [1,2,3,4]


 2009/9/17 Joost Kremers 
 joostkrem...@fastmail.fmhttp://mc/compose?to=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]
 [2,4,6,8]
 Prelude map (/ 2) [1,2,3,4]
 [0.5,1.0,1.5,2.0]
 Prelude map (2 /) [1,2,3,4]
 [2.0,1.0,0.,0.5]

 But I can't seem to find a way to get map to substract 1 from all members
 of the
 list. The following form is the only one that works, but it doesn't give
 the
 result I'd expect:

 Prelude map ((-) 1) [1,2,3,4]
 [0,-1,-2,-3]

 I know I can use an anonymous function, but I'm just trying to understand
 the
 result here... I'd appreciate any hints to help me graps this.

 TIA

 Joost


 --
 Joost Kremers, PhD
 University of Frankfurt
 Institute for Cognitive Linguistics
 Grüneburgplatz 1
 60629 Frankfurt am Main, Germany
 ___
 Beginners mailing list
 beginn...@haskell.org http://mc/compose?to=beginn...@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners



 -Inline Attachment Follows-

 ___
 Beginners mailing list
 beginn...@haskell.org http://mc/compose?to=beginn...@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners



 ___
 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] 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]
 [2,4,6,8]
 Prelude map (/ 2) [1,2,3,4]
 [0.5,1.0,1.5,2.0]
 Prelude map (2 /) [1,2,3,4]
 [2.0,1.0,0.,0.5]

 But I can't seem to find a way to get map to substract 1 from all members of 
 the
 list. The following form is the only one that works, but it doesn't give the
 result I'd expect:

 Prelude map ((-) 1) [1,2,3,4]
 [0,-1,-2,-3]

 I know I can use an anonymous function, but I'm just trying to understand the
 result here... I'd appreciate any hints to help me graps this.

 TIA

 Joost

The reason that map (-1) [1,2,3,4] doesn't work as you'd expect it
to is that - is ambiguous in Haskell (some may disagree).

-1 means -1 in Haskell, i.e. negative 1, not the function that
subtracts 1 from its argument. (-) 1 is the function that subtracts
its argument from 1, which is not what you were looking for either!
You're looking for the function that subtracts 1 from its argument,
which is `subtract 1'.

Prelude map (subtract 1) [1..4]
[0,1,2,3]

Note that `subtract' is just another name for `flip (-)', i.e.
subtraction with its argument in reverse order.

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


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:
 
  test1 = /\a \(x :: a). 1
  test2 = \(x :: forall a. a). x @Int
 
  /\ is type-level lambda, and @ is type-level application.

 Ok. But let me be pedantic: where is the universal quantification in
 test1? It seems to me the a is a free variable in test1 while being
 closed under universal quantification in test2.


The universal quantification is right in the extra lambda: it works for all
types a.

Just like this works on all lists [a]:

length = /\a. \(xs :: [a]). case xs of { [] - 0 ; (x:ys) - 1 + length @a
ys }

Here are some uses of test1:

v1 = test1 @Int 0
v2 = test1 @[Char] hello
v3 = test1 @() ()

Here's a use of test2:

v4 = test2 (/\a. error @a broken)

given error :: forall a. String - a

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


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
| otherwise = case drop n constructors of
 
 (x:_) - Just x
 _ - Nothing
 
  would make it compile.

 Neat trick.  It works: thanks!

  But there'd be a risk that Target is unusable, depending on how
  instance resolution is
  done.

 Unusable?  How so?  Sorry, but I don't follow...


Cf. Section 7.6.3.3 of the user's guide:

When matching, GHC takes no account of the context of the instance declaration 
(context1 
etc). GHC's default behaviour is that exactly one instance must match the 
constraint it is 
trying to resolve. It is fine for there to be a potential of overlap (by 
including both 
declarations (A) and (B), say); an error is only reported if a particular 
constraint 
matches more than one.

The -XOverlappingInstances flag instructs GHC to allow more than one instance 
to match, 
provided there is a most specific one. For example, the constraint C Int [Int] 
matches 
instances (A), (C) and (D), but the last is more specific, and hence is chosen. 
If there 
is no most-specific match, the program is rejected.

So for the matching, you have now

instance Target a where ...

which matches everything. Add an instance declaration of the form

instance (SomeClass b) = Target b where ...

and you're hosed.
Though I think that wouldn't compile, at least not without IncoherentInstances.
Actually, I think now that with one-parameter type classes, if it compiles, it 
will most 
likely work, at least I don't see the problems one can create with 
multi-parameter type 
classes now.

 -Andy


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


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 Enumerated a = Target a where
   convert n
   | n = 0  n  numConstrs = Just result
   | otherwise = Nothing
where
   numConstrs = length (constructors `asTypeOf` [result])
   result = constructors !! n

However let me warn you that you aren't going to be happy with this instance
when it comes time to use this.  Instead, you probably want one of the
following:

defaultConvert :: Enumerated a = Int - a
defaultConvert n
| n = 0  n  numConstrs = Just (WithEnumerated (constrs !! n))
| otherwise = Nothing
  where
constrs = constructors
numConstrs = length constrs

(a)
instance Target SomeEnumeratedType where convert = defaultConvert

(b)
newtype WithEnumerated a = WithEnumerated a
instance Enumerated a = Target (WithEnumerated a) where
convert n = WithEnumerated (defaultConvert n)

OverlappingInstances basically never does what you want in the long run.

  -- ryan

On Thu, Sep 17, 2009 at 9:01 AM, Andy Gimblett hask...@gimbo.org.uk wrote:


 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
   _ - Nothing

 would make it compile.


 Neat trick.  It works: thanks!

  But there'd be a risk that Target is unusable, depending on how instance
 resolution is
 done.


 Unusable?  How so?  Sorry, but I don't follow...


 -Andy

 ___
 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] 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).

For example with a naive fibs, the values you are passing in are computed,
and probably don't exist before you do the recursive call, and then are
discarded shortly afterward.

It seems like putting a cap on the cache size, and then just overwriting old
entries would be better.
Am I missing something?

- Job



On Wed, Sep 16, 2009 at 4:48 PM, Rodney Price rodpr...@raytheon.com wrote:

 How does garbage collection work in an example like the one below?  You
 memoize a function with some sort of lookup table, which stores function
 arguments as keys and function results as values.  As long as the
 function remains in scope, the keys in the lookup table remain in
 memory, which means that the keys themselves always remain reachable
 and they cannot be garbage collected.  Right?

 So what do you do in the case where you know that, after some period of
 time, some entries in the lookup table will never be accessed?  That is,
 there are no references to the keys for some entries remaining, except
 for the references in the lookup table itself.  You'd like to allow the
 memory occupied by the keys to be garbage collected.  Otherwise, if the
 function stays around for a long time, the size of the lookup table
 always grows.  How do you avoid the space leak?

 I notice that there is a function in Data.IORef,

 mkWeakIORef :: IORef a - IO () - IO (Weak (IORef a))

 which looks promising.  In the code below, however, there's only one
 IORef, so either the entire table gets garbage collected or none of it
 does.

 I've been reading the paper Stretching the storage manager: weak
 pointers and stable names in Haskell, which seems to answer my
 question.  When I attempt to run the memoization code in the paper on
 the simple fib example, I find that -- apparently due to lazy
 evaluation -- no new entries are entered into the lookup table, and
 therefore no lookups are ever successful!

 So apparently there is some interaction between lazy evaluation and
 garbage collection that I don't understand.  My head hurts.  Is it
 necessary to make the table lookup operation strict?  Or is it
 something entirely different that I am missing?

 -Rod


 On Thu, 10 Sep 2009 18:33:47 -0700
 Ryan Ingram ryani.s...@gmail.com wrote:

 
  memoIO :: Ord a = (a - b) - IO (a - IO b)
  memoIO f = do
 cache - newIORef M.empty
 return $ \x - do
 m - readIORef cache
 case M.lookup x m of
 Just y - return y
 Nothing - do let res = f x
   writeIORef cache $ M.insert x res m
   return res
 
  memo :: Ord a = (a - b) - (a - b)
  memo f = unsafePerformIO $ do
  fmemo - memoIO f
  return (unsafePerformIO . fmemo)
 
  I don't think there is any valid transformation that breaks this,
  since the compiler can't lift anything through unsafePerformIO.  Am I
  mistaken?
 
-- ryan

 ___
 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] 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 as possible into the class. Then I would like to
include properties in the class such as commutativity something like:
infixl 5 `com`
com :: Int - Int - Int
x `com` y  = (x + y)
commutative com a b = (a `com` b) == (b `com` a)

I seem to be able to include just one default equation the Peano2 attempt.
Any ideas?
I have looked at
http://www.haskell.org/haskellwiki/Peano_numbers

Regards,
Pat

-- Attempt 1
-- In this attempt the axioms are in the instance and things seem OK
module Peano1 where
infixl 6 `eq`
infixl 5 `plus`

class Peano1 n where
 suc :: n - n
 eq :: n - n - Bool
 plus :: n - n - n

data Nat = One | Suc Nat deriving Show


instance  Peano1 Nat where
 suc = Suc
 One `eq` One = True
 (Suc m) `eq` (Suc n) =  m `eq` n
 _`eq`_  = False
 m `plus` One = Suc m
 m `plus` (Suc n) = Suc (m `plus` n)
-- Evaluation *Peano1 Suc(One) `plus` ( Suc (One))





-- Attempt 2
-- In this attempt the axioms are in the class and things are not OK.
module Peano2 where
infixl 6 `eq`
infixl 5 `plus`

class Peano2 n where
  one :: n
  eq :: n - n - Bool
  plus :: n - n - n
  suc :: n - n
  suc a = a `plus` one

{-
 I cannot add the remaining default axioms
  one `eq` one = True
  (suc m) `eq` (suc n) =  m `eq` n
  (suc a) `eq` (suc b) =  a `eq` b
  _`eq`_  = False
-}

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


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 laziness to avoid
reading the body.

 Still, ByteStrings are probably the better choice (if you want the body and 
 that can be
 large).

That's not a problem by now.

 To avoid reading the body without unsafePerformIO:

 readBit fn
    = Control.Exception.bracket (openFile fn ReadMode) hClose
          (\h - do
                l - hGetLine h
                let i = read l
                bdy - hGetContents h
                return $ Bit i bdy)

Same problem with the withFile-version: nothing gets printed if I
try to print out the body: that's way I used seq.

I'm starting to think that the only way to do this without using
unsafePerformIO is to have the body being an IO action: simply, under
Haskell assumption, that's not possible to write, because Haskell
enforce safety above all.

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


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 defined the Eq instances
separately:

class (Eq n) = Peano2 n where
 one :: n
 plus :: n - n - n
 suc :: n - n
 suc a = a `plus` one

- Job

On Thu, Sep 17, 2009 at 2:36 PM, pat browne patrick.bro...@comp.dit.iewrote:

 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 as possible into the class. Then I would like to
 include properties in the class such as commutativity something like:
 infixl 5 `com`
 com :: Int - Int - Int
 x `com` y  = (x + y)
 commutative com a b = (a `com` b) == (b `com` a)

 I seem to be able to include just one default equation the Peano2 attempt.
 Any ideas?
 I have looked at
 http://www.haskell.org/haskellwiki/Peano_numbers

 Regards,
 Pat

 -- Attempt 1
 -- In this attempt the axioms are in the instance and things seem OK
 module Peano1 where
 infixl 6 `eq`
 infixl 5 `plus`

 class Peano1 n where
  suc :: n - n
  eq :: n - n - Bool
  plus :: n - n - n

 data Nat = One | Suc Nat deriving Show


 instance  Peano1 Nat where
  suc = Suc
  One `eq` One = True
  (Suc m) `eq` (Suc n) =  m `eq` n
  _`eq`_  = False
  m `plus` One = Suc m
  m `plus` (Suc n) = Suc (m `plus` n)
 -- Evaluation *Peano1 Suc(One) `plus` ( Suc (One))





 -- Attempt 2
 -- In this attempt the axioms are in the class and things are not OK.
 module Peano2 where
 infixl 6 `eq`
 infixl 5 `plus`

 class Peano2 n where
  one :: n
  eq :: n - n - Bool
  plus :: n - n - n
  suc :: n - n
  suc a = a `plus` one

 {-
  I cannot add the remaining default axioms
  one `eq` one = True
  (suc m) `eq` (suc n) =  m `eq` n
  (suc a) `eq` (suc b) =  a `eq` b
  _`eq`_  = False
 -}

 ___
 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] 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 a little of
Haskell's
type classes http://en.wikipedia.org/wiki/Type_class. In general, movement
away from inheritance is good. The proposal, however, feels a bit like
looking for the lost quarter where the light is good, rather than where you
lost it. Before considering delegation machinery, let's consider the
*value*of an interface. How many interfaces are there? One way to see
that is just
to consider all the sub interfaces of a single interface with n methods on
it. Hmmm... that's 2^n interfaces. That's a lot. Does that give us any
confidence that any one way of carving up functionality via interfaces is
going to be sane? Further, in practice, do we see random distribution
through this very large space?

What we see over and over again in practice is that the answer to these
questions is 'no!'. That means that there is *something* that binds a
collection of methods together. What might that something be? One place to
look is mathematics. Which maths should we look at? The maths of category
has been very fruitful both in explaining existing functional programming
techniques and -- perhaps more importantly -- suggesting ways to improve
them as well as wholly new techniques. What we find in category theory is
that it is natural to collect maps (read functions) together. A good example
of such a beast is a monad. A monad -- viewed categorically -- is

   - a map, T, taking types to new types and functions on those types to new
   functions. Let's call the universe of types and functions expressible in our
   model of computation (as proscribed by our programming language), C. Then T
   : C - C.
   - a higher order map, unit. Just like T takes C to C, we can understand a
   noop like map that takes C to C, call it Id. Then unit : Id - T. We
   intuitively think about it as putting basic types inside the container T,
   but it's really a higher order map.
   - another higher order map, mult : T^2 - T. We talk about it as a kind
   of flattening (and in Scala it's called flatMap), but it's a higher order
   map.

Now, one is not finished spelling out a monad when giving this collection of
maps. One must also show that they satisfy certain constraints.

   - T is functorial, meaning T g f = T(g) T(f)
   - unit and mult are natural transformations, look up the meaning because
   unpacking it here would take to long
   - mult( mult T ) = mult( T mult )
   - mult( unit T ) = mult( T unit  )

This set of constraints must go with the monad. This example provides a
little more detail in terms of what binds a group of maps together, and
hence of what *might* replace the notion of interface and *explain* what we
see in practice. Good programmers invariably pick out just a few
factorizations of possible interfaces -- from the giant sea of
factorizations (read different ways to carve up the functionality). The
reason -- i submit -- is because in their minds there are some constraints
they know or at least intuit must hold -- but they have no good way at the
language level to express those constraints. A really practical language
should help the programmer by providing a way express and check the
constraints that hold amongst the maps in an interface.

i submit that this idea is not the same as design by contract. i am not
proposing an Eiffel-like mechanism. Again, taking a functional approach to
computation via category theory leads one towards modeling interfaces as
categorical situations like monads, comonads, distribution laws, etc. This
means that a large number of the constraints come down to

   - functoriality
   - naturality
   - coherence

Language support for this approach might include *keywords for these kinds
of assertions*. It is a gnarly beast to offer automatic and/or compiler
support for checking general constraints. Even this limited family of
constraints that i'm proposing can generate some very difficult
computations, with very bad complexity. However, for those situations where
a general purpose solution to check assertions of functoriality, naturality
and coherence are infeasible, one can use these hints to generate tests to
probe for possible failures. This idea follows the in the same spirit of
replacing proof with proof-checking.

Of course, this is not the only way to go. i've yet to be convinced that
category theory offers a good account of concurrency. Specifically,
categorical composition does not line up well with concurrent composition.
So, interfaces organized around types for concurrency is also something to
consider. In this case, one might find a natural beginning in interfaces in
which -- roughly speaking -- the methods constitute the tokens of a formal
language the constructors of which are 

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, sometimes don't.

The for the case of sorting by metadata was tacitly assumed :)

 But I want to use the same code for reading files and exploit laziness
 to avoid reading the body.

  Still, ByteStrings are probably the better choice (if you want the body
  and that can be large).

 That's not a problem by now.

  To avoid reading the body without unsafePerformIO:
 
  readBit fn
     = Control.Exception.bracket (openFile fn ReadMode) hClose
           (\h - do
                 l - hGetLine h
                 let i = read l
                 bdy - hGetContents h
                 return $ Bit i bdy)

 Same problem with the withFile-version: nothing gets printed if I
 try to print out the body: that's way I used seq.

Ah, yes. The file is closed too soon.

 I'm starting to think that the only way to do this without using
 unsafePerformIO is to have the body being an IO action: simply, under
 Haskell assumption, that's not possible to write, because Haskell
 enforce safety above all.

Well, what about

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
_ - 1000
bl - mapM readBit [file1.txt,file2.txt]
mapM_ (putStrLn . show . index) $ sortBy (comparing index) bl
mapM_ (putStrLn . take 20 . drop n . body) bl



./cparis3 30 +RTS -sstderr
2
3
CCGGGCGCGGTGGCTCACGC
CCGGGCGCGGTGGCTCACGC
 408,320 bytes allocated in the heap
   1,220 bytes copied during GC
  34,440 bytes maximum residency (1 sample(s))
  31,096 bytes maximum slop
   1 MB total memory in use (0 MB lost due to fragmentation)


./cparis3 2 +RTS -sstderr 
2 
3 
TTAGCCGGGCGTGGTG  
TTAGCCGGGCGTGGTG  
   1,069,168 bytes allocated in the heap  
 105,700 bytes copied during GC   
 137,356 bytes maximum residency (1 sample(s))
  27,344 bytes maximum slop   
   1 MB total memory in use (0 MB lost due to fragmentation)  

./cparis3 200 +RTS -sstderr
2
3
CCTGGCCAACATGGTGAAAC
CCTGGCCAACATGGTGAAAC
  80,939,296 bytes allocated in the heap
   8,925,240 bytes copied during GC
 137,056 bytes maximum residency (2 sample(s))
  45,528 bytes maximum slop
   2 MB total memory in use (0 MB lost due to fragmentation)

  %GC time  38.5%  (27.0% elapsed)

  Alloc rate1,264,577,704 bytes per MUT second

  Productivity  61.5% of total user, 38.8% of total elapsed

./cparis3 2000 +RTS -sstderr
2
3
CAGAGCGAGACTCCGTCTCA
CAGAGCGAGACTCCGTCTCA
 806,034,756 bytes allocated in the heap
  76,775,944 bytes copied during GC
 136,876 bytes maximum residency (2 sample(s))
  43,324 bytes maximum slop
   2 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:  1536 collections, 0 parallel,  0.35s,  0.35s elapsed
  Generation 1: 2 collections, 0 parallel,  0.00s,  0.00s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.53s  (  0.67s elapsed)
  GCtime0.35s  (  0.36s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time0.88s  (  1.02s elapsed)

  %GC time  40.0%  (34.9% elapsed)

  Alloc rate1,526,482,681 bytes per MUT second

  Productivity  60.0% of total user, 51.7% of total elapsed

Seems to work as desired.


 Cristiano

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


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
                _ - 1000
    bl - mapM readBit [file1.txt,file2.txt]
    mapM_ (putStrLn . show . index) $ sortBy (comparing index) bl
    mapM_ (putStrLn . take 20 . drop n . body) bl

Yes, it *seems* to work but... the files don't get closed (readFile is
unfinished until body is read) so I think I'm going to have problems
when the number of files to read is higher than the maximum number of
open handles a process can have.

That's a possibility I considered even if not directly using readFile.

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


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 Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 + can be introduced as defined function
symbols that do not add substantive information to the theory.  The
only axioms you want are the ones for equality.

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


[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 applications

Package agum 2.2 provides unification and matching in an Abelian
group, also know as AG-unification and matching.  The core computation
finds the integer solutions to inhomogeneous linear equations.  The
linear equation solver has been place in a separate module so it can
be used for other applications

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


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
     args - getArgs
     let n = case args of
                 (a:_) - read a
                 _ - 1000
     bl - mapM readBit [file1.txt,file2.txt]
     mapM_ (putStrLn . show . index) $ sortBy (comparing index) bl
     mapM_ (putStrLn . take 20 . drop n . body) bl

 Yes, it *seems* to work but... the files don't get closed (readFile is
 unfinished until body is read) so I think I'm going to have problems
 when the number of files to read is higher than the maximum number of
 open handles a process can have.

Indeed. If the number of files is large, reading lazily with readFile is not so 
good.
Eat the cake and have it.
If you have a lot of files, want to read the metadata of all, select a (much) 
smaller 
number of files by some criterion on the set of metadata and then read the body 
of the 
selected files, it's hairy.
Reading all bodies immediately is probably out due to memory restrictions.
The clean approach would be to separate the reading of metadata and body.
The drawback is that then you have a second entry into IO.
Using unsafePerformIO, you can pretend that you don't reenter IO.
Whether that is safe in your situation, I don't know. Probably not (rule of 
thumb: all 
nontrivial actions wrapped in unsafePerformIO aren't safe, though chances 
aren't bad that 
it works most of the time).


 That's a possibility I considered even if not directly using readFile.

 Cristiano

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


[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 x,int y);

/*some functions that use the structure*/
int use_foo(foo *f,int w);

/*a funtion that releases the memory*/
int destroy_foo(foo *f);

And I want to use it in haskell using FFI. I can create a .hsc file like
this:

{-# LANGUAGE CPP, ForeignFunctionInterface #-}

import Foreign
import Foreign.C.Types

#include foo.h

newtype Foo = Foo ()

foreign import ccall static foo.h create_foo
c_create_foo :: Ptr (Foo) - Ptr (CFile) - CInt - CInt - IO CInt

foreign import ccall static foo.h use_foo
c_use_foo :: Ptr (Foo) - CInt - IO CInt

foreign import ccall static foo.h destroy_foo
c_destroy_foo :: Ptr (Foo) - IO CInt

It compiles but I have no idea how to call c_create_foo and get back Foo
Any suggestions?

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


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 the tree is exponential; if I do, it's somewhere
between linear and quadratic.

Another process prunes parts of this graph structure as time goes on.
The entire data structure is intended to be persistent, lasting for
days at a time in a server-like application.  If the parts pruned
aren't garbage collected, the space leak will eventually be
catastrophic.  Either the memo table or the graph structure itself will
outgrow available memory.

-Rod


On Thu, 17 Sep 2009 13:32:13 -0400
Job Vranish jvran...@gmail.com wrote:

 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).
 
 For example with a naive fibs, the values you are passing in are
 computed, and probably don't exist before you do the recursive call,
 and then are discarded shortly afterward.
 
 It seems like putting a cap on the cache size, and then just
 overwriting old entries would be better.
 Am I missing something?
 
 - Job
 
 
 
 On Wed, Sep 16, 2009 at 4:48 PM, Rodney Price rodpr...@raytheon.com
 wrote:
 
  How does garbage collection work in an example like the one below?
  You memoize a function with some sort of lookup table, which stores
  function arguments as keys and function results as values.  As long
  as the function remains in scope, the keys in the lookup table
  remain in memory, which means that the keys themselves always
  remain reachable and they cannot be garbage collected.  Right?
 
  So what do you do in the case where you know that, after some
  period of time, some entries in the lookup table will never be
  accessed?  That is, there are no references to the keys for some
  entries remaining, except for the references in the lookup table
  itself.  You'd like to allow the memory occupied by the keys to be
  garbage collected.  Otherwise, if the function stays around for a
  long time, the size of the lookup table always grows.  How do you
  avoid the space leak?
 
  I notice that there is a function in Data.IORef,
 
  mkWeakIORef :: IORef a - IO () - IO (Weak (IORef a))
 
  which looks promising.  In the code below, however, there's only one
  IORef, so either the entire table gets garbage collected or none of
  it does.
 
  I've been reading the paper Stretching the storage manager: weak
  pointers and stable names in Haskell, which seems to answer my
  question.  When I attempt to run the memoization code in the paper
  on the simple fib example, I find that -- apparently due to lazy
  evaluation -- no new entries are entered into the lookup table, and
  therefore no lookups are ever successful!
 
  So apparently there is some interaction between lazy evaluation and
  garbage collection that I don't understand.  My head hurts.  Is it
  necessary to make the table lookup operation strict?  Or is it
  something entirely different that I am missing?
 
  -Rod
 
 
  On Thu, 10 Sep 2009 18:33:47 -0700
  Ryan Ingram ryani.s...@gmail.com wrote:
 
  
   memoIO :: Ord a = (a - b) - IO (a - IO b)
   memoIO f = do
  cache - newIORef M.empty
  return $ \x - do
  m - readIORef cache
  case M.lookup x m of
  Just y - return y
  Nothing - do let res = f x
writeIORef cache $ M.insert x res m
return res
  
   memo :: Ord a = (a - b) - (a - b)
   memo f = unsafePerformIO $ do
   fmemo - memoIO f
   return (unsafePerformIO . fmemo)
  
   I don't think there is any valid transformation that breaks this,
   since the compiler can't lift anything through unsafePerformIO.
   Am I mistaken?
  
 -- ryan
 
  ___
  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] 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 CInt
foreign import ccall static foo.h use_foo
c_use_foo :: Ptr (Foo) - CInt - IO CInt
foreign import ccall static foo.h destroy_foo
c_destroy_foo :: Ptr (Foo) - IO CInt


Your 'create_foo' is only an initialization function, i.e., it
initializes data in a Foo but do not allocate memory for the data
such pointer points to. So, what you would like to do is something
like this:

import Foreign.Marshall.Alloc

(...)
ptrFoo - malloc
c_create_foo ptrFoo ptrCFile (...)
(...)
free ptrFoo

Looking at malloc you see:

malloc :: Storable a = IO (Ptr a)

and this gives you the hint: you need to make an
instance of Storable class with your Foo type.
Storable method 'sizeOf' should provide the proper
size to be used in such kind of memory allocation.
(After that, you would probably want to learn
about ForeignPtr, which would call, say, free and
c_destroy_foo when your pointer is not beeing used
anymore.)

Best,
Maurício

P.S.: (Warning: spam promoting my own work.)

If you use my package bindings-common, available in hackage, you
can get that type and instance in a .hsc file by doing this:

#bindings_starttype struct foo
#bindings_stoptype _

But this package is not very popular yet, so
I can't guarantee it's bug free.

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


[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
   derived Eq

showOp :: Op - String
showOp And  = 
showOp Or   = |
showOp Implies  = =
showOp Equiv= =

instance Show Op where show = showOp

precList = [(And,4),(Or,3),(Implies,2),(Equiv,1)]
showProp :: Prop - String
showProp (Var s) = s
showProp (Negation p) = ~ ++ showProp p
showProp (BinOp op p q) = paren (showProp a p ++ space (showOp op) ++
showProp a q)

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 (showMinProp a p  ++ space (showOp op) ++ showMinProp a q)
 else paren (showMinProp a p ++ space (showOp op) ++ showMinProp a
q))

space s =   ++ s ++  
paren s = ( ++ s ++ )

instance Show Prop where show = showProp
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 (showMinProp a p  ++ space (showOp op) ++ showMinProp a q)
          else paren (showMinProp a p ++ space (showOp op) ++ showMinProp a q))

showMinProp preNo (BinOp op p q) =
let a = case op of
And - 4
 ...
in if a  preNo
then (...) else (...)

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


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 type, or types, to instantiate the
argument at


I can easily understand your explanation for test2: the type var a is
closed under existential (?) quantification. I can't do the same for
test1, even if it seems that a is closed under universal (?)
quantification as well.


It's not existential, it's rank-2 universal. The first function is 
saying that for every type, a, there is a function, te...@a, taking a 
into Int. This is very different than the second function which says 
there is a function, test2, taking values which belong to all types 
into Int. The test2 function is not polymorphic, instead it takes 
arguments which are polymorphic.


Since _|_ is the only inhabitant of all types, it may be helpful to 
consider these functions instead:


f :: forall a. (a - a) - Int
g :: (forall a. a - a) - Int

The function f takes a monomorphic function of type (a-a) for some 
predefined a. Which a? Well it can be any of them, but it can only be 
one of them at a time. That is, the invocation of f will make the a 
concrete.


The function g takes a polymorphic function which, being polymorphic, 
will work for every a. That is, the invocation of g does not make the 
type concrete; only the invocation of the argument within the body of g 
will make the type concrete. Moreover, the argument must be able to be 
made concrete for every a, it can't pick and choose. This is different 
from existential quantification which means the argument works for some 
a, but it won't tell us which one.


To put it another way, this is a valid definition of g:

(\ r - let _ = r Nothing ; _ r hello in 42)

Since r is polymorphic, we can use it at two different types. Whereas if 
we gave this definition for f it wouldn't type check since we can't 
unify (Maybe a) and String.




Or, to put it another way, since there are no non-bottom objects of type
(forall a. a):


Why?


By definition of Haskell semantics. The only value belonging to all 
types is _|_ (whether undefined or various exception bottoms).


Perhaps it'd make more sense to look at another type. What values 
inhabit (forall a. Maybe a)? Well _|_ inhabits all types, so it's there. 
And Nothing doesn't say anything about a, so it's there too since it 
works for all a. And (Just _|_) is there since Just doesn't say anything 
about the type a and _|_ belongs to all types so it doesn't say anything 
about a either. And that's it. Any other value must say something about 
the type a, thus restricting it, and then it would no longer be 
universally quantified.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 - Formula - Formula
 ∀ = All

fine.  But then ghc complains.  What's going on here?

Thanks!

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


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:
 Invalid type signature

 In ghci I can do

  ∀ :: Var - Base - Formula - Formula
  ∀ = All

 fine.  But then ghc complains.  What's going on here?

Very odd:

GHCi, version 6.10.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Prelude let ∀ :: Int - Int - Int; ∀ x y = x*(y-x)

interactive:1:4: parse error on input `∀'
Prelude let (∀) :: Int - Int - Int; x ∀ y = x*(y-x)
Prelude 3 ∀ 5
6

Maybe your encodings aren't UTF8?


 Thanks!

 Sean

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


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,
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 - Formula - Formula
   ∀ = All
 
  fine.  But then ghc complains.  What's going on here?

 Very odd:

 GHCi, version 6.10.3: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 Prelude let ∀ :: Int - Int - Int; ∀ x y = x*(y-x)

 interactive:1:4: parse error on input `∀'
 Prelude let (∀) :: Int - Int - Int; x ∀ y = x*(y-x)
 Prelude 3 ∀ 5
 6

 Maybe your encodings aren't UTF8?

 
  Thanks!
 
  Sean


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


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

(∀) :: Int - Int - Int
x ∀ y = x*(y-x)
da...@linux-mkk1:~/Haskell/CafeTesting ghci Forall
GHCi, version 6.10.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Forall   ( Forall.hs, interpreted )
Ok, modules loaded: Forall.
*Forall 7 ∀ 4
-21
*Forall

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


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
committing genocide)

I wrote this function recently for a quick'n'dirty script:

 readFiles :: [FilePath] - String
 readFiles [] = return 
 readFiles (f:fs) = do
 f_data - readFile f
 rest - unsafeInterleaveIO (readFiles fs)
 return (f_data ++ rest)

It lazily reads from many files and concatenates all the input.  But I
probably wouldn't use it in a serious application.

  -- ryan

On Thu, Sep 17, 2009 at 3:41 PM, Daniel Fischer daniel.is.fisc...@web.dewrote:

 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
  args - getArgs
  let n = case args of
  (a:_) - read a
  _ - 1000
  bl - mapM readBit [file1.txt,file2.txt]
  mapM_ (putStrLn . show . index) $ sortBy (comparing index) bl
  mapM_ (putStrLn . take 20 . drop n . body) bl
 
  Yes, it *seems* to work but... the files don't get closed (readFile is
  unfinished until body is read) so I think I'm going to have problems
  when the number of files to read is higher than the maximum number of
  open handles a process can have.

 Indeed. If the number of files is large, reading lazily with readFile is
 not so good.
 Eat the cake and have it.
 If you have a lot of files, want to read the metadata of all, select a
 (much) smaller
 number of files by some criterion on the set of metadata and then read the
 body of the
 selected files, it's hairy.
 Reading all bodies immediately is probably out due to memory restrictions.
 The clean approach would be to separate the reading of metadata and body.
 The drawback is that then you have a second entry into IO.
 Using unsafePerformIO, you can pretend that you don't reenter IO.
 Whether that is safe in your situation, I don't know. Probably not (rule of
 thumb: all
 nontrivial actions wrapped in unsafePerformIO aren't safe, though chances
 aren't bad that
 it works most of the time).

 
  That's a possibility I considered even if not directly using readFile.
 
  Cristiano

 ___
 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] 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: [Haskell-beginners] map question
To: Gregory Propf gregorypr...@yahoo.com
Cc: Tom Doris tomdo...@gmail.com, Haskell-Cafe 
haskell-cafe@haskell.org, joostkrem...@fastmail.fm
Date: Thursday, September 17, 2009, 9:04 AM

(-) 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 ambiguity in common mathematical 
syntax. 

If you play around in ghci you should get the hang of it pretty quick.

- Job



On Thu, Sep 17, 2009 at 11:08 AM, Gregory Propf gregorypr...@yahoo.com wrote:


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: Re: [Haskell-beginners] map question
To: Joost Kremers joostkrem...@fastmail.fm

Cc: beginn...@haskell.org
Date: Thursday, September 17, 2009, 6:06 AM

This works:

map (+ (-1)) [1,2,3,4]



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]

[2,4,6,8]

Prelude map (/ 2) [1,2,3,4]

[0.5,1.0,1.5,2.0]

Prelude map (2 /) [1,2,3,4]

[2.0,1.0,0.,0.5]



But I can't seem to find a way to get map to substract 1 from all members of the

list. The following form is the only one that works, but it doesn't give the

result I'd expect:



Prelude map ((-) 1) [1,2,3,4]

[0,-1,-2,-3]



I know I can use an anonymous function, but I'm just trying to understand the

result here... I'd appreciate any hints to help me graps this.



TIA



Joost





--

Joost Kremers, PhD

University of Frankfurt

Institute for Cognitive Linguistics

Grüneburgplatz 1

60629 Frankfurt am Main, Germany

___

Beginners mailing list

beginn...@haskell.org

http://www.haskell.org/mailman/listinfo/beginners




-Inline Attachment Follows-

___
Beginners mailing list
beginn...@haskell.org

http://www.haskell.org/mailman/listinfo/beginners



  
___

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] 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]?

When in doubt, check citeseer.

http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.83.6505

Thank you; although attempting a download from the referenced
DOWNLOAD site at
http://citeseerx.ist.psu.edu/viewdoc/download;jsessionid=4185A586D773743C182087024049A81E?doi=10.1.1.83.6505rep=rep1type=urli=0
resulted in the same error as before, I was still able to download a
cached copy from the referenced CACHED site at
http://citeseerx.ist.psu.edu/viewdoc/download;jsessionid=4185A586D773743C182087024049A81E?doi=10.1.1.83.6505rep=rep1type=pdf;
that is a very useful service.

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
Furuike ya, kawazu tobikomu mizu no oto. 
-- Matsuo Basho^ 

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


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 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

 (∀) :: Int - Int - Int
 x ∀ y = x*(y-x)
 da...@linux-mkk1:~/Haskell/CafeTesting ghci Forall
 GHCi, version 6.10.3: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 [1 of 1] Compiling Forall   ( Forall.hs, interpreted )
 Ok, modules loaded: Forall.
 *Forall 7 ∀ 4
 -21
 *Forall

 Works here.

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


[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, so figure the actual compilation/link time is more like 15 to 30 
seconds. (This is Windows on a very old laptop.) I'm used to working in 
Python, so I'm used to a nearly instant code-build-test cycle, and GUI 
applications in PyQt run briskly, faster than ghci/qtHaskell.


Now I'm wondering if Hugs is a faster interpreter.

So during development I don't want to give up the quick cycle you get with 
an interpreter, but the application may be much too slow to use in any 
meaningful way without compilation. Any advice welcome. Maybe there is a 
way to speed up the interpretation.


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


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
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 difference between stealing cookies from the cookie jar and
 committing genocide)

I find that remark in rather bad taste.


 I wrote this function recently for a quick'n'dirty script:
  readFiles :: [FilePath] - String
  readFiles [] = return 
  readFiles (f:fs) = do
      f_data - readFile f
      rest - unsafeInterleaveIO (readFiles fs)
      return (f_data ++ rest)

 It lazily reads from many files and concatenates all the input.  But I
 probably wouldn't use it in a serious application.

   -- ryan

But that does something completely different from what Cristiano wants to do.
He wants to read many files files quasi-parallel.
As far as I can tell, he needs to read a small chunk from the beginning of 
every file, 
then, depending on what he got from that, he needs to read the rest of some 
files.
If he reads all the files lazily, he (maybe) runs into the open file limit (a 
semi-closed 
handle is still open from the OS' point of view, isn't it?).
So he has to close the first files before he opens the Nth.
But what if later he finds out that he has to read the body of a previously 
closed file?

I would separate the reading of headers and bodies, reopening the files whose 
body is 
needed, for some (maybe compelling) reason he wants to do it differently.

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


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 you're using built with split-objs?
If not, that would explain the long link time.

 that I can compile it much faster if I selectively import the needed
 modules, so figure the actual compilation/link time is more like 15 to 30
 seconds. (This is Windows on a very old laptop.) I'm used to working in
 Python, so I'm used to a nearly instant code-build-test cycle, and GUI
 applications in PyQt run briskly, faster than ghci/qtHaskell.

 Now I'm wondering if Hugs is a faster interpreter.

Usually it isn't. It's faster loading the code than ghci, but slower running it.


 So during development I don't want to give up the quick cycle you get with
 an interpreter, but the application may be much too slow to use in any
 meaningful way without compilation. Any advice welcome. Maybe there is a
 way to speed up the interpretation.

Smaller modules, so that only the hopefully few modules that were changed or 
depend on a 
changed module need be recompiled?
(Not sure that would help with linking, though)


 -Mike

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


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
  { int a = 3; ... } // except the type can be inferred

Note that the in is required unless part of a do-block, where block  
structure is implied.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 fast and only linking is slow, you may recompile
haskell modules every time but use ghci to omit linking. just execute ghc
compilation command inside ghci before running your app


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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