[Haskell-cafe] Re: Getting my feet wet - small browser game

2006-12-20 Thread Joachim Durchholz

Marc A. Ziegert schrieb:

software upgrades:
use Read/Show classes instead of Foreign.Marshal,


I'm having second thoughts here.
Wouldn't Show evaluate all thunks of the data Shown?
That would mean I couldn't use infinite data structures in data that 
goes out to disk.


I don't think this would be a strong restriction for the communication 
between simulation and satellites, but I'm pretty sure it would be for 
doing backups of the simulation. Unfortunately, doing simulation backups 
is also the area where versioning is probably the harder problem.


But I think I can work around that. I'd simply have to write a small 
upgrade program whenever data structures change, which unmarshalls using 
the old code and marshalls using the new code.


Regards,
Jo

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


Low-level Haskell profiling [Was: Re: [Haskell-cafe] Re: A suggestion for the next high profile Haskell project]

2006-12-20 Thread Andy Georges

Hi,

The GHC head can currently build against PAPI[1], a library for  
gathering CPU statistics.


I did not know that. I know PAPI, though I prefer using perfctr  
directly, at least for what I'm doing (stuff in a JVM) [1], [2], [3].


At the moment you can only gather such statistics for AMD Opteron  
but it shouldn't be difficult to port it to other CPUs after a bit  
of browsing around the PAPI docs. Installing PAPI requires  
installing a linux kernel driver though, so it is not for the faint  
hearted.


Well, AFAIK, PAPI abstracts away the platform dependencies quite  
well, so I guess your code can be run straightforward on all IA-32  
platforms (depending on the events you wish to measure, which may or  
may not be present on all platforms). PowerPC, Itanium, Mips, Alpha  
should work as well, IIRC. If the GHC backend can generate code  
there, that is.




We have used this library to find bottlenecks in the current code  
generation and we have implemented ways of correcting them, so  
expect some good news about this in the future.




Have you published anything about that?

I should get around to start a wiki page about using PAPI these  
days, but meanwhile feel free to contact me if you need further  
information or help.


I've been toying with this idea for a while [4], but never had the  
time to do something with it. If you have some cool stuff, let us  
know. I'm very interested.


-- Andy

[1] Eeckhout, L.; Georges, A.; De Bosschere, K. How Java Programs  
Interact with Virtual Machines at the Microarchitectural Level.  
Proceedings of the 18th Annual ACM SIGPLAN Conference on Object- 
Oriented Programming, Systems, Languages and Applications (OOPSLA  
2003). ACM. 2003. pp. 169-186
[2] Georges, A.; Buytaert, D.; Eeckhout, L.; De Bosschere, K. Method- 
Level Phase Behavior in Java Workloads. Proceedings of the 19th ACM  
SIGPLAN Conference on Object-Oriented Programming Systems, Languages  
and Applications. ACM Press. 2004. pp. 270-287
[3] Georges, A.; Eeckhout, L.; De Bosschere, K. Comparing Low-Level  
Behavior of SPEC CPU and Java Workloads. Proceedings of the Advances  
in Computer Systems Architecture: 10th Asia-Pacific Conference, ACSAC  
2005. Springer-Verlag GmbH. Lecture Notes in Computer Science. Vol.  
3740. 2005. pp. 669-679

[4] http://sequence.complete.org/node/68
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Versioning

2006-12-20 Thread Joachim Durchholz
As written in my other post, I will need to update data structures that 
were marshalled to disk.


Now I'm wondering how to best prepare for the situation. E.g. one of the 
common situations is that a single data item gets replaced by a list of 
items.


Now assume that there's a SomeData type that's used across the game, and 
which gets incompatibly updated SomeData1 (say, instead of containing 
just a string it turns into a list of strings).
The update code would now have to unmarshall a blob of game data, 
traverse it to find all instances of SomeData, wrap them in a 
one-element list to turn them into SomeData1s, reconstruct the blob of 
game data with the SomeData1 items, and marshall the result back out to 
disk.
This sounds as if I'd have to write code for every single data type in 
the update program just to update a single data type. Is that true, or 
is there a way around this?


Regards,
Jo

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


Re: [Haskell-cafe] Re: Getting my feet wet - small browser game

2006-12-20 Thread Donald Bruce Stewart
jo:
 Marc A. Ziegert schrieb:
 software upgrades:
 use Read/Show classes instead of Foreign.Marshal,
 
 I'm having second thoughts here.
 Wouldn't Show evaluate all thunks of the data Shown?
 That would mean I couldn't use infinite data structures in data that 
 goes out to disk.

Btw, if you're dumping large structures to disk, using Read/Show is a
bad idea :)

Use NewBinary, at a minimum, or one of the other serialisation modules
(possibly the one used in HAppS based on bytestrings) would be a better
option.

Read/Show is good for testing that the serialising code works, though.

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


Re[2]: [Haskell-cafe] Re: A suggestion for the next high profile Haskell project

2006-12-20 Thread Bulat Ziganshin
Hello ls-haskell-developer-2006,

Tuesday, December 19, 2006, 9:32:13 PM, you wrote:

 why you (and Donald) don't want to understand me. i say that imperative
 Haskell code is more efficient

 Second: Bulat, I think your generalization is, that performance
 matters so much and all the time

i don't say so. please don't make me a root of all evil :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Shrinking the Prelude: The categorical approach

2006-12-20 Thread Bulat Ziganshin
Hello Imam,

