Re: [Haskell-cafe] PSA: do not install xcode 5 if you are using ghc 7.6

2013-09-23 Thread Edsko de Vries
Just to add to Carter's message: if you happened to install Xcode 5 anyway, then realized your mistake and uninstalled it and installed Xcode 4 again, you will STILL have the command line tools that came with Xcode 5 and your Haskell toolchain will STILL be broken -- and so far I have been unable

Re: [Haskell-cafe] Errors with Template Haskell

2013-08-09 Thread Edsko de Vries
The Template Haskell quotation monad (Q) has proper support for fail: module A where import Language.Haskell.TH foo :: Q Exp foo = fail Custom compile error! and module B where import A main :: IO () main = print $foo gives B.hs:6:14: Custom

Re: [Haskell-cafe] meaning of referential transparency

2013-04-06 Thread Edsko de Vries
I have quite a detailed discussion of this concept, and related concepts, in Section 2.8 of my PhD thesis ( https://www.cs.tcd.ie/Edsko.de.Vries/pub/MakingUniquenessTypingLessUnique-screen.pdf ). -E On Sat, Apr 6, 2013 at 7:13 PM, Kim-Ee Yeoh k...@atamo.com wrote: On Sun, Apr 7, 2013 at 12:43

Re: [Haskell-cafe] Threadscope 0.2.2 goes in segmentation fault on Mac Os X 10.8.3

2013-04-04 Thread Edsko de Vries
starting just fine. Even though this fixes my problem, it doesn't solve the root, namely why it was failing. Can you tell me a bit more about the dark magic you used to make it work? Which GHC version did you use? Thanks a lot, A. On 3 April 2013 12:40, Edsko de Vries edskodevr...@gmail.com

Re: [Haskell-cafe] Threadscope 0.2.2 goes in segmentation fault on Mac Os X 10.8.3

2013-04-04 Thread Edsko de Vries
using hsenv c) I've brewed GTK instead of manually installing it, but gtk-demo runs just fine d) Are you using XQuartz? If yes, which version? Thanks again! A. On 4 April 2013 08:52, Edsko de Vries edskodevr...@gmail.com wrote: Hi Alfredo, No dark magic as far as I recall (except

Re: [Haskell-cafe] GSoC Project Proposal: Markdown support for Haddock

2013-04-04 Thread Edsko de Vries
Yes please! -E On Thu, Apr 4, 2013 at 5:49 PM, Johan Tibell johan.tib...@gmail.com wrote: Hi all, Haddock's current markup language leaves something to be desired once you want to write more serious documentation (e.g. several paragraphs of introductory text at the top of the module doc).

Re: [Haskell-cafe] Threadscope 0.2.2 goes in segmentation fault on Mac Os X 10.8.3

