Re: [Haskell-cafe] Collection of sets containing no sets which are a subset of another in the collection

2009-11-14 Thread Max Rabkin
On Sat, Nov 14, 2009 at 9:21 AM, Mark Wassell mwass...@bigpond.net.au wrote:
 Hi,

 I am looking for a data structure that will represent a collection of sets
 such that no element in the collection is a subset of another set. In other
 words, inserting an element that is already a subset of another element will
 return the original collection, and inserting an element that is a superset
 of any elements will result in a collection with the superset added and the
 subsets removed.

I *think* what you're describing is a Union-Find structure. A
functional union-find structure is described in
http://www.lri.fr/~filliatr/ftp/publis/puf-wml07.ps (the language used
is OCaml, but if you have any difficulty translating it to Haskell I'm
sure this list will offer its help).

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


[Haskell-cafe] Lexical Syntax and Unicode

2009-11-14 Thread Manlio Perillo
Hi.

Reading the Haskell 98 Report (section 9.2), I have found a possible
problem.

The lexical syntax supports Unicode, however this is not true for the
newline:

newline - return linefeed | return | linefeed | formfeed


The Unicode standard adds two additional characters:

U+2028 LINE SEPARATOR
U+2029 PARAGRAPH SEPARATOR

The Unicode Character Database, also defines two general categories:
Zl = Separator, line
Zp = Separator, paragraph

The Zl category only contains the LINE SEPARATOR character and the Zp
category only contains the PARAGRAPH SEPARATOR character.


So, IMHO, the lexical syntax should be changed in :

newline - return linefeed | return | linefeed | formfeed
   | uniLine | uniPara
uniLine - any Unicode character defined as line separator
uniPara - any Unicode character defined as paragraph separator

or, alternatively:

uniLine - LINE SEPARATOR
uniPara - PARAGRAPH SEPARATOR



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


Re: [Haskell-cafe] Opinion about JHC

2009-11-14 Thread Henning Thielemann


On Fri, 13 Nov 2009, John Meacham wrote:


On Fri, Nov 13, 2009 at 08:55:51PM +, Lennart Augustsson wrote:

That was indeed my point.  Since a compiler is a substantial program I
would have more confidence it a compiler that is self-hosting.
Surely you must have tried?


No, there are extensions that I use in jhc's code base that jhc itself
does not support yet (fundeps for instance).


Maybe you can skip fundeps and move to Type families immediately.

Although said extensions would be nice and are on the list of things to 
add to jhc, there are other tasks that are more important. I write a lot 
of code in Haskell, so getting jhc to compile in jhc isn't much more 
important than getting any of the other projects I work on to compile in 
it and I prioritize accordingly. I am all about variety in the tools I 
use. I never understood the desire to have it be self-hosting, I mean, 
sure it is a nice abstract goal, but there are things with concrete 
benefits that are more important to jhc right now. (of course, 
priorities change over time.)


A JHC compiled JHC might be faster and noticeably smaller? My current jhc 
executable is 15 MB.

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


[Haskell-cafe] Some thoughts about Hackage

2009-11-14 Thread Vasyl Pasternak
Hi,

Yesterday Max complained about documentation for many Haskell modules.
But I found another similar problem with Hackage.

Before coding some Haskell program I try to find most appropriate
libraries, which help me to do task more efficiently. But the problem,
that there are to many libraries with similar functionality (for
example - networking, web servers etc.). And to find the best solution
is not so obvious.

My idea is to improve Hackage to help everyone with package selecting.
I propose the following:

- add download counter for each package, it could show how popular the
package is

- allow registered users set the quality mark of the package (from 1
to 5) and show the average mark of each packet

- add counter which shows how many packages depend on this package
(direct/indirect)

- create an aggregate package rank (a function on previous three
values), similar to Google's PageRank, i. e. rank of the package is
proportional to the package mark and weighted rank of dependent
packages

- allow comments on the package page, so anyone could tell its opinion
or other useful info for this package. All messages should be
delivered to the maintainer. This is useful, because it could speedup
the feedback on the packages, and also could form large knowledge base
on each package. Now everyone, who wants to read more about some
package should use Google to extract info from HaskellWiki,
Haskell-Cafe or hundreds of blog posts from different authors.

What do you think ?

Best regards,
Vasyl Pasternak
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell-src-exts Question

2009-11-14 Thread Neil Mitchell
Hi

Adding brackets that MUST have been there, by default, sounds like a
great idea. The alternative is getting it wrong, so I think that's
very safe.

Adding brackets that MIGHT have been there is a lot less clear cut.
One important consideration is that the fixities you
parse/pretty-print with might be wrong, so it has to be sensitive to
that. You have the options:

* Always do it (but then you get way too many brackets, and in the
case where you mis-guess the fixities, you break the code)
* Do it based on a table of fixities (might work if the parser
fixities match the pretty-printer fixities, but could go wrong)
* Annotate operators with fixities (this seems really wrong, and
suffers from incorrect guessed fixities very badly)
* Never do it

My preference would be:

-- put in enough brackets based on a fixities
ensureEnoughBrackets :: [Fixities] - a - a

prettyPrint = show . ensureEnoughBrackets []

Always do the safe brackets, if people want to do a table-of-fixities
approach they can easily do so. Also by putting this code in the
pretty printer it's harder to reuse if you want to write a custom
pretty print or similar - ensureEnoughBrackets may be independently
useful.

Thanks

Neil


 To do it minimally yes, but correctly? In the AST you've got

 InfixApp Exp QOp Exp

 so we know the tree structure, we just can't insert minimal brackets
 without knowing the fixity.

 However, that doesn't mean we can't do better than what it is now, but
 be conservative about it. Only insert brackets where it's clear that
 brackets must be inserted, which would be the case for Dominic's
 example. If the argument to an application is non-atomic, it needs
 brackets, there's nothing ambiguous about that. Nothing can be said so
 categorically for infix applications, so there we should assume that
 the fixities are already done in the correct way, or that brackets are
 inserted manually where needed.

 Does that sound reasonable?