Wednesday, December 20, 2006, 6:53:35 AM, you wrote:

 * clean categorical hierarchy of type classes

i've tried to write alternative Base library. one caveat is that you can't
redefine standard classes, such as Num, without changing ghc itself

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Showing the 1 element tuple

2006-12-20 Thread Henning Thielemann

On Tue, 19 Dec 2006, Neil Mitchell wrote:

 () -- 0 element tuple
 (,) a b -- 2 element tuple
 (,,) a b c -- 3 element tuple

The problem is that the separator approach (comma) doesn't scale well:
  http://haskell.org/haskellwiki/Terminator_vs._separator
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A suggestion for the next high profile Haskell project

2006-12-20 Thread Henning Thielemann

On Mon, 18 Dec 2006, Bulat Ziganshin wrote:

 Monday, December 18, 2006, 4:46:16 PM, Henning Thielemann wrote:
 
  Very true. I really like to know some more clean tricks for speedup.
 
 use C. seriously :)

I followed the thread, hoping for a reference to an existing tutorial or
an announcement of an article on efficient but idiomatic Haskell
programming. But it seems, there is no such tutorial so far. It seems that
the tips on
 http://www.haskell.org/ghc/docs/6.6/html/users_guide/faster.html
  are not complete. :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Shrinking the Prelude: The categorical approach

2006-12-20 Thread Henning Thielemann

On Tue, 19 Dec 2006, Imam Tashdid ul Alam wrote:

 hi guys,
 I was just wondering if anyone is interested is a
 quasi-project of rewriting the Prelude (only
 shrinking it as measured by the total number of names
 imported, read along...)

There is a hybrid Java-Haskell language which also contains a Prelude with
renamed functions:
  http://labs.businessobjects.com/cal/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Versioning

2006-12-20 Thread Neil Mitchell

Hi Jo,

You seem to be describing SYB and not knowing it:
http://homepages.cwi.nl/~ralf/syb1/

That basically does exactly what you've requested, in terms of
traversing all items when only one matters. That said, serialisation
is still a hard problem - think long and hard before picking a data
format.

With Yhc.Core I used Drift to derve Binary instances, keep a version
tag, and if the version tags mismatch refuse to load the data.

Thanks

Neil

On 12/20/06, Joachim Durchholz [EMAIL PROTECTED] wrote:

As written in my other post, I will need to update data structures that
were marshalled to disk.

Now I'm wondering how to best prepare for the situation. E.g. one of the
common situations is that a single data item gets replaced by a list of
items.

Now assume that there's a SomeData type that's used across the game, and
which gets incompatibly updated SomeData1 (say, instead of containing
just a string it turns into a list of strings).
The update code would now have to unmarshall a blob of game data,
traverse it to find all instances of SomeData, wrap them in a
one-element list to turn them into SomeData1s, reconstruct the blob of
game data with the SomeData1 items, and marshall the result back out to
disk.
This sounds as if I'd have to write code for every single data type in
the update program just to update a single data type. Is that true, or
is there a way around this?

Regards,
Jo

___
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: Getting my feet wet - small browser game

2006-12-20 Thread Neil Mitchell

Hi


Btw, if you're dumping large structures to disk, using Read/Show is a
bad idea :)


Just as a mention how bad it is, maybe 30 times at Show and 50 times
at Read. I used to use this approach, moving away from it and learning
how to use Drift was a good idea.

Thanks

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


[Haskell-cafe] RE: New Layout Rule take 2

2006-12-20 Thread Simon Marlow
[EMAIL PROTECTED] wrote:
 I have made some improvements to the algorithm, and I am happy to say
 that with some minor tweaks, it correctly lays out the programs in
 the nofib suite.

 the algorithm is not much more complicated than the current one in the
 report, but doesn't have the parse-error rule. it does
 require a single
 token of lookahead to look for an in.

 darcs get http://repetae.net/repos/getlaid/

 I have also added a mode so it can work as a ghc preprocesor, allowing
 very easy testing. just compile with.

 ghc -pgmF /path/to/getlaid -F --make Main.hs

 and it will automatically process all your files.