2013-04-03 Thread Edsko de Vries
I provide a ThreadScope binary on my site ( http://www.edsko.net/2013/01/24/threadscope-0-2-2/) which runs fine for me on 10.8.3. -E On Mon, Apr 1, 2013 at 8:01 AM, Dominic Steinitz domi...@steinitz.orgwrote: Alfredo Di Napoli alfredo.dinapoli at gmail.com writes: Said that,has someone

Re: [Haskell-cafe] Library API design: functional objects VS type classes

2013-03-05 Thread Edsko de Vries
What is the advance of using type classes? A function of the form f :: Show a = ... really has an implicit argument f :: Show__Dict a - ... that the compiler infers for us. So, the advantage of type classes is one of convenience: we don't have to pass dictionaries around, or even figure

Re: [Haskell-cafe] adding recursion to a DSL

2013-02-19 Thread Edsko de Vries
Hi Joerg, You might find Abstract Syntax Graphs for Domain Specific Languages by Bruno Oliveira and Andres Löh ( http://ropas.snu.ac.kr/~bruno/papers/ASGDSL.pdf) a helpful reference to adding things like recursion (and other binding constructs) to your DSL. Edsko On Tue, Feb 19, 2013 at 9:47

[Haskell-cafe] Difference Lists versus Accumulators

2013-01-08 Thread Edsko de Vries
Hey all, The connection between difference lists and accumulators is probably well known, but I only recently realized it myself and a quick Google search didn't find turn up any page where this was explicitly stated, so I thought this observation might be useful to some. Every beginner Haskell

Re: [Haskell-cafe] License of CloudHaskell code write by Haskell language.

2012-10-17 Thread Edsko de Vries
Hi Chatsiri, Yes, there are multiple backends for Cloud Haskell. The Azure backend is, as you say, work in progress, although it's almost in a usable state and we hope to release a first version (with minimal functionality) soon. There is also the SimpleLocalnet backend which you can use for

Re: [Haskell-cafe] License of CloudHaskell code write by Haskell language.

2012-10-16 Thread Edsko de Vries
Hi, The version of Cloud Haskell you cite is a prototype. I recommend you use the 'distributed-process' package instead; it is licensed under BSD3. Edsko ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Cloud Haskell real usage example

2012-08-22 Thread Edsko de Vries
Hi Thiago, Let me address your questions one by one. On Wed, Aug 22, 2012 at 1:01 AM, Thiago Negri evoh...@gmail.com wrote: Hello everyone. I'm taking my first steps in Cloud Haskell and got some unexpected behaviors. I used the code from Raspberry Pi in a Haskell Cloud [1] as a first

Re: [Haskell-cafe] What's the deal with Clean?

2009-11-04 Thread Edsko de Vries
On 4 Nov 2009, at 13:36, Alberto G. Corona wrote: Artyom. I know what uniqueness means. What I meant is that the context in which uniqueness is used, for imperative sequences: (y, s')= proc1 s x (z, s'')= proc2 s' y . is essentially the same sequence as if we rewrite an state monad

Re: [Haskell-cafe] What's the deal with Clean?

2009-11-04 Thread Edsko de Vries
, at 15:27, David Leimbach wrote: On Wed, Nov 4, 2009 at 7:11 AM, Edsko de Vries edskodevr...@gmail.com wrote: On 4 Nov 2009, at 13:36, Alberto G. Corona wrote: Artyom. I know what uniqueness means. What I meant is that the context in which uniqueness is used, for imperative sequences

Re: [Haskell-cafe] Bool as type class to serve EDSLs.

2009-05-27 Thread Edsko de Vries
+1. I agree completely, I've missed this often for exactly the same reasons. Edsko ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: A guess on stack-overflows - thunks build-up and tail recursion

2009-03-20 Thread Edsko de Vries
The problem occurs when the result value is needed and thus the thunks need to be reduced, starting with the outermost, which can't be reduced without reducing the next one etc and it's these reduction steps that are pushed on the stack until its size cause a stack-overflow. Yes,

Re: [Haskell-cafe] least fixed points above something

2009-03-19 Thread Edsko de Vries
I've used a similar function myself, but why write it in such a complicated way? How about lfp :: Eq a = (a - a) - a - a lfp f x | f x == x = x | otherwise = lfp f (f x) Edsko On 19 Mar 2009, at 09:49, Jens Blanck wrote: Hi, I found myself writing the following leastFixedPoint :: (Eq

Re: [Haskell-cafe] least fixed points above something

2009-03-19 Thread Edsko de Vries
I always feel that the compiler should do such optimizations for me :) On 19 Mar 2009, at 16:21, Neil Mitchell wrote: I've used a similar function myself, but why write it in such a complicated way? How about lfp :: Eq a = (a - a) - a - a lfp f x | f x == x = x | otherwise = lfp f (f x)

Re: [Haskell-cafe] least fixed points above something

2009-03-19 Thread Edsko de Vries
On 19 Mar 2009, at 16:37, Martijn van Steenbergen wrote: Neil Mitchell wrote: if length (replicate 'a' 1) == 1 then [] else head (replicate 'a' 1) This program will use O(1) memory. Doesn't length force evaluation of the 1 cells? Yes, but without CSE every cell can

[Haskell-cafe] *almost* composition in writer monad

2009-03-04 Thread Edsko de Vries
Hi, Does this function remind anybody of anything? It seems like I'm missing an obvious abstraction: composeWriter :: [a - (a, b)] - a - (a, [b]) composeWriter [] a = (a, []) composeWriter (f:fs) a = let (a', b) = f a (final_a, bs) = composeWriter fs a' in (final_a, b:bs)

Re: [Haskell-cafe] *almost* composition in writer monad

2009-03-04 Thread Edsko de Vries
Doh, yes, of course. I had a feeling I was missing something obvious :) Thanks :) On 4 Mar 2009, at 17:29, Miguel Mitrofanov wrote: Isn't that sequence in State monad? On 4 Mar 2009, at 19:37, Edsko de Vries wrote: Hi, Does this function remind anybody of anything? It seems like I'm