Yes - that seems perfectly sensible.

 The suggestion is to move to a safe/correct by default where brackets
 are inserted to preserve the tree structure of infix expressions. The
 problem then becomes, what if we want to have the minimal (or pleasing
 not-quite-minimal) number of brackets.

 Right?

 If I've understood right, then yes I think making the pretty printing
 right by default is a good idea, and then for the users/applications
 where optimising for fewer brackets is important, it should be a little
 extra work to supply the necessary information.

 Perhaps like the ParseMode has fixities :: [Fixity], give the PPHsMode
 the same (partial) fixities environment. For operators not in the
 environment we fall back to using brackets all the time, but for known
 operators we can the use minimal bracketing.

 Another option I suppose would be to annotate the QOp used in InfixApp
 with a Maybe fixity. The parser would annotate these when it knows them
 from its fixities env in the ParseMode. For ASTs constructed manually
 the user would add them if they know or care. If not, they just get
 slightly more brackets than might strictly be necessary if the fixity
 were known.

 Duncan


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


Re: [Haskell-cafe] Some thoughts about Hackage

2009-11-14 Thread Andrew Coppin

Vasyl Pasternak wrote:

Before coding some Haskell program I try to find most appropriate
libraries, which help me to do task more efficiently. But the problem,
that there are to many libraries with similar functionality (for
example - networking, web servers etc.). And to find the best solution
is not so obvious.
  


I agree. (Have you seen how many binary packages there are??)

Some people seem to think having dozens of libraries for the same task 
is an advantage because it lets the libraries compete against each 
other and the best one will win. However, I don't think this is the case 
if it's too difficult to tell the libraries apart.



- allow comments on the package page, so anyone could tell its opinion
or other useful info for this package.

What do you think ?
  


I think this last idea is the best.

Adding a ranking is nice, but a comment lets people add highly relevant 
information like this package is good, but doesn't work properly with 
Unicode and so forth. Stuff somebody about to try using the package 
would *really* want to know.


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


Re: [Haskell-cafe] Re: Writing great documentation[MESSAGE NOT SCANNED]

2009-11-14 Thread John O'Donnell

I agree with Duncan's comment:

I rather like the idea of using markdown (pandoc) for separate
non-reference docs like man pages, tutorials, user guides etc rather
than trying to make haddock do everything.



In one of my projects (Hydra and Sigma), I use pandoc for the bulk of 
the documentation, and integrate this with haddock documentation for the 
parts of the documentation that haddock can do (which is a small part of 
it).  This is all coordinated by a (rather clunky) Setup.hs.  The whole 
thing isn't very elegant, but it works robustly on both Linux and 
Windows.  That's a big advantage of pandoc: you can install it with 
cabal and use it in your Setup, so it isn't necessary to do any shell 
scripting, which can cause portability problems.  I'll attach the 
Setup.hs file.


One of the central issues here is *where* the documentation files go.  I 
don't like the existing situation, where haddock documentation goes into 
a standard place, and presumably other documentation goes somewhere 
else.  It's surely better to have all the documentation for a package in 
one directory, with all the parts linked together.  So my setup makes a 
directory, builds the haddock and pandoc pieces of the documentation, 
copies (or build)  it all into the directory, and then the contents of 
this directory is listed under data-files in the cabal file.  The result 
is that building the system produces a complete self-contained directory 
and the executable application is able to find its own documentation 
files.  This is usful in a GUI program, for example, where it's nice to 
make the documentation availble under the Help menu.


Something along these lines (with a cleaner design) would be generally 
useful.


John O'Donnell



On 11/13/2009 10:31 PM, Duncan Coutts wrote:

On Fri, 2009-11-13 at 23:20 +0200, Max Rabkin wrote:


On Fri, Nov 13, 2009 at 10:58 PM, Simon Michaelsi...@joyful.com  wrote:


A very common problem with online docs is fragmentation.


Absolutely! Is it possible to include non-haddock documentation in a
cabal package. Is it possible to have it readable on Hackage?


Not yet.

Want to volunteer?

http://hackage.haskell.org/trac/hackage/ticket/330

It's partly a matter of tasteful design and partly implementation. The
same person/people do not need to do both bits. Thrashing out a detailed
and workable design would get us most of the way there.



I think this would help with the fragmentation and versioning issues.


Yes, I agree.



One option is to have haddock-only modules for non-reference
documentation (xmonad-contrib does this), and I think at the moment it
is a good option, but it does have disadvantages. It may not be clear
from the outline where documentation can be found, and it clutters up
the module namespace. Perhaps we could add support for a
Documentation-Modules field in cabal files, which would separate these
modules in the outline, and not install them but only their
documentation.


I rather like the idea of using markdown (pandoc) for separate
non-reference docs like man pages, tutorials, user guides etc rather
than trying to make haddock do everything.

Duncan

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




import Distribution.Simple
import System.Directory
import System.FilePath
import Text.Pandoc
import Text.Pandoc.Shared
import qualified System.IO.UTF8 as U

-- To do:

main = defaultMainWithHooks hooks

hooks :: UserHooks
hooks = simpleUserHooks {postBuild = postBuildHook}



