[Haskell-cafe] Re: Continuations and coroutines

2010-06-22 Thread Heinrich Apfelmus
is a reimplementation of Koen Claessen's poor man's concurrency monad based on this approach: PoorMansConcurrency.hs http://projects.haskell.org/operational/examples.html Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list

[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-22 Thread Heinrich Apfelmus
Sebastian Fischer wrote: Heinrich Apfelmus wrote: [...] you can implement your type as newtype CMaybe a = CMaybe { forall b . (a - [b]) - [b] } Yes. For me it was interesting to see how far we get by wrapping `Maybe` in `Codensity`: we get more than `Maybe` but not as much

[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-19 Thread Heinrich Apfelmus
(eval . view . k) xs The call pattern of this interpreter shows that you can implement your type as newtype CMaybe a = CMaybe { forall b . (a - [b]) - [b] } but, as I said, this type is not good way of thinking about it in my opinion. Regards, Heinrich Apfelmus -- http

[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-18 Thread Heinrich Apfelmus
Heinrich Apfelmus wrote: Sebastian Fischer wrote: For example, the implementation of `callCC` does not type check with your changed data type. [snip] As for the interaction: what should ((callCC ($ 0) mzero) `orElse` return 2) = return . (+3) be? If the scope of callCC should

[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-18 Thread Heinrich Apfelmus
Sebastian Fischer wrote: Edward Kmett wrote: Sebastian Fischer wrote: Heinrich Apfelmus wrote: newtype CMaybe a = CMaybe (forall r. (a - Maybe r) - Maybe r) Yes, with this type `orElse` has the same type as `mplus`, which is very nice. This type is the same as Codensity Maybe using

[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-18 Thread Heinrich Apfelmus
David Menendez wrote: Heinrich Apfelmus wrote: Sebastian Fischer wrote: I wonder whether for every monad `m` and `a :: Codensity m a` getCodensity a f = getCodensity a return = f Is this true? Why (not)? It's not true. a = Codensity $ \x - Just 42 f = return . (+1

[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-16 Thread Heinrich Apfelmus
Sebastian Fischer wrote: Heinrich Apfelmus wrote: The reason is that you have chosen the wrong type for your continuation monad; it should be newtype CMaybe a = CMaybe (forall r. (a - Maybe r) - Maybe r) Yes, with this type `orElse` has the same type as `mplus`, which is very nice

[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-15 Thread Heinrich Apfelmus
a forall r . Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Harder than you'd think

2010-06-13 Thread Heinrich Apfelmus
Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Help with Bird problem 3.3.3

2010-06-11 Thread Heinrich Apfelmus
on m . Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Stone age programming for space age hardware?

2010-06-09 Thread Heinrich Apfelmus
Michael Schuerig wrote: Heinrich Apfelmus wrote: I have absolutely no experience with real time system, but if I were tasked to write with these coding standards, I would refuse and instead create a small DSL in Haskell that compiles to the requested subset of C. That suggestion

[Haskell-cafe] Re: Stone age programming for space age hardware?

2010-06-08 Thread Heinrich Apfelmus
theorem provers, this should no longer be the case. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-19 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote: Heinrich Apfelmus writes: Yes; what I mean is that you can retrofit a custom vertex type to any graph implementation that uses a fixed vertex type. So, let's say that data Gr a b = .. -- graph with vertex type Vertex Gr = Int then type Gr' node a b

[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-18 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote: Heinrich Apfelmus writes: Ivan Lazar Miljenovic wrote: Well, we'll provide a Map-based one that lets you specify the vertex type as a type parameter; this functionality (type parameter being ued for the vertex type) won't be required since not all graphs

[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-17 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote: Heinrich Apfelmus writes: I was under the impression that I would have to define a new graph data type with FilePath as vertex type and make that an instance of Graph ? [..] Well, we'll provide a Map-based one that lets you specify the vertex type as a type

[Haskell-cafe] Re: ANN: Monad.Reader Issue 16

2010-05-16 Thread Heinrich Apfelmus
some mailing lists posts on his debit method here: http://apfelmus.nfshost.com/articles/debit-method.html Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org

[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-15 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote: Heinrich Apfelmus writes: I'd be happy with either one. :) In both cases, I want to specify a custom vertex type. Except an abstract type isn't a custom vertex type... I can either do that directly if the library permits, though I think the solution

[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-14 Thread Heinrich Apfelmus
Ivan Miljenovic wrote: Heinrich Apfelmus wrote: Yes, the integers are just indexes. Of course, the example with the even integers is a bit silly; but if the integers are actually indexes, then it's conceptually cleaner to make them abstract, i.e. data Node -- constructors

[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-13 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote: Heinrich Apfelmus writes: Graphs with different node types don't behave differently; graphs are parametric with respect to the node type, just like lists don't behave differently on different element types. There will be a Map-based graph available

[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-12 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote: Heinrich Apfelmus writes: I'm not sure what the right solution is, but I think it definitely involves catering for different node types. For instance, the library could operate on a type newtype Graph node a b = Graph (Gr a b, Data.Map.Map Int node

[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-12 Thread Heinrich Apfelmus
into the graph type, though, an abstract Node type might work as well. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-10 Thread Heinrich Apfelmus
of requiring a fixed number to be specified in advance? Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: FRP for game programming / artifical life simulation

2010-05-03 Thread Heinrich Apfelmus
slightly into the future. The FPS number measures the frequency of drawn graphics, not the rate of physics updates. There may be multiple physics steps per drawing when the latter is slow, or the other way round, when the latter is fast. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-05-01 Thread Heinrich Apfelmus
' (Return a) = return a id' (i := k) = singleton i = mapMonad f . k (This is contrary to what I said earlier, mapMonad does *not* have to be a library function.) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing

[Haskell-cafe] Re: FRP for game programming / artifical life simulation

2010-04-29 Thread Heinrich Apfelmus
of the operational package, it's the WebSessionState.lhs on http://projects.haskell.org/operational/examples.html Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: FRP for game programming / artifical life simulation

2010-04-25 Thread Heinrich Apfelmus
qualities. In fact, I am convinced that it's not a good idea to focus on the semantics of FRP, the key focus should be on the syntax, on the way of expressing a given thought in computer words. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: ANN: forkable-monad 0.1

2010-04-23 Thread Heinrich Apfelmus
. But that should not deter from experimentation. :) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Hughes' parallel annotations for fixing a space leak

2010-04-22 Thread Heinrich Apfelmus
Leon Smith wrote: Heinrich Apfelmus wrote: which were introduced by John Hughes in his Phd thesis from 1983. They are intriguing! Unfortunately, I haven't been able to procure a copy of Hughes' thesis, either electronic or in paper. :( Can anyone help? Are there any other resources about

[Haskell-cafe] Re: hamming distance allocation

2010-04-21 Thread Heinrich Apfelmus
, chapter 12. Richard Bird. Introduction to Functional Programming using Haskell 2nd edition, chapter 7. The wikibook contains some preliminary material, too. http://en.wikibooks.org/wiki/Haskell/Graph_reduction Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: ANN: forkable-monad 0.1

2010-04-21 Thread Heinrich Apfelmus
- forkIO (down m return ()) down (return ()) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: hamming distance allocation

2010-04-20 Thread Heinrich Apfelmus
Daniel Fischer wrote: Heinrich Apfelmus: For instance, your expression can be replaced by filter (/=0) [hammingX x y | (x:xs) - tails example, y - xs] which cuts the total running time in half. It's still quadratic in the length of example . I'm sure there are faster algorithms out

[Haskell-cafe] Re: hamming distance allocation

2010-04-19 Thread Heinrich Apfelmus
| (x:xs) - tails example, y - xs] which cuts the total running time in half. It's still quadratic in the length of example . I'm sure there are faster algorithms out there that can bring it down to O(n log n) if you want. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-19 Thread Heinrich Apfelmus
Heinrich Apfelmus wrote: Limestraël wrote: Okay, I start to understand better... Just, Heinrich, how would implement the mapMonad function in terms of the operational package? You just shown the signature. Ah, that has to be implemented by the library, the user cannot implement

[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-15 Thread Heinrich Apfelmus
(runIdentity x) violates this condition. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-15 Thread Heinrich Apfelmus
it verbatim, but try to simplify it a bit to turn it into another easy to understand example of how to use operational . Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: Simple game: a monad for each player

2010-04-14 Thread Heinrich Apfelmus
this actually be a member of the MonadTrans class? mapMonad :: (Monad m1, Monad m2, MonadTrans t) = (forall a . m1 a - m2 a) - t m1 a - t m2 a ? Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: Simple game: a monad for each player

2010-04-14 Thread Heinrich Apfelmus
to several examples. Two small examples are also included in the Haddock documentation. I'd like to make it very accessible, so please don't hesitate to report any difficulties with finding and understanding documentation and examples! Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Cabal dependency hell

2010-04-12 Thread Heinrich Apfelmus
is prompted? Would you like to send an anonymous report of this build failure to hackage.org? Users have been uploading 189 reports so far; yours would be the 190th report that ensures high quality Haskell packages! [y/n] Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Cabal dependency hell

2010-04-12 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote: Heinrich Apfelmus writes: Perhaps exactly when the user is prompted? Would you like to send an anonymous report of this build failure to hackage.org? Users have been uploading 189 reports so far; yours would be the 190th report that ensures high quality Haskell

[Haskell-cafe] Re: Hackage accounts and real names

2010-04-10 Thread Heinrich Apfelmus
Steve Schafer wrote: Heinrich Apfelmus wrote: I agree, and this is why I phased out apfelmus in favor of the pseudonym Heinrich Apfelmus. You mean your name isn't really Applesauce? I would probably apply for a name change if it were. ;) Regards, Heinrich Apfelmus -- http

[Haskell-cafe] Re: Suitable structure to represents lots of similar lists

2010-04-09 Thread Heinrich Apfelmus
gain anything. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Simple game: a monad for each player

2010-04-09 Thread Heinrich Apfelmus
/package/operational which implements the same concept. It's throughly explained here: http://apfelmus.nfshost.com/articles/operational-monad.html http://projects.haskell.org/operational/ Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Suitable structure to represents lots of similar lists

2010-04-08 Thread Heinrich Apfelmus
cell and garbage collect the old one while you're at it. But if you can skip large contiguous parts of the lists, then sharing may be worth thinking about. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell

[Haskell-cafe] Re: Metaprogramming in Haskell vs. Ocaml

2010-04-07 Thread Heinrich Apfelmus
Nicolas Pouillard wrote: Heinrich Apfelmus wrote: I'm curious, can metaocaml create new data type definitions, value declarations or type class instances? No metaocaml cannot do this. It is restricted to the expression level, and not the declaration level. Moreover you cannot pattern match

[Haskell-cafe] Re: Hackage accounts and real names

2010-04-06 Thread Heinrich Apfelmus
Edward Z. Yang wrote: This is a pretty terrible reason, but I'm going to throw it out there: I like real names because they're much more aesthetically pleasing. I agree, and this is why I phased out apfelmus in favor of the pseudonym Heinrich Apfelmus. So, a more accurate policy would

[Haskell-cafe] Re: Metaprogramming in Haskell vs. Ocaml

2010-04-06 Thread Heinrich Apfelmus
, for instance for creating functional lenses for record types data Foo = Foo { bar_ :: Int, ...} $(DeriveLenses Foo) -- bar :: Lens Foo Int It seems to me that metaocaml is more used as user annotated partial evaluation? Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: libraries [was GUI haters]

2010-04-06 Thread Heinrich Apfelmus
a bit dormant. And Javascript [1] is really not _that_ bad! But it's not Haskell. :'( Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: libraries [was GUI haters]

2010-04-06 Thread Heinrich Apfelmus
, but that's what I can think of right now off the top of my hat. :) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Seeking advice about monadic traversal functions

2010-04-06 Thread Heinrich Apfelmus
f m n p = return f `ap` m `ap` n `ap` o Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Hackage accounts and real names

2010-04-05 Thread Heinrich Apfelmus
. Are they that ashamed of their own software that they wouldn't want to be associated with it, or is there some legal reason that they don't want to be associated with it? I'm sure they have their reasons, and who am I to judge them. Most likely, it's about googleability. Regards, Heinrich Apfelmus -- http

[Haskell-cafe] Re: ANN: spec2code

2010-04-05 Thread Heinrich Apfelmus
. But maybe that's because no one likes to be obsoleted... In fact, I do have to admit that I'm secretly working on a specification of a program that halts exactly when spec2code produces a program that does not halt. It's my only hope! Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Hughes' parallel annotations for fixing a space leak

2010-04-05 Thread Heinrich Apfelmus
Max Bolingbroke wrote: Heinrich Apfelmus wrote: As I understand it, GHC implements the technique from Sparud's paper, so this is a solved problem. This is not my understanding. As far as I know, the STG machine has a special notion of selector thunks, which represent projections from

[Haskell-cafe] Re: libraries [was GUI haters]

2010-04-03 Thread Heinrich Apfelmus
sluggish to navigate between pages, doesn't support drag drop from other applications and most importantly, doesn't play nice with local files. From the programmers point of view, I don't want to code my GUI in Javascript either, I want to do it in Haskell. Regards, Heinrich Apfelmus -- http

[Haskell-cafe] Re: Haskellers hate GUIs!!

2010-04-03 Thread Heinrich Apfelmus
supposed to. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Haskellers hate GUIs!!

2010-04-03 Thread Heinrich Apfelmus
-Linux systems and you still have to deal with unexpected errors somewhere deep in the dungeons of preprocessing for the Haskell FFI. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: Haskellers hate GUIs!!

2010-04-03 Thread Heinrich Apfelmus
the compiled binary with some otool vodoo; Inkscape did it this way last time I remember. There was also a gtk framework once, but it seems to be out of date. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list

[Haskell-cafe] Re: Seeking advice about monadic traversal functions

2010-04-02 Thread Heinrich Apfelmus
trees again. However, this solution is essentially the same as using a mutable tree, the unique identifiers represent memory addresses. That's why I sought to reconstruct the tree from the structure of the traversal (using the same intermediate queue data structure, etc.). Regards, Heinrich Apfelmus

[Haskell-cafe] Re: Seeking advice about monadic traversal functions

2010-03-31 Thread Heinrich Apfelmus
by repeatedly applying synthesize to the final state of bfs : unBfs ts = (`index` 0) . queue $ until (List.null . nodes) synthesize ([],ts,empty) By construction, we have obtained the desired unBfs . bfs xs = id Regards, Heinrich Apfelmus PS: * I have used a double-ended queue

[Haskell-cafe] Hughes' parallel annotations for fixing a space leak

2010-03-31 Thread Heinrich Apfelmus
about this parallel approach? Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Randomized N-Queens

2010-03-27 Thread Heinrich Apfelmus
) where q = (row,col) test seed = evalRand solve $ mkStdGen seed Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Sugar for function application

2010-03-25 Thread Heinrich Apfelmus
the list in a suitable Writer monad layoutSet myButton $ do text = Ok on action = doSomething with (=) :: Property a - a - Writer Properties () It's ugly semantically but pleasant syntactically. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: breadth first search one-liner?

2010-03-25 Thread Heinrich Apfelmus
where more 0 _ = [] more n (x:xs) = f x ++ more (n + length (f x) - 1) xs Unfortunately, this cannot be made to work with nub because that would screw up the size calculation. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Bytestrings and [Char]

2010-03-23 Thread Heinrich Apfelmus
x y = toEnum $ fromEnum x + fromEnum y are not possible with Data.Text.Text . (Whether you really need these is another question, of course.) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: A few ideas about FRP and arbitrary access in time

2010-03-09 Thread Heinrich Apfelmus
of modeling more fundamental theories as well.) The key point is that this is not absolute reality, it's just a model. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: GPL answers from the SFLC (WAS: Re: ANN: hakyll-0.1)

2010-03-07 Thread Heinrich Apfelmus
a default markdown - html converter, which means that it's also useful without it. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Books for advanced Haskell

2010-03-07 Thread Heinrich Apfelmus
are actually about missing or just recently understood prerequisites. Hence, I think that tracking prerequisites explicitly has potential. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: Books for advanced Haskell

2010-03-05 Thread Heinrich Apfelmus
://apfelmus.nfshost.com/articles/operational-monad.html when the semantics of the effects are a bit tricky to fit into existing transformers. My package operational http://projects.haskell.org/operational/ contains a bunch of examples. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: idioms ... for using Control.Applicative.WrapMonad or Control.Arrow.Kleisli?

2010-03-04 Thread Heinrich Apfelmus
/libraries/2008-January/008917.html might be of help. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Multiple Interpretations for a monad?

2010-03-02 Thread Heinrich Apfelmus
for the syntax and make the interpret function do all the work. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Real-time garbage collection for Haskell

2010-02-28 Thread Heinrich Apfelmus
-physics/fix-your-timestep/ or numerical integration will deteriorate rather quickly. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Generalizing nested list comprehensions

2010-02-27 Thread Heinrich Apfelmus
= map baz xs in nub ys == ys Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: What are free Monads?

2010-02-27 Thread Heinrich Apfelmus
: newtype Foo13 = Foo13 Int 0 = Foo13 0 s = \(Foo13 k) - Foo13 $ if k == 13 then 13 else k+1 Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: Heterogeneous Data Structures - Nested Pairs and functional references

2010-02-24 Thread Heinrich Apfelmus
, of course. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Heterogeneous Data Structures - Nested Pairs and functional references

2010-02-20 Thread Heinrich Apfelmus
type RGB = RGB' Int -- what we're interested in instance Functor RGB' where fmap f (RGB x y z) = RGB (f x) (f y) (f z) mapRGB :: (Int - Int) - RGB - RGB mapRGB = fmap but I don't quite see what you're doing with the free monad here, Alexander? Regards, Heinrich Apfelmus

[Haskell-cafe] Re: Implementing unionAll

2010-02-18 Thread Heinrich Apfelmus
Leon Smith wrote: On Wed, Feb 17, 2010 at 6:58 AM, Heinrich Apfelmus apfel...@quantentunnel.de wrote: Ah, I meant to use the union' from your previous message, but I think that doesn't work because it doesn't have the crucial property that the case union (VIP x xs) ys = ... does

[Haskell-cafe] Re: Implementing unionAll

2010-02-17 Thread Heinrich Apfelmus
Leon Smith wrote: Heinrich Apfelmus wrote: I see no obvious deficiencies. :) Personally, I'd probably structure it like http://www.haskell.org/haskellwiki/Prime_numbers#Implicit_Heap This variant, based on the wiki article, is cleaner, slightly simpler, appears to be just as fast

[Haskell-cafe] Re: on finding abstractions ...

2010-02-16 Thread Heinrich Apfelmus
. http://decenturl.com/homepages.inf.ed/wadler-98-prettier-printer Simon Peyton Jones, Jean-Marc Eber, Julian Seward. Composing contracts: an adventure in financial engineering. http://decenturl.com/research.microsoft/spj-financial-contracts Regards, Heinrich Apfelmus -- http

[Haskell-cafe] Re: Implementing unionAll

2010-02-16 Thread Heinrich Apfelmus
to abandon the lazy tree altogether and use a heap to achieve the same effect, similar to Melissa O'Neils prime number code. It's not as neat, but much more predictable. :) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe

[Haskell-cafe] Re: GUI programming

2010-02-04 Thread Heinrich Apfelmus
no community preference choice for either type families or functional dependencies. Personally, I didn't want to think about this and simply chose mtl . But if you like type families a lot, I see no problem with going ahead and using transformers + monads-tf . Regards, Heinrich Apfelmus -- http

[Haskell-cafe] Re: GUI programming

2010-02-03 Thread Heinrich Apfelmus
) = runBehaviour (a = (\x - f x = g)) Just a minor note: you can somewhat clean up your code by using a generic monad, as implemented in my cabal package operational http://hackage.haskell.org/package/operational and described in Heinrich Apfelmus. The Operational Monad Tutorial. In http

[Haskell-cafe] Re: Why no merge and listDiff?

2010-01-28 Thread Heinrich Apfelmus
Will Ness wrote: Heinrich Apfelmus writes: (Just for historical reference, credit for the data structure that works with infinite merges goes to Dave Bayer, I merely contributed the mnemonic aid of interpreting it in terms of VIPs.) yes, yes, my bad. GMANE is very unreliable at presenting

[Haskell-cafe] ANN: operational-0.1.0.0

2010-01-26 Thread Heinrich Apfelmus
* The Operational Monad Tutorial by Heinrich Apfelmus * Implementing STM in pure Haskell by Andrew Coppin I'm pleased to release a small package named operational in conjunction with The Operational Monad Tutorial. The tutorial presents a method to implement monads by specifying the primitive

[Haskell-cafe] Re: Why no merge and listDiff?

2010-01-26 Thread Heinrich Apfelmus
Will Ness wrote: You can check it out on the Haskellwiki Prime Numbers page (work still in progress, the comparison tables are missing). We had also a recent thread here in cafe under FASTER primes. The original idea of Heinrich Apfelmus of treefold merging the composites really panned

[Haskell-cafe] Re: Space Efficiency When Sorting a List of Many Lists

2010-01-24 Thread Heinrich Apfelmus
storing a recipe for creating a list of single wagers instead of the list itself, and [Row [a]] is just one possible recipe format. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: Is Haskell capable of matching C in string processing performance?

2010-01-22 Thread Heinrich Apfelmus
experience, ByteStrings are great for reading data, but not that good for writing data that is being generated on the fly. For writing, good old difference lists or the Builder monoid / Put monad from Data.Binary seem to be best. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: FASTER primes

2010-01-13 Thread Heinrich Apfelmus
Daniel Fischer wrote: Heinrich Apfelmus wrote: It is exactly because these troubles that I'm advocating the original VIP data structure that buries the dorks (that name is awesome :D) deep inside the structure. :) In fact, your transformation that fixes the space leaks pretty much emulates

[Haskell-cafe] Re: FASTER primes

2010-01-12 Thread Heinrich Apfelmus
, not sure how well it's implemented in GHC, I vaguely remember a bug reports. Alternatively, retaining zs in any way might already be too much. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: Space Efficiency When Sorting a List of Many Lists

2010-01-09 Thread Heinrich Apfelmus
) ∪ (A ∩ D) ∪ (B ∩ C) ∪ (B ∩ D) where A,B,C,D are sets. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: FASTER primes

2010-01-07 Thread Heinrich Apfelmus
Will Ness wrote: Heinrich Apfelmus writes: Concerning lists as producer/consumer, I think that's exactly what lazy evaluation is doing. Neither filter , map or span evaluate and store more list elements that strictly necessary. I laways suspected as much, but was once told that Chris

[Haskell-cafe] Re: lawless instances of Functor

2010-01-05 Thread Heinrich Apfelmus
have a go but the style of proof for these sorts of things is outside of my domain of confidence/experience. This looks relevant: Janis Voigtländer. Free Theorems Involving Type Constructor Classes. http://wwwtcs.inf.tu-dresden.de/~voigt/icfp09.pdf Regards, Heinrich Apfelmus -- http

[Haskell-cafe] Re: [darcs-users] Iteratees, streams, and mmap

2010-01-05 Thread Heinrich Apfelmus
Jason Dagit wrote: Heinrich Apfelmus wrote: How about tracking the requirement of bounded in the type system? In particular, I'm thinking of a type class class NFData a = Small a where the idea is that all types that can be stored in constant space are members of this class

[Haskell-cafe] Re: Space Efficiency When Sorting a List of Many Lists

2010-01-04 Thread Heinrich Apfelmus
or a Word64. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: FASTER primes

2010-01-04 Thread Heinrich Apfelmus
jump over p constructors of a data structure in O(1) time. [1]: http://www.cse.unsw.edu.au/~dons/papers/CLS07.html Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org

[Haskell-cafe] Re: Data.Ring -- Pre-announce

2009-12-31 Thread Heinrich Apfelmus
. (thesis) http://www.cs.cmu.edu/~rwh/theses/okasaki.pdf (Not sure if 3 is a good size factor; this can be determined with the amortized cost/step graph c(a) = let b = a/(1+a)-1/2 in (b+1)/b where a is the size factor.) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Space Efficiency When Sorting a List of Many Lists

2009-12-31 Thread Heinrich Apfelmus
sortCartesian = ana headsOut . cata (sort1 . cartesian1) This is readily extended to handle the explode function as well. And thanks to lazy evaluation, I expect this to run with a much better memory footprint. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Finally tagless and abstract relational Algebra

2009-12-30 Thread Heinrich Apfelmus
the problem just fine? Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Performance of functional priority queues

2009-12-29 Thread Heinrich Apfelmus
evaluation. http://www.comlab.ox.ac.uk/people/richard.bird/online/ BirdJonesDeMoor1997More.pdf Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: Why does HXT use Arrows?

2009-12-25 Thread Heinrich Apfelmus
://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.39.4029 I am not convinced that the abstract arrow interface is more convenient than an explicit b - M c version. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing

[Haskell-cafe] Re: install-dirs on Mac OS X

2009-12-23 Thread Heinrich Apfelmus
Tom Tobin wrote: Heinrich Apfelmus wrote: Likewise, ~/Library/Haskell seems to be the best place for user installs. While I don't mind the /Library/Haskell path for global installs, I'm not sure how I feel about this for local installs. It usually drives me crazy when my more Unix-y

[Haskell-cafe] Re: install-dirs on Mac OS X

2009-12-22 Thread Heinrich Apfelmus
then either set something like: symlink-global-bindir: /usr/local/bin in .cabal/config. Or symlink-global-bindir: /Library/Haskell/bin and then put that in their PATH +1 , considering that folks may also want to install their GHC with MacPorts. Regards, Heinrich Apfelmus -- http

<    1   2   3   4   5   6   7   8   9   >