Nice!  I ran the GHC parser tests using your preprocessor, and get 9 failures 
out of 27 in the should_compile class.   Some of these are bogus (problems with 
the lexer you're using rather than the layout preprocessor).  The should_fail 
class all failed, but that's because column numbers are different in the 
preprocessed result, so the error messages changed, I'll need to look at these 
individually.

I've attached a patch that corrects a couple of the failures in the 
should_compile class.

Cheers,
Simon


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


[Haskell-cafe] Re: [Haskell] Haskell Weekly News: December 20, 2006

2006-12-20 Thread Arthur van Leeuwen


On 20-dec-2006, at 2:17, Donald Bruce Stewart wrote:

-- 
-

Haskell Weekly News
http://sequence.complete.org/hwn/20061220
Issue 54 - December 20, 2006
-- 
-


Announcements

   Haskell Vim plugin. Arthur van Leeuwen [15]announced a new [16]vim
   plugin for Haskell providing some preliminary folding support, easy
   insertion of type signatures into programs, and support for  
handling

   .hi files.

  15. http://article.gmane.org/gmane.comp.lang.haskell.cafe/17675
  16. http://www.cs.uu.nl/~arthurvl/haskell.vba



Read that as 'support for automatically ignoring .hi files' (which  
really
helps when editing large programs consisting of multiple files... it  
makes

tab Do The Right Thing).

Doei, Arthur.

--

  /\/ |   [EMAIL PROTECTED]   | Work like you don't need  
the money
/__\  /  | A friend is someone with whom | Love like you have never  
been hurt
/\/__ | you can dare to be yourself   | Dance like there's nobody  
watching




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


RE: [Haskell-cafe] Success with Takusen (was: Type problem with simpletakusen code)

2006-12-20 Thread Bayley, Alistair
 To build a program, you need to do
 
 ghc --make db.hs -o db D:\Oracle\Ora92\bin\oci.dll
 
 (put the path to your oci.dll here).
 
 This compiles your program, and links it with oci.dll to get the
 Oracle externals resolved.


I've been working with Paul on his linking problems, and there's a
gotcha for Oracle 10 users. Apparently the folder that contains oci.dll,
typically $ORACLE_HOME/bin, can also include hsbase.dll, which has
something to do with Heterogeneous Services. Obviously (this being
Windows, where filenames are not case sensitive) this clashes with GHC's
HSbase.dll; hence linker errors.

I'm not sure exactly what the solution should be; one obvious one is to
not include Heterogeneous Services in your installation. I'm also not
sure if this affects Oracle clients; Paul hinted that he was pointing at
a server installation folder, so a standard client installation is
likely to be OK.

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FD problem in GHC 6.6

2006-12-20 Thread Robert Dockins


On Dec 19, 2006, at 10:11 PM, Dan Weston wrote:


 instance CommandFunction (Sh st ()) st where
   ^
I think your first argument (on which the second has a functional  
dependence) does not determine the second argument, since it makes  
use of st in the first argument. This strikes me as a likely place  
to begin.


No, I'm pretty sure this isn't a problem.  The second argument is  
determined _because_ it is mentioned in the first.  The functional  
dependencies and instance declarations work, as long as I can make  
the compiler accept them.  They are only being rejected by the  
termination-checking part of the algorithm.


That said, I'm open to the idea of reformulating these instances.  In  
fact, I don't really like the fact that I need FDs.  It seems to me  
that I should somehow be able to eliminate the second argument  
altogether and thus the FD, but I can't seem to figure it out.



Dan

Robert wrote:

Fellow Haskellers,
I have a package that uses some light typeclass hackery to  
automaticly

build parsing algorithms based on the type of a function.
I was recently informed that my package doesn't compile on GHC 6.6  
due
to the new restrictions on FD resolution; in particular I have  
instance
declarations which fail the coverage condition.  I can use  
undecidable
instances to make the package compile again, but I'd prefer not to  
if I

can avoid it.
class CommandFunction f st | f - st where
  parseCommand  :: String - f - CommandParser st
  commandSyntax :: f - [Doc]
instance CommandFunction (Sh st ()) st where





  parseCommand wbc m str =
 -- list monad
 do (x,[]) - runRegex (maybeSpaceBefore (Epsilon  
(CompleteParse

 m))) str
return x
  commandSyntax _ = []
instance CommandFunction r st
  = CommandFunction (Int - r) st where
  parseCommand = doParseCommand Nothing intRegex id
  commandSyntax f = text (show intRegex) : commandSyntax (f  
undefined)

instance CommandFunction r st
  = CommandFunction (Integer - r) st where
  parseCommand = doParseCommand Nothing intRegex id
  commandSyntax f =  text (show intRegex) : commandSyntax (f  
undefined)







Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Shrinking the Prelude: The categorical approach

2006-12-20 Thread Brian Hulley

Imam Tashdid ul Alam wrote:

hi guys,
I was just wondering if anyone is interested is a
quasi-project of rewriting the Prelude (only
shrinking it as measured by the total number of names
imported, read along...)
the idea is (just to be substantially different in
approach) to develop an alternate history of
Haskell.
take map for example, and fmap, I don't think they
should be named different (fmap is ugly, not
suggestive, and conceptually the same).
mplus could be renamed (++) (they are conceptually the
same


I suggest that all functions in classes be given actual names and ASCII 
symbolic names could be defined outside the class as an additional 
convenience eg:


   class Monad m = MonadPlus m where
   mzero :: m a
   mplus :: m a - m a - m a

   (++) = mplus-- 'convenience' name

I think people forget that ASCII symbol names which look intuitive to them 
when they are writing a library or paper, can be very confusing for people 
who need to use many libraries (with consequent explosion of obfuscatory 
symbols) in a project, look terrible when qualified, and make code difficult 
to read because of the need to find/remember precedences and associativity. 
(Note that Haddock does *not* supply this info, you need to look at the 
actual source code of the library to find it out.)



, mzero looks odd, name it empty, or simply zero)


What about (mempty) from Monoid or (empty) from Data.Sequence or 
Control.Applicative? Either these are in some way the same thing as mzero, 
or else they are different in which case either qualified imports would be 
needed everywhere (not necessarily a bad thing) or different names like the 
ones we already have, are needed.



although I think concat should be replaced by msum (or
the other way around preferably :) ? msum is a bad
name) I am somewhat confused by join. concat seems to
match join's type but I don't think the ideas
coincide.
and so on. in particular, we would want:
* no backwards compatibility. the Prelude as is it, is
good enough. we are defining a new module.


Starting with a clean slate seems a good idea, especially to get rid of 
lispy names like (cons), (snoc), (null) and replace them with something 
self-explanatory like (pushL), (pushR), (isEmpty).