{- Haddock creates its documentation in the form of a set of files in
dist/doc/html/Hydra.  These files have names matching *.html, *.gif,
*.css, *.js, Hydra.haddock.  After running haddock, we have:

  dist/doc/html/Hydra/(files created by Haddock)

Hydra has much more extensive documentation, produced by pandoc from
sources in doc.  The top level file in this is index.html.  To avoid
conflicts between the primary Hydra documentation and the API
documentation from haddock, the following steps are taken:

  1. A list of files in dist/doc/html/Hydra/ is created,
 and named haddock_files

  2. A directory dist/doc/html/Hydra/haddock is created

  3. All the files in dist/doc/html/Hydra[haddock_files] are copied to
 dist/doc/html/Hydra/haddock

  4. All the files in dist/doc/html/Hydra[haddock_files] are removed

  5. Pandoc is run on the documentation source files, with the results
 placed in dist/doc/html/Hydra.  These files contain relative
 pointers (URLs) into the haddock documentation.

The result is a documentation directory in the same place Cabal
expects to find it --- dist/doc/html/Hydra --- which contains the
Hydra documentation as well as the API reference produced by haddock.

 -}



{- The csslink string is html to be 

Re: [Haskell-cafe] Some thoughts about Hackage

2009-11-14 Thread Felipe Lessa
On Sat, Nov 14, 2009 at 11:32:33AM +, Andrew Coppin wrote:
 Adding a ranking is nice, but a comment lets people add highly
 relevant information like this package is good, but doesn't work
 properly with Unicode and so forth. Stuff somebody about to try
 using the package would *really* want to know.

Probably adding markers to the comment area every time a new
version is added is also a nice idea because a problem in the
comment are may be corrected.  The marker would serve as a visual
aid that the comment may be outdated.

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


Re: [Haskell-cafe] Some thoughts about Hackage

2009-11-14 Thread Stephen Tetley
2009/11/14 Felipe Lessa felipe.le...@gmail.com:


 Probably adding markers to the comment area every time a new
 version is added is also a nice idea because a problem in the
 comment are may be corrected.  The marker would serve as a visual
 aid that the comment may be outdated.

It would be nice if you could see a changelog from a package's 'start'
page on the Hackage website.

Otherwise, don't Roel van Dijk's reverse dependencies give some of the
information - i.e. the 'social proof' that a package is used and
useful?

http://www.haskell.org/pipermail/haskell-cafe/2009-October/067765.html
http://bifunctor.homelinux.net/~roel/hackage/packages/hackage.html

As Hackage already has Haddock docs and source-code view, you can
easily scan a project to see if you like the code. Plus, the project's
Hackage start page tracks versions so you can judge the maintained
status of a project (some great packages 'just work' of course and
haven't needed updating e.g. wl-pprint). As the Hackage server builds
projects, you can tell to some degree that a project works or not
(include the usual caveats for Windows and Mac users at this
juncture)...


Slighty of topic - how does a package author remove or at mark least
deprecated their own package?


Best wishes

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


Re: [Haskell-cafe] Some thoughts about Hackage

2009-11-14 Thread Gwern Branwen
On Sat, Nov 14, 2009 at 7:21 AM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 2009/11/14 Felipe Lessa felipe.le...@gmail.com:


 Probably adding markers to the comment area every time a new
 version is added is also a nice idea because a problem in the
 comment are may be corrected.  The marker would serve as a visual
 aid that the comment may be outdated.

 It would be nice if you could see a changelog from a package's 'start'
 page on the Hackage website.

http://hackage.haskell.org/trac/hackage/ticket/299
http://hackage.haskell.org/trac/hackage/ticket/244

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


Re: [Haskell-cafe] Collection of sets containing no sets which are a subset of another in the collection

2009-11-14 Thread Gwern Branwen
On Sat, Nov 14, 2009 at 4:35 AM, Max Rabkin max.rab...@gmail.com wrote:
 On Sat, Nov 14, 2009 at 9:21 AM, Mark Wassell mwass...@bigpond.net.au wrote:
 Hi,

 I am looking for a data structure that will represent a collection of sets
 such that no element in the collection is a subset of another set. In other
 words, inserting an element that is already a subset of another element will
 return the original collection, and inserting an element that is a superset
 of any elements will result in a collection with the superset added and the
 subsets removed.

 I *think* what you're describing is a Union-Find structure. A
 functional union-find structure is described in
 http://www.lri.fr/~filliatr/ftp/publis/puf-wml07.ps (the language used
 is OCaml, but if you have any difficulty translating it to Haskell I'm
 sure this list will offer its help).

 --Max

http://hackage.haskell.org/package/union-find ?

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


Re: [Haskell-cafe] haskell-src-exts Question

2009-11-14 Thread Daniel Schüssler
Hi,

On Friday 13 November 2009 21:08:42 Neil Mitchell wrote:
 In HLint I have a bracketing module, which has served me well. Please
 take any ideas you need from it -
 http://community.haskell.org/~ndm/darcs/hlint/src/HSE/Bracket.hs . In
 particular, given a fully bracketed expression, I can call
 transformBracket to transform the expression, not caring about
 brackets, in a way that guarantees the right brackets are put back.
 There is also needBracket and isAtom which are very useful. If you
 call descendBi (transformBracket Just) it will automatically bracket
 your term as much as is necessary.
 

Funny, I did the opposite approach the other day (not saying either is better 
:)); that is: parenthesize everything while building the AST (with a wrapper 
for App) and then:

deparenthesize :: (Data a) = a - a
deparenthesize = everywhereBut isString (mkT goE `extT` goT) 