Re: [Haskell-cafe] Strict version of Data.Map.map

2009-02-27 Thread Edsko de Vries
I guess so. Maybe using mapAccum helps: import qualified Data.Map as M strictMap :: (a - b) - M.Map k a - M.Map k b strictMap f m = case M.mapAccum f' () m of ((), m') - m' where f' () x = x' `seq` ((), x') where x' = f x testStrictness mapper = m `seq` Not strict.

[Haskell-cafe] Strict version of Data.Map.map

2009-02-26 Thread Edsko de Vries
Hi, Is it possible to write a strict version of Data.Map.map (so that the Map becomes strict in the elements as well as the keys)? Thanks, Edsko ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Strict version of Data.Map.map

2009-02-26 Thread Edsko de Vries
On Thu, Feb 26, 2009 at 12:45:09PM -0300, Felipe Lessa wrote: I'd advise you to see Control.Parallel.Strategies, specially the NFData class and the rnf function. What is the time complexity of running rnf on a Data.Map? If it is O(n), then surely running rnf on my map after every 'map'

Re: [Haskell-cafe] ANN: The Typeclassopedia, and request for feedback

2009-02-18 Thread Edsko de Vries
Hey, Another comment: I feel that the Const datatype in Control.Applicative deserves to be better-known; you might mention it in your article, especially since it connects Applicative with Monoid. (In Conor's article, he calls that datatype 'Accy' and shows why it is so useful). Edsko

Re: [Haskell-cafe] ANN: The Typeclassopedia, and request for feedback

2009-02-16 Thread Edsko de Vries
Hi Brent, I want to congratulate you on your article! An excellent piece of work which should be compulsory reading for all serious haskell programmers :) My one suggestion would be that you expand on some of the examples; for example, in the monoid section, you refer to various cool

Re: [Haskell-cafe] Another point-free question (=, join, ap)

2009-02-14 Thread Edsko de Vries
On Fri, Feb 13, 2009 at 05:21:50PM +0100, Thomas Davie wrote: Hey, Thanks for all the suggestions. I was hoping that there was some uniform pattern that would extend to n arguments (rather than having to use liftM2, litM3, etc. or have different 'application' operators in between

Re: [Haskell-cafe] Another point-free question (=, join, ap)

2009-02-14 Thread Edsko de Vries
Hi Conor, Will this do? http://www.haskell.org/haskellwiki/Idiom_brackets You get to write iI f a1 a2 a3 Ji for do x1 - a1 x2 - a2 x3 - a3 f a1 a2 a3 amongst other things... Cool :-) I had seen those idiom brackets before and put them on my mental

Re: [Haskell-cafe] Another point-free question (=, join, ap)

2009-02-13 Thread Edsko de Vries
Hey, Thanks for all the suggestions. I was hoping that there was some uniform pattern that would extend to n arguments (rather than having to use liftM2, litM3, etc. or have different 'application' operators in between the different arguments); perhaps not. Oh well :) Thanks again! Edsko

[Haskell-cafe] Another point-free question (=, join, ap)

2009-02-12 Thread Edsko de Vries
Hi, I can desugar do x' - x f x' as x = \x - f x' which is clearly the same as x = f However, now consider do x' - x y' - y f x' y' desugared, this is x = \x - y = \y' - f x' y' I can simplify the second half to x = \x - y = f x' but now we are stuck. I

[Haskell-cafe] Looking for pointfree version