* clean categorical hierarchy of type classes
(category theorists wanted!) promoting uniformity.


This would be great. However it is a question to me whether it is even 
possible to organize everything in a single hierarchy. Eg look at the 
problems with trying to reorganize Num, or standard OOP problems with 
hierarchies in general. Since there are multiple ways of looking at a 
domain, it is likely there will need to be multiple hierarchies which will 
probably not interact so well.



* cleaner names. foldl1 means nothing. absolutely
nothing. what's the 1 for?


A while back I suggested using capital letters for suffix to distinguish the 
functionality (fold) from the variant (L == left). Perhaps (foldl1) could be 
renamed (foldLN) ie fold + left + non-empty or (foldLO) for fold + left + 
occupied.



* our Prelude only contains typeclasses, datatypes,
and functions of utmost conceptual (and semantic, such
as error, undefined and seq) importance, everything
else goes to other modules. our Prelude is not going
to be a place for convenient declarations.
* the suffix method of naming (liftM2) is considered
messy. we would prefer a seperate module (promoting
qualified import).


In the particular case of *M functions, I quite like the existing naming 
since it's clear that it's a monadic function. However I'd agree that names 
like (newIORef) are an abomination, that should be replaced by (Ref.new).



this is a fun project. we will not rewrite the
Prelude, we'll merely rename it. I would suggest the
name TheOtherPrelude to make our intentions clear. the
conveniences (like concatMap) goes to
TheOtherPrelude.Extension. I suggest we do it on the
wiki. anyone interested just open a page with your
name of choice. I am not doing it only because there's
no point doing it if no one's interested.


Good luck with this. For my own project, I re-implemented FingerTree's so I 
could use my preferred naming style (and also as an exercise following the 
excellent tutorial-style FingerTree paper), and wrote some trivial wrappers 
for a few other modules eg Data.IORef, Data.Unique so that I could use 
Ref.new, Unique.new etc.I think it would be quite a big task to refactor the 
entire code base according to a clean hierarchy of type classes, and also a 
task I can't really help with since I'm not familiar enough with category 
theory at present, but certainly it would be a worthwhile endeavour imho,


Brian.
--
http://www.metamilk.com 


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


Re: [Haskell-cafe] Success with Takusen (was: Type problem with simpletakusen code)

2006-12-20 Thread Paul Moore

On 12/20/06, Bayley, Alistair [EMAIL PROTECTED] wrote:

 To build a program, you need to do

 ghc --make db.hs -o db D:\Oracle\Ora92\bin\oci.dll

 (put the path to your oci.dll here).

 This compiles your program, and links it with oci.dll to get the
 Oracle externals resolved.

I've been working with Paul on his linking problems, and there's a
gotcha for Oracle 10 users. Apparently the folder that contains oci.dll,
typically $ORACLE_HOME/bin, can also include hsbase.dll, which has
something to do with Heterogeneous Services. Obviously (this being
Windows, where filenames are not case sensitive) this clashes with GHC's
HSbase.dll; hence linker errors.


To clarify a little - I believe the issue exists on Oracle 8i, 9i and
10g. It's not so much the version as the options you choose when you
install the software.

As far as I am able to confirm, a default enterprise edition install
includes hsbase.dll. A default client install does not. If you do a
custom install, then the relevant option is Heterogeneous Services -
but the simplest way to check is just to look for hsbase.dll in the
oracle home\bin directory.

Alistair - maybe you could add a check in Setup.hs, to see if
hsbase.dll is present, and if so, to display a warning? I can sort of
see where such a check would occur (in configOracle), but I don't know
enough about Cabal to suggest code...

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


[Haskell-cafe] multi parameter type classes for NP problems

2006-12-20 Thread Joshua Ball

Hi all,

For my own study, I've been playing around with various NP complete
problems. Previuosly I was doing so in Java, but because I want to
learn Haskell, I'm trying to port the algorithms. In Java, I had an
abstract class called AbstractNPProblem which looked like this:

public abstract class AbstractNPProblem implements NPProblem {
   public abstract boolean validates(Certificate c);
   public abstract ListCertificate certificates();
   public boolean decide() {
   for (Certificate c : certificates()) {
   if (validates(c)) {
   return true;
   }
   }
   return false;
   }
}

This has one problem, however: it is slightly dynamically typed.
Anybody that implements the verify method must cast the object c to a
particular type (could be a bitmask, a list of integers, a subgraph,
etc.) I'd like to get rid of this problem in porting to Haskell. Here
is how I am trying to solve the problem, using multi-parameter type
classes.

class NPProblem inst cert where
   validates :: cert - inst - Bool
   certificates :: inst - [cert]
   decide :: inst - Bool
   decide i = any (\x - x `validates` i) $ certificates i

Unfortunately, ghc throws the following type error:

NPProblem.hs:5:45
   Could not deduce (NPProblem inst a)
 from the context (NPProblem inst cert)
 arising from use of `certificates' at NPProblem.hs:5:45-58
   Possible fix:
 add (NPProblem inst a) to the class or instance method `decide'
   In the second argument of `($)', namely `certificates i'
   In the expression:
 (any (\ x - x `validates` i)) $ (certificates i)
   In the definition of `decide':
   decide i = (any (\ x - x `validates` i)) $ (certificates i)

Could somebody explain what is wrong with my intuitive approach? Also,
is multi parameter type classes the way to go, or is there a better
way?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FD problem in GHC 6.6

2006-12-20 Thread Iavor Diatchki

Hi,
I don't have a solution for you problem (besides using undecidable
instances) but I can explain the coverage condition.

On 12/19/06, Robert [EMAIL PROTECTED] wrote:

class CommandFunction f st | f - st where
  parseCommand  :: String - f - CommandParser st
  commandSyntax :: f - [Doc]


The functional dependency on this class adds the following axiom
(improvement rule) :
improve (CommandFunction f st1, CommandFunction f st2) using st1 = st2

Before accepting an instance, an implementation needs to check that
the instance will not violate this rule (i.e., the functional
dependency is satisfied).  In general, this may be difficult to check.
The coverage condition (CC) is a (conservative) rule that
guarantees that the functional dependency is satisfied.  It states
that an instance is accepted if all type variables in the determined
types are mentioned in the determining types.  The rule is
conservative because (as you have noticed) there are cases when the FD
axiom is not violated but the rule rejects an instance.Examples:


instance CommandFunction (Sh st ()) st where
  parseCommand wbc m str = ...


This instance satisfies the CC because st is mentioned in Sh st ().


instance CommandFunction r st
  = CommandFunction (Int - r) st where ...


This instance does not satisfy the CC because st is not mentioned in
Int - r.


instance CommandFunction r st
  = CommandFunction (Integer - r) st where ...


This instance does not satisfy the CC because st is not mentioned in
Integer - r.

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


[Haskell-cafe] Re: Versioning

2006-12-20 Thread Joachim Durchholz

Neil Mitchell schrieb:

You seem to be describing SYB and not knowing it:
http://homepages.cwi.nl/~ralf/syb1/

That basically does exactly what you've requested, in terms of
traversing all items when only one matters.


Yup, that's exactly what I was looking for. Actually I had seen it a 
while ago, but didn't remember it now. Thanks.


One thing that might become a problem is that the Scrap your 
boilerplate approach seems to work only in GHC.
There's nothing wrong with GHC, but it sounds like I'm committing to a 
specific compiler right from the start. I'd like to keep the number of 
choices as high as possible... and besides, if the compiler gives me an 
error message, or the generated code does unexpected things, I'd like to 
have the possibility to cross-check with a different compiler.


So have other compilers picked up SYB support yet?

It might be not feasible though. The papers mention that you can't 
serialize (well, actually unserialize) function values with it. For the 
envisioned update-through-marshalling process, this would prevent me 
from ever using function values in data that needs to be persistent, and 
that's quite a harsh restriction.



That said, serialisation is still a hard problem - think long and
hard before picking a data format.


What would be the problems of choosing the wrong one?


With Yhc.Core I used Drift to derve Binary instances, keep a version
tag, and if the version tags mismatch refuse to load the data.


Links?

Regards,
Jo

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


Re: [Haskell-cafe] multi parameter type classes for NP problems

2006-12-20 Thread Greg Buchholz
Joshua Ball wrote:
 Here is how I am trying to solve the problem, using multi-parameter
 type classes.
 
 class NPProblem inst cert where
validates :: cert - inst - Bool
certificates :: inst - [cert]
decide :: inst - Bool
decide i = any (\x - x `validates` i) $ certificates i
 
 Unfortunately, ghc throws the following type error:
 
 NPProblem.hs:5:45
Could not deduce (NPProblem inst a)
  from the context (NPProblem inst cert)
  arising from use of `certificates' at NPProblem.hs:5:45-58
Possible fix:
  add (NPProblem inst a) to the class or instance method `decide'
In the second argument of `($)', namely `certificates i'
In the expression:
  (any (\ x - x `validates` i)) $ (certificates i)