where

  isString x = typeOf x == typeOf (undefined :: String)

   

  goE (App (Paren (App e1 e2)) e3)  = 
  (App (App e1 e2) e3)
  
  goE (Paren (Paren e)) = Paren e
  

  goE (InfixApp e1 op'' (Paren (InfixApp e2 op' e3))) 
  | op'' == op'
  , knownAssociative op''

  = InfixApp e1 op'' (InfixApp e2 op' e3)

  goE (InfixApp (Paren (InfixApp e1 op'' e2)) op' e3) 
  | op'' == op'
  , knownAssociative op''

  = InfixApp (InfixApp e1 op'' e2) op' e3
  
  goE x = x
  
  
  goT (TyApp (TyParen (TyApp t1 t2)) t3)  = 
  (TyApp (TyApp t1 t2) t3)

  -- add rule for function types too
  
  goT (TyParen (TyParen t)) = TyParen t
  
  goT x = x
  

  knownAssociative x = x `elem` [QVarOp (UnQual (Symbol .))]


Though the infix thing doesn't quite work; apparently they still get printed 
with parens even if there are no parens in the AST? Or the rule just didn't 
match for some reason...

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


[Haskell-cafe] How much time until dependencies are rebuilt in hackage?

2009-11-14 Thread Maurí­cio CA

Suppose package B depends on A. If a new
version of A is uploaded to hackage, how much
later package B will be rebuilt (either to show
a problem with the new version or to solve a
problem with a previous version of A)?

Thanks,
Maurício

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


Re: [Haskell-cafe] What does the `forall` mean ?

2009-11-14 Thread Mark Lentczner
On Nov 12, 2009, at 2:59 PM, Sean Leather wrote:
   foo :: forall x y. (x - x) - y
   bar :: forall y. (forall x . x - x) - y
 
 While neither function is seemingly useful, the second says that the 
 higher-order argument must be polymorphic. I see two options:

AHA! This is the bit of insight I needed! My confusion over forall was I 
thought that I understood that all Haskell types were as if there was a forall 
for all free type variables in front of the expression. For example, I think 
the following are the same:

fizz :: a - String - [a]
fizz :: forall a. a - String - [a]

So why would you need forall? The example Sean explained is that if you want to 
control the scope of the existential quantification. And you can only push the 
scope inward, since the outer most scope basically foralls all the free type 
variables (after type inference, I suppose.)

I also think I understand that the implicit 'forall' inherent in Haskell falls 
at different places in various constructs, which also had me confused. For 
example, while the above two function type declarations are equivalent, these 
two data declarations aren't:

data Fizzle a = Fizzle (b - (a, b)) a
data Fizzle a = forall b. Fizzle (b - (a, b)) a

This would be because the implicit 'forall' is essentially to the left of the 
'data Fizzle a' section. I'm guessing that the same holds true for type and 
newtype constructs.

Have I got this all correct?

Would I be correct in thinking: The difference between these two is that the 
type b can be fixed upon application of amy to the first two arguments (given 
context), whereas bob applied to two arguments MUST return a function that is 
applicable to every type.

amy :: Int - a - b - [Either a b]
bob :: Int - a - (forall b. b) - [Either a b]

Thanks for helping me understand...
- Mark

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


Re: [Haskell-cafe] haskell-src-exts Question

2009-11-14 Thread Neil Mitchell
Hi Daniel,

 Funny, I did the opposite approach the other day (not saying either is better
 :)); that is: parenthesize everything while building the AST (with a wrapper
 for App) and then:

I have utilities in HLint for that too - but I don't want to remove
users brackets automatically :-)

Btw, if you use uniplate you might find your code goes faster, and is simpler:

deparenthesize :: (Data a) = a - a
deparenthesize = transformBi goT . transformBi goT
    where

(the rest exactly as before, but skipping isString)

I always use Uniplate when working with HSE - they go great together
(do import Data.Generics.PlateData, and you don't need any extra
instances or anything)

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


[Haskell-cafe] Where is a good place to place code like this, so if I may be so bold, people can learn from it?

2009-11-14 Thread Casey Hawthorne
Where is a good place to place code like this, so if I may be so bold,
people can learn from it?


{- Author Modifications:Casey Hawthorne
   Author Original: Jeff Newbern
   Maintainer: Casey Hawthorne cas...@istar.ca
   Maintainer?: Jeff Newbern jnewb...@nomaware.com   
   Time-stamp: Jeff Tue Aug 19 09:31:32 2003
   Time-stamp: Casey Sat Nov 14 10:10 2009
   License:GPL
   
   The N-queens puzzle is to place N queens on an N by N chess board
   so that no queen can attack another one.
   
   Compiler Flags: ghc -O2 -fvia-c --make N-Queens.hs
   
   Description
   http://www.haskell.org/all_about_monads/html/stacking.html#example
   
   Original Code
   http://www.haskell.org/all_about_monads/examples/example25.hs
-}

{- Description

Example 25 - Using the StateT monad transformer
 with the List monad to achieve non-deterministic
 stateful computations, and the Writer monad to
 do logging

Usage: Compile the code and run it with an argument between 1 and 8.
   It will print a solution to the N-queens puzzle along with
   a log of the number of choices it had at each step.
   
   The N-queens puzzle is to place N queens on a chess board
   so that no queen can attack another one.  The original version
always used an 8x8 board.
   
Try: ./ex25 8
 ./ex25 1
 ./ex25 7
 

Added by Casey:
- different board sizes
-- up to a maximum 26x26 square board
- updated imports list

-}


import IO
import System
import Monad
import Data.Maybe
import Data.List
import Data.Char (toLower)
import Control.Monad.State
import Control.Monad.Writer


-- describe Chess Units and positions

type Rank = Int

data File = A | B | C | D | E | F | G | H | I | J | K | L | M | N | O
| P | Q | R | S | T | U | V | X | Y | Z
deriving (Eq, Show, Ord, Enum)

data Position = Pos {file::File, rank::Rank}
deriving Eq

instance Show Position where
show (Pos f r) = (map toLower (show f)) ++ (show r)

instance Ord Position where
compare p1 p2 = 
case (rank p1) `compare` (rank p2) of
LT - GT
GT - LT
_  - (file p1) `compare` (file p2)

data Kind = Pawn | Knight | Bishop | Rook | Queen | King
deriving (Eq, Ord, Enum)

instance Show Kind where
show Pawn   = P
show Knight = N
show Bishop = B
show Rook   = R
show Queen  = Q
show King   = K

data Color = Black | White
deriving (Eq, Ord, Enum)

instance Show Color where
show Black = b
show White = w

data Unit = Unit {color::Color, kind::Kind}
deriving (Eq, Ord)

instance Show Unit where
show (Unit c k) = ((show c) ++ (show k))

data Board = Board {size::Int, psns::[(Unit,Position)]}
-- newtype Board = Board [(Unit,Position)]

-- newtype BoardMax = BoardMax Int

instance Show Board where
show (Board n ps) = 
let ordered = (sort . swap) ps
ranks   = map (showRank ordered) [n,(n-1)..1]
board   = intersperse 
(concat (take n (repeat --+))) ranks
rlabels = intersperse(map (\n-(twoSpaces n)++
) [n,(n-1)..1])
flabels =  take (n*3)   a  b  c  d  e  f  g  h  i  j
k  l  m  n  o  p  q  r  s  t  u  v  w  x  y  z
twoSpaces n
| length (show n) == 2  = show n
| otherwise =   ++ (show n)
in unlines $ zipWith (++) rlabels board ++ [flabels]
where 
swap = map (\(a,b)-(b,a))
showRank ps  r =let rnk = filter (\(p,_)-(rank p)==r)
ps
cs  = map (showUnit rnk) (take n
[A .. Z])
in concat (intersperse | cs)
showUnit ps f = maybe(show . snd) (find
(\(p,_)-(file p)==f) ps)

data Diagonal = Ascending Position | Descending Position
deriving (Eq, Show)

-- define the diagonal according to its interesction with rank 1 or
size of board)
-- or with file a
normalize :: Int - Diagonal - Diagonal
normalize n d@(Ascending psn)
| (rank psn) == 1   = d
| (file psn) == A   = d
| otherwise = normalize n (Ascending (Pos (pred
(file psn)) ((rank psn)-1)))
normalize n d@(Descending psn)
| (rank psn) == n   = d
| (file psn) == A   = d
| otherwise = normalize n (Descending (Pos (pred
(file psn)) ((rank psn)+1)))

-- get the diagonals corresponding to a location on the board
getDiags :: Int - Position - (Diagonal,Diagonal)
getDiags n p = (normalize n (Ascending p), normalize n (Descending p))

-- this is the type of our problem description
data NQueensProblem = NQP {board::Board,
   ranks::[Rank],
   files::[File],
   asc::[Diagonal], 
   desc::[Diagonal]}
   
-- initial state = empty board, all ranks, files, and diagonals free

[Haskell-cafe] Some help needed to start Haskell with Yi

2009-11-14 Thread Jaco van Iterson
Hi there

I'm new to Haskell and need some help to get started faster (busy busy
busy).
I like to adjust and extend an editor to my liking and I choose Yi.

Only installation with 'cabal install yi' in a Cygwin shell under MS Windows
XP ended in:
Yi\Prelude.hs:182:9:
Duplicate instance declarations:
  instance Category Accessor.T -- Defined at Yi\Prelude.hs:182:9-38
  instance Category Accessor.T
-- Defined in data-accessor-0.2.1:Data.Accessor.Private
cabal.exe: Error: some packages failed to install:
yi-0.6.1 failed during the building phase. The exception was:
exit: ExitFailure 1

:(

Seems easy to fix but I can't even find where on my drive I can find the
source code.

Where is the source?

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


Re: [Haskell-cafe] Where is a good place to place code like this, so if I may be so bold, people can learn from it?

2009-11-14 Thread Bulat Ziganshin
Hello Casey,

Saturday, November 14, 2009, 9:15:51 PM, you wrote:

 Where is a good place to place code like this, so if I may be so bold,
 people can learn from it?

the solution i've seen in 80's was:

main = print (solutions 8 8)

solutions n 0 = [[]]
solutions n k = [(i,k):xs | xs - solutions n (k-1), i - [1..n], check i k xs]

check i k xs = and [i1/=i  k1/=k  abs(i1-i)/=abs(k1-k)  |  (i1,k1) - xs]


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

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


Re: [Haskell-cafe] Where is a good place to place code like this, so if I may be so bold, people can learn from it?

2009-11-14 Thread Casey Hawthorne
Hi Bulat:

I believe Jeff's original idea was to show an example of a monad
transformer stack and ASCII art output.


On Sat, 14 Nov 2009 21:42:01 +0300, you wrote:

Hello Casey,

Saturday, November 14, 2009, 9:15:51 PM, you wrote:

 Where is a good place to place code like this, so if I may be so bold,
 people can learn from it?

the solution i've seen in 80's was:

main = print (solutions 8 8)

solutions n 0 = [[]]
solutions n k = [(i,k):xs | xs - solutions n (k-1), i - [1..n], check i k xs]

check i k xs = and [i1/=i  k1/=k  abs(i1-i)/=abs(k1-k)  |  (i1,k1) - xs]
--
Regards,
Casey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type-indexed expressions with fixpoint

2009-11-14 Thread pbrowne
o...@okmij.org wrote:
 Brent Yorgey wrote:
 
 John Reynolds showed long ago that any higher-order language can be
 encoded in first-order. We witness this every day: higher-order
 language like Haskell is encoded in first-order language (machine
 code). The trick is just to add a layer of interpretive overhead -- I
 mean, a layer of interpretation. The closure conversion on type level
 was shown in
   http://okmij.org/ftp/Computation/lambda-calc.html#haskell-type-level
 
Brent,
Do you have the reference for Reynolds higher-order to first-order encoding.

Regards,
Pat

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


Re: [Haskell-cafe] Collection of sets containing no sets which are a subset of another in the collection

2009-11-14 Thread Felipe Lessa
On Sat, Nov 14, 2009 at 09:13:48AM -0500, Gwern Branwen wrote:
 http://hackage.haskell.org/package/union-find ?

This one is ephemeral, not persistant.

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


Re: [Haskell-cafe] How much time until dependencies are rebuilt in hackage?

2009-11-14 Thread Felipe Lessa
On Sat, Nov 14, 2009 at 01:47:04PM -0200, Maurí­cio CA wrote:
 Suppose package B depends on A. If a new
 version of A is uploaded to hackage, how much
 later package B will be rebuilt (either to show
 a problem with the new version or to solve a
 problem with a previous version of A)?

I would guess never, but don't quote me on that ;).

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


Re: [Haskell-cafe] ANN: hesql

2009-11-14 Thread Jake Wheat
Hello Christoph,

I've been working on a SQL parser
(http://hackage.haskell.org/package/hssqlppp) which might be useful
for your project, although it might be a bit heavy weight (its feature
scope getting more and more out of control...). Adding support for
parsing ? placeholder statements is on my todo list, I could bump it
up to the top if that would be useful to you.

Also, have you checked out MetaHDBC
(http://www.haskell.org/haskellwiki/MetaHDBC). I think it has similar
goals to your project.

2009/11/13 Colin Paul Adams co...@colina.demon.co.uk:
 Why would hesql be an improvement for me? It sounds like several steps 
 backwards?

The last few paragraphs on this page
http://lindstroem.wordpress.com/2008/09/18/metahdbc-paper-draft/
(comment dated November 4, 2008 at 9:31 pm, starting with 'Second,
MetaHDBC is a thin layer above a DBMS, as compared to ...') give some
reasons why an approach like this might sometimes be preferred to a
haskelldb-like approach, different situations can recommend one or the
other.

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


Re: [Haskell-cafe] Where is a good place to place code like this, so if I may be so bold, people can learn from it?

2009-11-14 Thread Gwern Branwen
On Sat, Nov 14, 2009 at 1:15 PM, Casey Hawthorne cas...@istar.ca wrote:
 Where is a good place to place code like this, so if I may be so bold,
 people can learn from it?

The Haskell wiki, I would suggest. If it were shorter and less
Haskell-specific, then maybe also Rosetta Code
(http://rosettacode.org/wiki/N-Queens#Haskell).

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


Re: [Haskell-cafe] Type-indexed expressions with fixpoint

2009-11-14 Thread Pierre-Evariste Dagand
 Do you have the reference for Reynolds higher-order to first-order encoding.

The reference discussed here is very likely to be:

Definitional Interpreters for Higher-Order Programming Languages
http://www.brics.dk/~hosc/local/HOSC-11-4-pp363-397.pdf

You might also be interested in:

Higher-order functions considered unnecessary for higher-order
programming, by Goguen
http://portal.acm.org/citation.cfm?id=119842

This technique is called defunctionalization, so you will probably
find other references under that name.


Regards,

-- 
Pierre-Evariste DAGAND
http://perso.eleves.bretagne.ens-cachan.fr/~dagand/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Little errors in number calculations

2009-11-14 Thread Abby Henríquez Tejera
Hi.

I've seen that in GHC sometimes there are little errors in some basic
number calculations:

*Prelude 123.35503 * 10.0
1233.55029

*Prelude properFraction 123.35503
(123,0.35502993)

whereas in Hugs no such errors seem to occur (that I have found, at
least):

*Hugs 123.35503 * 10.0
1233.5503

(but:)

*Hugs properFraction 123.35503
(123,0.3550299)

I understand that error may (and will) happen in floating point, but
it surprises me that they do so easily, and, above all, the difference
between GHC and Hugs. Does someone know why does this difference
occur?

(Thanks in advance, by the way :) ).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Little errors in number calculations

2009-11-14 Thread Bulat Ziganshin
Hello Abby,

Sunday, November 15, 2009, 12:00:42 AM, you wrote:

 I understand that error may (and will) happen in floating point, but
 it surprises me that they do so easily, and, above all, the difference
 between GHC and Hugs. Does someone know why does this difference
 occur?

compare:
0.3550299
0.35502993

hugs just prints one less digit

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

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


Re: [Haskell-cafe] Little errors in number calculations

2009-11-14 Thread Ross Paterson
On Sat, Nov 14, 2009 at 09:00:42PM +, Abby Henríquez Tejera wrote:
 I understand that error may (and will) happen in floating point, but
 it surprises me that they do so easily, and, above all, the difference
 between GHC and Hugs. Does someone know why does this difference
 occur?

The inaccuracy of floating point is the issue; it's just that Hugs
sometimes prints things with less precision than required by the Haskell
Report, and this can hide the errors.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Little errors in number calculations

2009-11-14 Thread Erik de Castro Lopo
Abby Henríquez Tejera wrote:

 I understand that error may (and will) happen in floating point,

Yes, explained here:

http://docs.sun.com/source/806-3568/ncg_goldberg.html

 but
 it surprises me that they do so easily, and, above all, the difference
 between GHC and Hugs. Does someone know why does this difference
 occur?

It looks like the two implementations just print floating  point
numbers with differing amounts of precision (or rather number of
digits).

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] attoparsec and parsec

2009-11-14 Thread Manlio Perillo
Hi.

I'm writing a generic log parsing package, and I'm serching a parser
combinators library.

Parsing log files is a simple task, so I would like to use the more
efficient solution.

I have looked at attoparsec source code, and it seems very specialized
for lazy bytestrings parsing, so I assume it is very efficient.

How stable is the attoparsec package?
How much more efficient is attoparsec than standard packages like parsec?

By the way: there seem to be problems with generated documentation in
http://hackage.haskell.org/package/attoparsec.

Moreover, there is a similar package:
http://hackage.haskell.org/package/bytestringparser

what is the status of this package?
It has the same API of attoparsec, but its older.
However there is no indication that this package is deprecated in favor
of attoparsec.



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


Re: [Haskell-cafe] What does the `forall` mean ?

2009-11-14 Thread Lennart Augustsson
Of the two declarations
data Fizzle a = Fizzle (b - (a, b)) a
data Fizzle a = forall b. Fizzle (b - (a, b)) a
only the second one is allowed (with some suitable extension).

Personally I think the first one should be allowed as well, with the
same meaning as the second one.
Some people thought it was to error prone not to have any indication
when an existential type is introduced,
so instead we are now stuck with a somewhat confusing keyword.

  -- Lennart

On Sat, Nov 14, 2009 at 4:55 PM, Mark Lentczner ma...@glyphic.com wrote:
 On Nov 12, 2009, at 2:59 PM, Sean Leather wrote:
   foo :: forall x y. (x - x) - y
   bar :: forall y. (forall x . x - x) - y

 While neither function is seemingly useful, the second says that the 
 higher-order argument must be polymorphic. I see two options:

 AHA! This is the bit of insight I needed! My confusion over forall was I 
 thought that I understood that all Haskell types were as if there was a 
 forall for all free type variables in front of the expression. For example, I 
 think the following are the same:

        fizz :: a - String - [a]
        fizz :: forall a. a - String - [a]

 So why would you need forall? The example Sean explained is that if you want 
 to control the scope of the existential quantification. And you can only 
 push the scope inward, since the outer most scope basically foralls all 
 the free type variables (after type inference, I suppose.)

 I also think I understand that the implicit 'forall' inherent in Haskell 
 falls at different places in various constructs, which also had me confused. 
 For example, while the above two function type declarations are equivalent, 
 these two data declarations aren't:

        data Fizzle a = Fizzle (b - (a, b)) a
        data Fizzle a = forall b. Fizzle (b - (a, b)) a

 This would be because the implicit 'forall' is essentially to the left of the 
 'data Fizzle a' section. I'm guessing that the same holds true for type and 
 newtype constructs.

 Have I got this all correct?

 Would I be correct in thinking: The difference between these two is that the 
 type b can be fixed upon application of amy to the first two arguments 
 (given context), whereas bob applied to two arguments MUST return a function 
 that is applicable to every type.

        amy :: Int - a - b - [Either a b]
        bob :: Int - a - (forall b. b) - [Either a b]

 Thanks for helping me understand...
        - Mark

 ___
 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] attoparsec and parsec

2009-11-14 Thread Jason Dusek
  To add to the confusion, I forked `bytestringparser` when I
  wrote the `json-b` package. The fork is here:

http://hackage.haskell.org/package/bytestringparser-temporary/

  I have added a number of things to original as well as fixing
  some problems with it.

  The reason I went with the older package is that the new one
  depended on stuff that wouldn't build on Hackage so I was like
  whatever; however, I now consider that it might have been
  better to work off the newer package.

  A subtle error, corrected in my version, seems yet to be
  present in the `attoparsec-0.7.2`, in an operator used
  internally to build up the result set.

{-# LINE 132 Data/Attoparsec/Internal.hs #-}
-- | Turn our split representation back into a normal lazy ByteString.
(+:) :: SB.ByteString - LB.ByteString - LB.ByteString
sb +: lb | SB.null sb = lb
 | otherwise = LB.Chunk sb lb

  Where this operator showed up in `bytestringparser`, I
  replaced `LB.Chunk` with the smart constructor, `LB.chunk`, to
  ensure that the no empty chunks invariant of lazy
  `ByteString`s was followed (I discovered this failing one
  evening when I was fleshing out the JSON parser).

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


Re: [Haskell-cafe] Some help needed to start Haskell with Yi

2009-11-14 Thread Kapil Hari Paranjape
Hello,

On Sat, 14 Nov 2009, Jaco van Iterson wrote:
 Only installation with 'cabal install yi' in a Cygwin shell under MS Windows
 XP ended in:
 Yi\Prelude.hs:182:9:
 Duplicate instance declarations:
   instance Category Accessor.T -- Defined at Yi\Prelude.hs:182:9-38
   instance Category Accessor.T
 -- Defined in data-accessor-0.2.1:Data.Accessor.Private
 cabal.exe: Error: some packages failed to install:
 yi-0.6.1 failed during the building phase. The exception was:
 exit: ExitFailure 1
 
 Seems easy to fix but I can't even find where on my drive I can find the
 source code.
 
 Where is the source?

You need to run 'cabal unpack yi' in a suitable directory. This will
create a subdirectory containing the source. Enter that subdirectory,
make the changes and then run 'cabal install' from that subdirectory.

Regards,

Kapil.
--

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


Re: [Haskell-cafe] What does the `forall` mean ?

2009-11-14 Thread Felipe Lessa
On Sun, Nov 15, 2009 at 01:14:34AM +, Lennart Augustsson wrote:
 Of the two declarations
 data Fizzle a = Fizzle (b - (a, b)) a
 data Fizzle a = forall b. Fizzle (b - (a, b)) a
 only the second one is allowed (with some suitable extension).

 Personally I think the first one should be allowed as well, with the
 same meaning as the second one.
 Some people thought it was to error prone not to have any indication
 when an existential type is introduced,
 so instead we are now stuck with a somewhat confusing keyword.

I think you are able to say

  data Fizzle a where
Fizzle :: (b - (a,b)) - a - Fizzle a

Cheers,

--
Felipe.


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


[Haskell-cafe] help with musical data structures

2009-11-14 Thread Michael Mossey
I'm pretty new to Haskell so I don't know what kind of data structure I
should use for the following problem. Some kind of arrays, I guess.

One data item, called OrientedPCSet (oriented pitch class set, a musical
term) will represent a set whose members are from the range of integers 0
to 11. This could probably be represented efficiently as some kind of bit
field for fast comparison.

Another item, PitchMatrix, will be a 2-d matrix of midi pitch numbers.
This matrix will be constructed via a backtracking algortithm with an
evaluation function at each step. It will probably be constructed by
adding one number at a time, starting at the top of a column and working
down, then moving to the next column. This matrix should probably be
implemented as an array of some sort for fast lookup of the item row x,
column y. It doesn't require update/modification to be as fast as lookup,
and it won't get very large, so some sort of immutable array may work.

Thanks,
Mike



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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-14 Thread Daniel Schüssler
Hi,

  - Product (a,b) and co-product (Either) of monoids

the coproduct of monoids is actually a bit tricky. It could be implemented 
like this:

-- | 
-- Invariant 1: There are never two adjacent Lefts or two adjacent Rights
-- Invariant 2: No elements (Left mempty) or (Right mempty) allowed
newtype Coprod m1 m2 = C [Either m1 m2]
 
instance (Eq m1, Eq m2, Monoid m1, Monoid m2) = Monoid (Coprod m1 m2) where
mempty = C []
mappend (C x1) (C x2) = C (normalize (x1 ++ x2))

normalize [] = []
normalize (Left a0 : as)  | a0 == mempty = normalize as
normalize (Right a0 : as) | a0 == mempty = normalize as
normalize [a] = [a]
normalize (Left a0 : Left a1 : as) = Left (mappend a0 a1) : normalize as
normalize (Right a0 : Right a1 : as) = Right (mappend a0 a1) : normalize as
normalize (a0:as) = a0 : normalize as

inl x = normalize [Left x]
inr x = normalize [Right x]

fold :: (Monoid m1, Monoid m2, Monoid n) =
 (m1 - n) - (m2 - n) - Coprod m1 m2 - n
fold k1 k2 = foldMap (either k1 k2)

--
Alternative version, possibly more efficient? Represent directly as fold:
--
newtype Coprod m1 m2 = C (forall n. Monoid n = (m1 - n) - (m2 - n) - n)

instance Monoid (Coprod m1 m2) where
  mempty = C (\_ _ - mempty)
  mappend (C x) (C x') = 
C (\k1 k2 - mappend (x k1 k2) (x' k1 k2))

inl x = C (\k1 _ - k1 x)
inr x = C (\_ k2 - k2 x) 

--

Question: in the mappend of the second version, we have a choice: We could 
also, when possible, multiply on the *inside*, that is *before* applying 
k1/k2:
---
mappend (C x) (C x') =
 C (\k1 k2 -
 x (\m1 - x' (\m1' - k1 (mappend m1 m1')
(\m2' - mappend (k1 m1) (k2 m2'))
  (\m2 - x' (\m1' - mappend (k2 m2) (k1 m1'))
 (\m2' - k2 (mappend m2 m2')))
---

Now I don't know what the efficiency implications of the two different 
versions are :) Apparently it depends on the relative costs of mappend in 
m1/m2 vs. n, and the cost of computing k1/k2?

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


[Haskell-cafe] Why can `env` be assigned value two times ?

2009-11-14 Thread zaxis

defineVar :: Env - (Id, Val) - IOThrowsError Val
defineVar envRef (id, val) = do {
env - liftIO $ readIORef envRef;
env - return $ filter (\(_id, _) - _id/=id) env; -- clear the current
scope
valRef - liftIO $ newIORef val;
liftIO $ writeIORef envRef $ ((id, valRef):env);
return val;
}

In haskell, the variable canot change its value , right? If so, why can the
`env` be assigned value twice?

Sincerely!

-
fac n = foldr (*) 1 [1..n]
-- 
View this message in context: 
http://old.nabble.com/Why-can-%60env%60-be-assigned-value-two-times---tp26356073p26356073.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Why can `env` be assigned value two times ?

2009-11-14 Thread Ross Mellgren
They're two different 'env's, which can be observed by desugaring the 
do-notation:

do env - liftIO (readIORef envRef)
   env - return (filter (\(_id, _) - _id /= id) env)
...

Desugaring do-notation gets us:

liftIO (readIORef envRev) = \ env -
return (filter (\(_id, _) - _id /= id) env) = \ env -
...

Sometimes people use different names to make this obvious, e.g.

do env - liftIO $ readIORef envRef
   env' - return (filter ... env)

Also note that you're doing a pure operation here, so you don't need two 
bindings. You could instead do:

do env - filter (\(_id, _) - _id /= id) $ readIORev envRef
...

($ is from the supremely useful Control.Applicative, and is equivalent to 
fmap from Functor, or liftM from Monad)

or:

do env - liftIO $ readIORef envRef
   let env' = filter ... env

Using let notation here makes it somewhat more obvious that that line doesn't 
have any side effects.

-Ross

On Nov 15, 2009, at 2:05 AM, zaxis wrote:

 
 defineVar :: Env - (Id, Val) - IOThrowsError Val
 defineVar envRef (id, val) = do {
env - liftIO $ readIORef envRef;
env - return $ filter (\(_id, _) - _id/=id) env; -- clear the current
 scope
valRef - liftIO $ newIORef val;
liftIO $ writeIORef envRef $ ((id, valRef):env);
return val;
 }
 
 In haskell, the variable canot change its value , right? If so, why can the
 `env` be assigned value twice?
 
 Sincerely!
 
 -
 fac n = foldr (*) 1 [1..n]
 -- 
 View this message in context: 
 http://old.nabble.com/Why-can-%60env%60-be-assigned-value-two-times---tp26356073p26356073.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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