2009-02-09 Thread Edsko de Vries
Hi, Is there a nice way to write down :: Focus - [Focus] down p = concat [downPar p, downNew p, downTrans p] in point-free style? (In doesn't make much difference what these functions do; if it helps, their types are downPar, downNew, downTrans :: Focus - [Focus]). Ideally, I would like

Re: [Haskell-cafe] Looking for pointfree version

2009-02-09 Thread Edsko de Vries
Perfect! Beautiful. I was hoping there'd be a simple solution like that. Thanks! On 9 Feb 2009, at 14:31, Wouter Swierstra wrote: snip How about using Data.Monoid: down = downPar `mappend` downNew `mappend` downTrans Wouter ___ Haskell-Cafe

Re: [Haskell-cafe] Just how unsafe is unsafe

2009-02-06 Thread Edsko de Vries
Hi, My opinion is that unsafeXXX is acceptable only when its use is preserved behind an abstraction that is referentially transparent and type safe. Others may be able to help refine this statement. I would agree with this. The problem is that impurity spreads easily. For example, suppose we

Re: [Haskell-cafe] Type wildcards

2008-12-16 Thread Edsko de Vries
Hi, On Tue, Dec 16, 2008 at 05:26:00PM +0200, Eyal Lotem wrote: Martin Foster (aka. EvilTerran) suggested an interesting idea, and I decided it was too nice to ignore/be forgotten inside Martin's head... So I'd like to try and suggest it. Type wildcards that allow partially specifying

Re: [Haskell-cafe] Proof that Haskell is RT

2008-11-12 Thread Edsko de Vries
See What is a purely functional language by Sabry. Not quite a formal proof about *Haskell*, but then we would first need a formal semantics of Haskell to be able to do that proof ;-) On 12 Nov 2008, at 10:11, Andrew Birkett wrote: Hi, Is a formal proof that the Haskell language is

[Haskell-cafe] Implementing pi-calculus using STM

2008-10-17 Thread Edsko de Vries
Hi, (Note: assumes knowledge of pi-calculus.) I am playing with writing a simple interpreter for the pi-calculus using STM. The implementation of most of the operators of the pi- calculus is straightforward, but I am unsure on how to implement the replication operator. The interpretation

Re: [Haskell-cafe] Associative Commutative Unification

2008-07-08 Thread Edsko de Vries
On Tue, Jul 08, 2008 at 08:24:45AM -0400, John D. Ramsdell wrote: The Haskell typechecker contains a nice example of a unifier for freely generated terms. My focus is on equational unification, but thanks anyway. Are you aware of Term Rewriting and all That? It describes how to do associative

Re: [Haskell-cafe] Haskell's type system

2008-06-18 Thread Edsko de Vries
On Tue, Jun 17, 2008 at 04:40:51PM -0400, Ron Alford wrote: I'm trying to wrap my head around the theoretical aspects of haskell's type system. Is there a discussion of the topic separate from the language itself? Since I come from a rather logic-y background, I have this (far-fetched) hope

Re: [Haskell-cafe] Moving forall over type constructors

2008-06-09 Thread Edsko de Vries
On Mon, Jun 09, 2008 at 03:20:33PM +0200, Klaus Ostermann wrote: At first I'd like to thank Claus, Ryan, Edsko, Luke and Derek for their quite helpful replies to my previous thread. In the course of following their advice I encountered the problem of moving a forall quantifier over a

Re: [Haskell-cafe] Moving forall over type constructors

2008-06-09 Thread Edsko de Vries
On Mon, Jun 09, 2008 at 06:55:20AM -0700, Klaus Ostermann wrote: But here we have an argument that can return a Wrapper (t a) for any 'a'; that does *not* mean it can return a wrapper of a polymorphic type. If you think about 'a' as an actual argument, then you could pass 'Int' to get

Re: [Haskell-cafe] Question about kinds

2008-06-07 Thread Edsko de Vries
On Fri, Jun 06, 2008 at 03:41:07PM -0700, Klaus Ostermann wrote: Why does the code below not pass the type checker? If I could explictly parameterize y with the type constructor Id (as e.g. in System F), then 'y Id' should have the type Int - Int and hence y Id x should be OK, but with

Re: [Haskell-cafe] What is the maturity of Haskell Web Frameworks

2008-06-05 Thread Edsko de Vries
On Wed, Jun 04, 2008 at 10:30:49PM -0400, Paul L wrote: Pardon me to hijack this thread, but I have an idea to build a different kind of Web Framework and am not sure if somebody has already done it. Have a look at iTasks, written in Clean. Not *quite* Haskell, I know, but close enough. I does

Re: [Haskell-cafe] automatically deriving Map and Filter on datatypes etc.

2008-06-05 Thread Edsko de Vries
On Thu, Jun 05, 2008 at 10:39:16AM +0200, Thomas Davie wrote: Even deriving an instance of Functor seems rather implausable, what should it do for data Wierd a b = Nil | A a (Wierd a b) | B b (Wierd a b) Should fmap's function argument operate on 'a's, 'b's, or both? Generic Haskell can