In the definition of `decide':
decide i = (any (\ x - x `validates` i)) $ (certificates i)

Maybe something like?...

class NPProblem inst cert where
   validates :: cert - inst - Bool
   certificates :: inst - [cert]
   decide :: inst - Bool
   decide i = any (\x - x `validates` i) $ (certificates i :: [cert])

...or a functional dependency of some sort...

class NPProblem inst cert | inst - cert where

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


Re: [Haskell-cafe] Re: Versioning

2006-12-20 Thread Ross Paterson
On Wed, Dec 20, 2006 at 07:30:02PM +0100, Joachim Durchholz wrote:
 Neil Mitchell schrieb:
 You seem to be describing SYB and not knowing it:
 http://homepages.cwi.nl/~ralf/syb1/
 
 That basically does exactly what you've requested, in terms of
 traversing all items when only one matters.
 
 Yup, that's exactly what I was looking for. Actually I had seen it a 
 while ago, but didn't remember it now. Thanks.

You spoke of changing each element to something of a different type.
I don't think SYB can do that.  A solution (and a portable one too) might
be to parameterize all these types, and make them instances of Functor,
Foldable and Traversable (see Data.Foldable and Data.Traversable in
the GHC 6.6 documentation).  You'd have the labour or writing all those
instances (though the trivial instances of Functor and Foldable would
suffice).  But once you've done that, a range of different traversals
would be available.

 It might be not feasible though. The papers mention that you can't 
 serialize (well, actually unserialize) function values with it. For the 
 envisioned update-through-marshalling process, this would prevent me 
 from ever using function values in data that needs to be persistent, and 
 that's quite a harsh restriction.

That's hard to avoid, unless you have a data representation of the
functions you're interested in.

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


Re: [Haskell-cafe] #haskell irc channel reaches 300 users

2006-12-20 Thread Henk-Jan van Tuyl


Nice to know! Can anybody tell me, how many people have subscribed to the  
Haskell Cafe mailing list? What is the growth?

How many people visit haskell.org?


On Tue, 19 Dec 2006 03:04:43 +0100, Donald Bruce Stewart  
[EMAIL PROTECTED] wrote:



A small announcement :)

5 years after its inception, under the guiding hand of Shae Erisson (aka
shapr), the #haskell IRC channel[1] on freenode has finally reached 300
users!



--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
--

Using Opera's revolutionary e-mail client:
https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433

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


[Haskell-cafe] Re: Versioning

2006-12-20 Thread Joachim Durchholz

Ross Paterson schrieb:
It might be not feasible though. The papers mention that you can't 
serialize (well, actually unserialize) function values with it. For the 
envisioned update-through-marshalling process, this would prevent me 
from ever using function values in data that needs to be persistent, and 
that's quite a harsh restriction.


That's hard to avoid, unless you have a data representation of the
functions you're interested in.


I could encode functions by their name. I don't think that would scale 
to a large application with multiple developers, but it's not this kind 
of project anyway.
I'd be reluctant to accept that way if it means adding boilerplate code 
for every function that might ever be serialized. Since I'm planning to 
serialize an entire application, I fear that I'd need that boilerplate 
code for 90% of all functions, so even a single line of boilerplate 
might be too much.


Regards,
Jo

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


Re: [Haskell-cafe] YAHT bug

2006-12-20 Thread Eric Y. Kow
Hi,

 The page says this was corrected in the wikibook, but it seems not to 
 have been fixed in the darcs repository at haskell.org.

Sorry for that.  I still haven't worked out a smart way to update the
darcs repository from the wikibook.  I'm thinking of versioning a
copy of the wiki pages with darcs, and using mvs to synch with the
wiki.  This will help me keep track of changes, which I can then
manually transfer to the latex version.  It is on my projects list;
I just haven't gotten around to it yet.

The intention is for the wikibook version to be the unstable YAHT
and the latex version to be stable.

 I found no mentioning on the YAHT page of ways to change this, so 
 sending a mail to this list seemed simplest to me.

One way to do it would be to

1) retrieve with:
darcs get http://darcs.haskell.org/yaht
2) edit the latex files in question
3) darcs record
4) darcs send

I will then review the changes and push them in.

Best,

-- 
Eric Kow http://www.loria.fr/~kow
PGP Key ID: 08AC04F9 Merci de corriger mon français.


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


Re: [Haskell-cafe] Re: Versioning

2006-12-20 Thread Robert Dockins


On Dec 20, 2006, at 2:37 PM, Joachim Durchholz wrote:


Ross Paterson schrieb:
It might be not feasible though. The papers mention that you  
can't serialize (well, actually unserialize) function values with  
it. For the envisioned update-through-marshalling process, this  
would prevent me from ever using function values in data that  
needs to be persistent, and that's quite a harsh restriction.

That's hard to avoid, unless you have a data representation of the
functions you're interested in.


I could encode functions by their name. I don't think that would  
scale to a large application with multiple developers, but it's not  
this kind of project anyway.
I'd be reluctant to accept that way if it means adding boilerplate  
code for every function that might ever be serialized. Since I'm  
planning to serialize an entire application, I fear that I'd need  
that boilerplate code for 90% of all functions, so even a single  
line of boilerplate might be too much.


Let me just say here that what you are attempting to do sounds very  
difficult.  As I understand, you want to be able to serialize an  
entire application at some (predetermined / arbitrary?) point, change  
some of its code and/or data structures, de-serialize and run the  
thing afterwards.  Doing something like this without explicit  
language support is going to be hard, especially in a fairly static  
language like Haskell.


I would think Smalltalk, Erlang, or something from the Lisp/Scheme  
family would be more suitable for this sort of work (caveat, I have  
little experience with any of these languages).  Also, take a look  
here (http://lambda-the-ultimate.org/node/526) for some related  
discussion.





Regards,
Jo



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


[Haskell-cafe] Re: Versioning

2006-12-20 Thread Joachim Durchholz

Robert Dockins schrieb:


Let me just say here that what you are attempting to do sounds very 
difficult.  As I understand, you want to be able to serialize an entire 
application at some (predetermined / arbitrary?) point, change some of 
its code and/or data structures, de-serialize and run the thing 
afterwards.


Right.

Though it's not too far out of the ordinary. Haskell being a rather 
orthogonal language, I had hoped that I can simply serialize any data 
structure.


 Doing something like this without explicit language support

is going to be hard, especially in a fairly static language like Haskell.


Exactly.
I was intrigued when I found that libraries can do quite a lot 
serialization in Haskell - that gives Haskell an excellent rating in 
what could be called aspect-orientedness.

It doesn't help to serialize functions values or thunks, though.

I would think Smalltalk, Erlang, or something from the Lisp/Scheme 
family would be more suitable for this sort of work (caveat, I have 
little experience with any of these languages). 


Erlang is actually on my list of potential alternatives. It has 
different advantages than Haskell, though, and right now, I'm willing to 
try Haskell.



Also, take a look here (http://lambda-the-ultimate.org/node/526) for
some related discussion.


I'm not sure whether that relates to my project. I let network 
connections be handled by Apache and FastCGI, so I'm leaving out a whole 
lot of library issues that hit that reported project really hard.


Regards,
Jo

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


[Haskell-cafe] How to serialize thunks?

2006-12-20 Thread Joachim Durchholz
I have skimmed the serialization libraries on haskell.org (NewBinary, 
SerTH, AltBinary, HsSyck, GenericSerialize).


I'm under the impression that these all force the data that they serialize.
Is that correct?
If yes: are there workarounds? I'd really like to be able to use 
infinite data structures in the data that I serialize.


Regards,
Jo

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


Re: [Haskell-cafe] Shrinking the Prelude: The categorical approach

2006-12-20 Thread Diego Navarro

take map for example, and fmap, I don't think they
should be named different (fmap is ugly, not
suggestive, and conceptually the same).
mplus could be renamed (++) (they are conceptually the
same


Wouldn't this raise the same problems monad comprehensions raise?
Worse yet, beginners can't start off with lists -- and understand
error messages -- without knowing about monads first!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Origins of (x:xs)?

2006-12-20 Thread Doug Quale
Paul Hudak [EMAIL PROTECTED] writes:

 As for x:xs, the xs is meant to be the plural of x, and is
 pronounced exs (I guess...).
 Similarly, n:ns is one n followed by many more ens.   Make sense?

I think this convention is often used in the Prolog community as well,
as in X|Xs.

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


Re: [Haskell-cafe] multi parameter type classes for NP problems

2006-12-20 Thread Joshua Ball

That works. Thanks. I didn't realize you could put types in the
expression itself.

On 12/20/06, Greg Buchholz [EMAIL PROTECTED] wrote:

Joshua Ball wrote:
 Here is how I am trying to solve the problem, using multi-parameter
 type classes.

 class NPProblem inst cert where
validates :: cert - inst - Bool
certificates :: inst - [cert]
decide :: inst - Bool
decide i = any (\x - x `validates` i) $ certificates i

 Unfortunately, ghc throws the following type error:

 NPProblem.hs:5:45
Could not deduce (NPProblem inst a)
  from the context (NPProblem inst cert)
  arising from use of `certificates' at NPProblem.hs:5:45-58