Re: [Haskell-cafe] hs-plugins compile error

2008-06-03 Thread Edsko de Vries
On Tue, Jun 03, 2008 at 03:07:33PM +0100, John O'Donnell wrote: Hi, What is the status of hs-plugins? I recently tried to install the version plugins-1.2 on hackage, using a Gnu/Linux box with Fedora 9 and ghc-6.8.2, but didn't get past the configure stage (see config.log below). The

[Haskell-cafe] hs-plugins compile error

2008-06-02 Thread Edsko de Vries
Hi, I'm getting the compilation error that is actually logged on Hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/plugins Below is a small diff file that resolves these problems; I don't know what the proper protocol is for submitting these diffs but it may be useful to

Re: [Haskell-cafe] hs-plugins compile error

2008-06-02 Thread Edsko de Vries
Hi Don, Is this the kind of thing you mean (I'm not really a darcs user; this is the patch created by darcs record): [Hide some names to remove ambiguity errors Edsko de Vries [EMAIL PROTECTED]**20080602202001] { hunk ./src/System/Plugins/Env.hs 76 -import Distribution.Package +import

Re: [Haskell-cafe] I/O without monads, using an event loop

2008-05-30 Thread Edsko de Vries
On Fri, May 30, 2008 at 03:09:37PM +0100, Robin Green wrote: I have been thinking about to what extent you could cleanly do I/O without explicit use of the I/O monad, and without uniqueness types (which are the main alternative to monads in pure functional programming, and are used in the

Re: [Haskell-cafe] Aren't type system extensions fun? [Further analysis]

2008-05-29 Thread Edsko de Vries
On Thu, May 29, 2008 at 01:44:24PM +0200, Roberto Zunino wrote: Kim-Ee Yeoh wrote: How about foo :: (exists. m :: * - *. forall a. a - m a) - (m Char, m Bool) Thank you: I had actually thought about something like that. First, the exists above should actually span over the whole type,

Re: [Haskell-cafe] Re: Monad for HOAS?

2008-05-15 Thread Edsko de Vries
On Wed, May 14, 2008 at 06:01:37PM -0400, Chung-chieh Shan wrote: Conal Elliott [EMAIL PROTECTED] wrote in article [EMAIL PROTECTED] in gmane.comp.lang.haskell.cafe: I share your perspective, Edsko. If foo and (Let foo id) are indistinguishable to clients of your module and are equal with

Re: [Haskell-cafe] Monad for HOAS?

2008-05-14 Thread Edsko de Vries
Hi, On Wed, May 14, 2008 at 03:59:58PM +0300, Lauri Alanko wrote: On Wed, May 14, 2008 at 10:11:17AM +0100, Edsko de Vries wrote: Suppose we have some data structure that uses HOAS; typically, a DSL with explicit sharing. For example: data Expr = One | Add Expr Expr | Let Expr (Expr

Re: [Haskell-cafe] Stack vs Heap allocation

2008-05-09 Thread Edsko de Vries
Hi, No, the thunks are (usually) stored on the heap. You don't get the stack overflow until you actually force the computation at which point you have an expression like: (...(((1+2)+3)+4) ... + 1000) which requires stack in proportion to the number of nested parentheses (effectively)

[Haskell-cafe] Stack vs Heap allocation

2008-05-08 Thread Edsko de Vries
Hi, How can I know whether something will be stack or heap allocated? For example, in the standard example of why foldl (+) 0 will fail to evaluate a long list of integers due to a stack overflow, but foldl' won't, it is pointed out that foldl starts building up unevaluated thunks. So,

Re: [Haskell-cafe] Re: Understanding tail recursion and trees

2008-05-03 Thread Edsko de Vries
Hi, I think Huet's Zipper is intended to solve this sort of problem. data Path = Top | BranchL Path Tree | BranchR Tree Path type Zipper = (Path, Tree) openZipper :: Tree - Zipper openZipper t = (Top, t) Conceptually the zipper is a tree with one subtree selected. You can

[Haskell-cafe] Understanding tail recursion and trees

2008-05-01 Thread Edsko de Vries
Hi, I am writing a simple compiler for a small DSL embedded in Haskell, and am struggling to identify and remove the source of a stack error when compiling larger examples. To understand the issues better, I was playing around with tail recursion on trees when I came across the following problem.

[Haskell-cafe] Re: Understanding tail recursion and trees

2008-05-01 Thread Edsko de Vries
Hi, Thanks to Miguel for pointing out my silly error. So at least my understanding of tail recursion is correct :) So then the question becomes: what *is* the best way to write this function? One version I can think of is ecount :: [Tree] - Integer - Integer ecount [] acc =

[Haskell-cafe] Functional programmer's intuition for adjunctions?

2008-03-04 Thread Edsko de Vries
Hi, Is there an intuition that can be used to explain adjunctions to functional programmers, even if the match isn't necessary 100% perfect (like natural transformations and polymorphic functions?). Thanks, Edsko ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Functional programmer's intuition for adjunctions?

2008-03-04 Thread Edsko de Vries
On Tue, Mar 04, 2008 at 11:58:38AM -0600, Derek Elkins wrote: On Tue, 2008-03-04 at 17:16 +, Edsko de Vries wrote: Hi, Is there an intuition that can be used to explain adjunctions to functional programmers, even if the match isn't necessary 100% perfect (like natural

[Haskell-cafe] OT: Isorecursive types and type abstraction

2008-01-24 Thread Edsko de Vries
Hi, This is rather off-topic but the audience of this list may be the right one; if there is a more appropriate venue for this question, please let me know. Most descriptions of recursive types state that iso-recursive types (with explicit 'fold' and 'unfold' operators) are easy to typecheck,

Re: [Haskell-cafe] OT: Isorecursive types and type abstraction

2008-01-24 Thread Edsko de Vries
On Thu, Jan 24, 2008 at 10:06:04AM -0600, Antoine Latter wrote: Can Fix be made to work with higher-kinded types? If so, would the following work: Perfect = /\ A . Fix (L :: * - *) . (A + L (A,A)) Hi, Thanks for your quick reply. Unfortunately, your solution does not work. For Fix X. t

Re: [Haskell-cafe] OT: Isorecursive types and type abstraction

2008-01-24 Thread Edsko de Vries
On Thu, Jan 24, 2008 at 10:46:36AM -0600, Antoine Latter wrote: Hmm ... How about: Perfect :: * - * = Fix (L :: * - *) . /\ A . (A + L (A,A)) unfold Perfect = [L := Fix L . t] t where t = /\ A . (A + L (A,A)) = /\ A . (A + (Fix L . /\ B . (B + L (B,B))) (A,A)) assuming

[Haskell-cafe] Precedence and associativity in a pretty-printer

2008-01-22 Thread Edsko de Vries
Hi, Suppose we have some algebraic datatype describing an expression language containing the usual suspects (various binary arithmetic operators such as addition, subtraction, multiplication, division, exponentiation, function abstraction and application, etc.) each with their own precendence

[Haskell-cafe] Re: [Haskell] Fixpoint combinator without recursion

2007-04-04 Thread Edsko de Vries
Yeah, it's rather cool. IIRC, this style of encoding of recursion operators is attributed to Morris. Do you have a reference? Before the advent of equality coercions, GHC typically had problems generating code for these kinds of definitions. Did you test this with a release version?

[Haskell-cafe] Re: [Haskell] Fixpoint combinator without recursion

2007-04-04 Thread Edsko de Vries
On Wed, Apr 04, 2007 at 11:05:51PM +0200, Stefan Holdermans wrote: Edsko, Yeah, it's rather cool. IIRC, this style of encoding of recursion operators is attributed to Morris. Do you have a reference? James H. Morris. Lambda calculus models of programming languages. Technical Report

[Haskell-cafe] Re: [Haskell] Fixpoint combinator without recursion

2007-04-04 Thread Edsko de Vries
On Wed, Apr 04, 2007 at 11:15:25PM +0200, Stefan Holdermans wrote: Edsko, James H. Morris. Lambda calculus models of programming languages. Technical Report MIT-LCS//MIT/LCS/TR-57, Massachusetts Institute of Technology, 1968. Aah, I guess that's a bit old to be avaiable online :) Does he

[Haskell-cafe] Search monad

2007-03-19 Thread Edsko de Vries
Hey, I have a structure containing Xs in various places, like so data X data Structure = Structure .. [X] .. [X] .. And I defined mapStructure mapStructure :: (X - X) - (Structure - Structure) I then wanted to use mapStructure to define queries as well as transformations on structures. I