Possible fix:
  add (NPProblem inst a) to the class or instance method `decide'
In the second argument of `($)', namely `certificates i'
In the expression:
  (any (\ x - x `validates` i)) $ (certificates i)
In the definition of `decide':
decide i = (any (\ x - x `validates` i)) $ (certificates i)

Maybe something like?...

class NPProblem inst cert where
   validates :: cert - inst - Bool
   certificates :: inst - [cert]
   decide :: inst - Bool
   decide i = any (\x - x `validates` i) $ (certificates i :: [cert])

...or a functional dependency of some sort...

class NPProblem inst cert | inst - cert where

___
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] Shrinking the Prelude: The categorical approach

2006-12-20 Thread Greg Fitzgerald

Wouldn't this raise the same problems monad comprehensions raise?


The do-notation isn't specific to IO, yet it is the only thing beginners use
it for.  Do beginners have noticeably more trouble with the do-notation
errors than list comprehension errors?

As someone who learned Haskell fairly recently, I never really read the
compiler errors.  I looked for the line number, and whether it was a type
error or syntax error.  The rest might as well have been Greek, and I was
fine with that.

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


[Haskell-cafe] Haskell Side Effect

2006-12-20 Thread Ashley Yakeley

Since learning Haskell, I can now count in Spanish! See:

  one in Spanish,
  two in Spanish,
  three in Spanish,
  four in Spanish..

--
Ashley Yakeley

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


Re: [Haskell-cafe] Haskell Side Effect

2006-12-20 Thread Bernie Pope

I thought this email might be interesting for the Spanish speaking
part of the Haskell community, so I have written it in Spanish for them:

(Since learning Haskell, I can now count in Spanish! See:

  one in Spanish,
  two in Spanish,
  three in Spanish,
  four in Spanish..

--
Ashley Yakeley) in Spanish
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Versioning

2006-12-20 Thread Neil Mitchell

Hi


 With Yhc.Core I used Drift to derve Binary instances, keep a version
 tag, and if the version tags mismatch refuse to load the data.

Links?


http://repetae.net/~john/computer/haskell/DrIFT/

http://darcs.haskell.org/yhc/src/libraries/general/Yhc/General/Binary.hs

Thats Drift which can derive binary instances (pick GhcBinary), and
then a module which can work with the derived classes.

Warning, mild hacking was required to get it going on Windows.

Thanks

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


Re: [Haskell-cafe] Haskell Side Effect

2006-12-20 Thread jerzy . karczmarczuk

Bernie Pope writes:


I thought this email might be interesting for the Spanish speaking
part of the Haskell community, so I have written it in Spanish for them:



(Since learning Haskell, I can now count in Spanish! See:



  one in Spanish,
  two in Spanish,
  three in Spanish,
  four in Spanish..



Ashley Yakeley) in Spanish

=

You have proven once more how powerful is the Haskell genericity.
It is straightforward to extend the algorithm to Polski and Türkçe.
...werbeH neve dna

a
n
d

C
h
i
n
e
s
e

==

Jerzy Karczmarczuk


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


Re: [Haskell-cafe] Haskell Side Effect

2006-12-20 Thread Jason Dagit

Am I the only one that doesn't get it?

Jason

On 12/20/06, [EMAIL PROTECTED]
[EMAIL PROTECTED] wrote:

Bernie Pope writes:

 I thought this email might be interesting for the Spanish speaking
 part of the Haskell community, so I have written it in Spanish for them:

 (Since learning Haskell, I can now count in Spanish! See:

   one in Spanish,
   two in Spanish,
   three in Spanish,
   four in Spanish..

 Ashley Yakeley) in Spanish
=

You have proven once more how powerful is the Haskell genericity.
It is straightforward to extend the algorithm to Polski and Türkçe.
 ...werbeH neve dna

a
n
d

C
h
i
n
e
s
e

==

Jerzy Karczmarczuk


___
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] Haskell Side Effect

2006-12-20 Thread Dan Piponi

On 12/20/06, Bernie Pope [EMAIL PROTECTED] wrote:

(Since learning Haskell, I can now count in Spanish! See:

   one in Spanish,
   ...
Ashley Yakeley) in Spanish


I notice you're using the assumption that Spanish is a Monad so that
Double Spanish can be mapped back into Spanish.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Shrinking the Prelude: The categorical approach

2006-12-20 Thread J. Garrett Morris

On 12/20/06, Diego Navarro [EMAIL PROTECTED] wrote:

 take map for example, and fmap, I don't think they
 should be named different (fmap is ugly, not
 suggestive, and conceptually the same).
 mplus could be renamed (++) (they are conceptually the
 same

Wouldn't this raise the same problems monad comprehensions raise?
Worse yet, beginners can't start off with lists -- and understand
error messages -- without knowing about monads first!


I may be in the distinct minority here, but I greatly miss monad
comprehensions.  Since the objection to monad comprehensions (as well
as more general types for (++) etc) seems to be difficulty for
beginners, has anyone considered providing either language levels as a
command line switch - ala Dr. Scheme - or specifying the meaning of
comprehensions et. al. in regard to whatever operations are in scope
and then having different versions of the Prelude for educational
purpose?

(As a side note, when I was first learning Haskell and learned about
MonadPlus - with the comment that (++) was the monadic plus operator
for lists, I gleefully assumed that (++) :: MonadPlus m = m a - m a
- m a, and was quite happily surprised that something I'd been using
for a while was actually more general than I'd realized.  When I found
out that it wasn't really, I was quite disappointed.)

/g

--
It is myself I have never met, whose face is pasted on the underside of my mind.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Showing the 1 element tuple

2006-12-20 Thread John Meacham
have it be 
( ) 1

with a space between the parens to denote that it is a single tuple
rather than a nullary one.

John
-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Side Effect

2006-12-20 Thread Bryan Burgers

On 12/20/06, Jason Dagit [EMAIL PROTECTED] wrote:

Am I the only one that doesn't get it?

Jason


No, you are not the only one that doesn't get it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Side Effect

2006-12-20 Thread Brian Hulley

Ashley Yakeley wrote:

Since learning Haskell, I can now count in Spanish! See:

  one in Spanish,
  two in Spanish,
  three in Spanish,
  four in Spanish..


Is there a solution ie some concept C such that C Haskell  C Spanish, 
somewhere?

Thanks, Brian.
--
http://www.metamilk.com 


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


[Haskell-cafe] Re: Shrinking the Prelude: The categorical approach

2006-12-20 Thread Imam Tashdid ul Alam
so the main issues are these:

Bulat Ziganshin raised: Num is intrinsically bound to
the compiler. sad. so let's leave Num out. this
basically means we will avoid abstract algebra in
general. that is, forget groups, rings, for now,
the principle focus will be functor, monad...

Henning Thielemann provided links to CAL: hi Henning,
would you mind if we steal some of the good looking
names in your Prelude?

Brian Hulley raised one serious issue: even if we were
to define a newbie friendly Prelude, which should be
preferred, alphanumeric names or operators? I have a
thing for operators, they look good! but Brian's issue
is solid, the precedence isn't documented by Haddock.
any Haddock developer reading this? so mplus stays. I
would still suggest plus/zero over mplus/zero but
Haskell's scoping is rather liberal. I suggest the
convention that Control.Monad is always imported as M.
this would mean we use M.plus, M.zero, M.lift and so
on. 

Diego Navarro said: this will confuse beginners. I
disagree. I think type classes and monads are the
basics of Haskell (before that, it's just commonsense
;)... ) so if the error message successfully conveys
the message that there's a problem, that should be
enough to inspire the beginner to start on the basics.

besides, people will ultimately use the standard
Prelude. what I am trying to do is to prove that with
a good choice of names programs written in Haskell can
look more comprehensible to beginners.

like Gosling said about Java, the language syntax has
one very good property: it's easy to read it.

Garrett Morris seems to agree with me on this.

Greg Fitzgerald raised the further issue of monads
being overlooked by the beginners. I think do
notation considered harmful blog was at least
partially right: it's better to expose the concept
rather than hiding it.

so with enough people interested (I assume) it's time
to move this discussion to the wiki. the wiki code is
not to be taken seriously, it's a proof-of-concept,
a guideline.

cheers!
Imam

__
Do You Yahoo!?
Tired of spam?  Yahoo! Mail has the best spam protection around 
http://mail.yahoo.com 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Side Effect

2006-12-20 Thread Murray Gross



On Wed, 20 Dec 2006, Bryan Burgers wrote:


On 12/20/06, Jason Dagit [EMAIL PROTECTED] wrote:

Am I the only one that doesn't get it?

Jason




But your question on it clearly implies that you did get it.

Murray Gross

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