[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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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-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: 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: 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: 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: 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: 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-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: 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: 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-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-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-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: 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-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: 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-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: 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: 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: 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: 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: 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: 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-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-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: 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: When the unknown is unknown

2010-06-24 Thread Heinrich Apfelmus
, 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: Finding zipper for custom tree

2010-07-02 Thread Heinrich Apfelmus
: ContextDTree a = List (DList (a * DTree a) * a) After all, what you describe is only the context of DTree a within a single level, but it might be many levels down in the tree. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe

[Haskell-cafe] Re: Finding zipper for custom tree

2010-07-02 Thread Heinrich Apfelmus
the derivative of List first: List' x = List x * List x and then you can use the chain rule to find DTreeF . Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: finding the right mathematical model

2010-07-07 Thread Heinrich Apfelmus
can also use a toy implementation like type Graph = [(Node, -- Department [Node]) -- List of Departments it shares revenue to ] To test whether a graph has cycles (looping mapping), you can use a depth-first search. Regards, Heinrich Apfelmus -- http

[Haskell-cafe] Re: Memoization in Haskell?

2010-07-09 Thread Heinrich Apfelmus
might get reconstructed redundantly. (However, there are other strategies for memoization that are persistent across calls.) It should be f = \n - memo ! n where memo = .. so that memo is shared across multiple calls like f 1 , f 2 etc. Regards, Heinrich Apfelmus -- http

[Haskell-cafe] Re: Memoization in Haskell?

2010-07-10 Thread Heinrich Apfelmus
Gregory Crosswhite wrote: Heinrich Apfelmus wrote: Gregory Crosswhite wrote: You're correct in pointing out that f uses memoization inside of itself to cache the intermediate values that it commutes, but those values don't get shared between invocations of f; thus, if you call f

[Haskell-cafe] Re: Equivalence of two expressions

2010-07-12 Thread Heinrich Apfelmus
such problems. As Michael already mentioned, the problem is undecidable in general since it includes group rings. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: lambda calculus and equational logic

2010-07-15 Thread Heinrich Apfelmus
, say product [1..5] - 1 * product [2..5] - .. - 120 is a proof that the initial and the final expression denote the same value. The Curry-Howards correspondence is about the type system, viewing types as logical propositions and programs as their proofs. Regards, Heinrich Apfelmus

[Haskell-cafe] Re: Finding zipper for custom tree

2010-07-16 Thread Heinrich Apfelmus
Backhouse, P Jansson, J Jeuring, L Meertens Generic Programming - An Introduction - http://www.cse.chalmers.se/~patrikj/poly/afp98/ A corresponding chapter in the wikibook (Datatype algebra) has not been written, so far. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Designing a DSL?

2009-10-03 Thread Heinrich Apfelmus
Günther Schmidt wrote: there are numerous examples on how to implement a DSL, but I haven't been able to figure out how to design one. I mean I have a pretty good idea of the problem domain, I've coded it over and over again until I got it right. Now I'd like to express that part as a DSL

[Haskell-cafe] Re: Generalizing IO

2009-10-07 Thread Heinrich Apfelmus
David Menendez wrote: Floptical Logic wrote: The code below is a little interactive program that uses some state. It uses StateT with IO to keep state. My question is: what is the best way to generalize this program to work with any IO-like monad/medium? For example, I would like the

[Haskell-cafe] Re: Any example of concurrent haskell application?

2009-10-09 Thread Heinrich Apfelmus
Daryoush Mehrtash wrote: I am trying to learn more about concurrent applications in Haskell by studying an existing a real application source code. I would very much appreciate if you can recommend an application that you feel has done a good job in implementing a real time application in

[Haskell-cafe] Re: How to use bracket properly ?

2009-10-19 Thread Heinrich Apfelmus
zaxis wrote: It works very well. However, as i am used to C style so i want convert it into winSSQ count noRed noBlue = do { let yesRed = [1..33] \\ noRed; let yesBlue = [1..16] \\ noBlue; bracket (openFile ssqNum.txt WriteMode) (hClose) (\hd1 - pickSSQ count yesRed yesBlue

[Haskell-cafe] Re: How to use bracket properly ?

2009-10-20 Thread Heinrich Apfelmus
zaxis wrote: oh! thanks! But why ? The gory details can be found in the Haskell 98 Report: syntax of do expressions http://www.haskell.org/onlinereport/exps.html#do-expressions syntax of decls http://www.haskell.org/onlinereport/decls.html Details for the layout rule

[Haskell-cafe] Re: ANN: Data.Stream 0.4

2009-10-23 Thread Heinrich Apfelmus
Bas van Dijk wrote: 1) What's the difference between your: tail ~(Cons _ xs) = xs and the more simple: tailStrict (Cons _ xs) = xs ? I know they're desugared to: tail ys = let Cons _ xs = ys in xs and: tailStrict ys = case ys of Cons _ xs - xs respectively. But aren't they

[Haskell-cafe] Re: Time and space complexity of take k . sort

2009-10-23 Thread Heinrich Apfelmus
Paul Johnson wrote: Paul Johnson wrote: takeLargest k = take k . sort Because sort is lazily evaluated this only does enough sorting to find the first k elements. I guess the complexity is something like O(n*k*log(k)). Correction: O(n*log(k)) It's O(n + k log k) (which is the same

[Haskell-cafe] Re: wxMac/wxHaskell focus problem, a quick solution

2009-10-29 Thread Heinrich Apfelmus
Simon Peyton-Jones wrote: Would someone like to make a Haskell wiki page explaining all this? Very helpful for people using wx for the first time. Maybe there is one already? The enableGUI thing is mentioned here: http://www.haskell.org/haskellwiki/WxHaskell/MacOS_X Not that easy to

[Haskell-cafe] Re: Applicative but not Monad

2009-10-31 Thread Heinrich Apfelmus
Dan Weston wrote: Can you elaborate on why Const is not a monad? return x = Const x fmap f (Const x) = Const (f x) join (Const (Const x)) = Const x This is not Const , this is the Identity monad. The real Const looks like this: newtype Const b a = Const b instance Monoid b =

[Haskell-cafe] Re: Experiments with defunctionalization, church-encoding and CPS

2009-11-01 Thread Heinrich Apfelmus
Eugene Kirpichov wrote: I took a toy problem - find the first node satisfying a predicate in a binary tree, started with a naive Maybe-based implementation - and experimented with 3 ways of changing the program: - Church-encode the Maybe - Convert the program into CPS - Defunctionalize

[Haskell-cafe] Re: Experiments with defunctionalization, church-encoding and CPS

2009-11-01 Thread Heinrich Apfelmus
David Menendez wrote: On Sun, Nov 1, 2009 at 7:12 AM, Heinrich Apfelmus apfel...@quantentunnel.de wrote: Even then, the results are mixed. The Church-encoding shines in GHCi as it should, but loses its advantage when the code is being compiled. I guess we have to look at the core if we want

[Haskell-cafe] Re: Experiments with defunctionalization, church-encoding and CPS

2009-11-02 Thread Heinrich Apfelmus
David Menendez wrote: Heinrich Apfelmus wrote: David Menendez wrote: Heinrich Apfelmus wrote: Even then, the results are mixed. The Church-encoding shines in GHCi as it should, but loses its advantage when the code is being compiled. I guess we have to look at the core if we want to know

[Haskell-cafe] Re: Fair diagonals

2009-11-04 Thread Heinrich Apfelmus
Luke Palmer wrote: I believe you can get what you want using the diagonal function from Control.Monad.Omega. product xs ys = [ [ (x,y) | y - ys ] | x - xs ] diag2 xs ys = diagonal (product xs ys) I think if you separate taking the cartesian product and flattening it, like this, you might

[Haskell-cafe] Re: is proof by testing possible?

2009-11-10 Thread Heinrich Apfelmus
Conor McBride wrote: and you can calculate how much testing is enough by computing an upper bound on the polynomial degree of the expression. (The summation operator increments degree, the difference operator decreases it, like in calculus.) This is sometimes described as the reflective

[Haskell-cafe] Re: Long running Haskell program

2009-11-12 Thread Heinrich Apfelmus
David Menendez wrote: I think replacing put s with put $! s should guarantee that the state is evaluated. If you're using get and put in many place in the code, you could try something along these lines: newtype SStateT s m a = S { unS :: StateT s m a } deriving (Monad, etc.) instance

[Haskell-cafe] Re: (state) monad and CPS

2009-11-12 Thread Heinrich Apfelmus
jean-christophe mincke wrote: I do not master all the subtilities of lazy evaluation yet and perhaps tail recursivity does not have the same importance (or does not offer the same guarantees) in a lazy language as it does in a strict language. Yep, that's the case. With lazy evaluation, tail

[Haskell-cafe] Re: ANNOUNCE: deepseq-1.0.0.0

2009-11-18 Thread Heinrich Apfelmus
Simon Marlow wrote: I've just uploaded deepseq-1.0.0.0 to Hackage http://hackage.haskell.org/package/deepseq This provides a DeepSeq class with a deepseq method, equivalent to the existing NFData/rnf in the parallel package. I'll be using this in a newly revamped parallel package,

[Haskell-cafe] Re: Pointfree rank-2 typed function

2009-11-25 Thread Heinrich Apfelmus
Simon Peyton-Jones wrote: | Are there workarounds for uses of impredicative types, or do we lose the | ability to express certain programs as a result? There's usually a workaround. I include the msg I sent below. I tried to use impredicative polymorphism once to create polymorphic values

[Haskell-cafe] Re: Are there standard idioms for lazy, pure error handling?

2009-12-01 Thread Heinrich Apfelmus
:: (a - c - c) - (b - c) - Train a b - c fold f g (Loco b) = g b fold f g (Wagon a t) = f a (fold f g t) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org

[Haskell-cafe] Re: Help mixing pure and IO code

2009-12-01 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: Optimization with Strings ?

2009-12-04 Thread Heinrich Apfelmus
problems. Also, knowing Haskell's evaluation model helps a lot http://en.wikibooks.org/wiki/Haskell/Graph_reduction Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org

[Haskell-cafe] Re: I miss OO

2009-12-04 Thread Heinrich Apfelmus
languages too, like logic languages or constraint languages (does the latter exist?) Related: Paul Hudak, Mark P. Jones. Haskell vs. Ada vs. C++ vs. Awk vs. ... An Experiment in Software Prototyping Productivity http://www.haskell.org/papers/NSWC/jfp.ps Regards, Heinrich Apfelmus

[Haskell-cafe] Re: Are there standard idioms for lazy, pure error handling?

2009-12-04 Thread Heinrich Apfelmus
to the dog itself. Another, not entirely serious, suggestion: ;) data Life a b = Work a (Life a b) | TheEnd b Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: universal binary version of Haskell Platform?

2009-12-06 Thread Heinrich Apfelmus
rather click on an application icon in the Dock. You can write an applescript similar to Open Terminal Here from http://www.entropy.ch/software/applescript/ and endow it with a custom icon. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Are there standard idioms for lazy, pure error handling?

2009-12-09 Thread Heinrich Apfelmus
/Caboose makes sense too and swapping the arguments is less natural to read. It's a bifunctor! :D I don't really mind. The application list that may end with an error uses a fixed b , so putting the a at the end makes sense. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

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

2009-12-13 Thread Heinrich Apfelmus
) memory instead of an infinite amount and foldl (+) 0 [1..n] taking O(n) memory as opposed to foldl' (+) 0 [1..n] which only takes O(1) memory. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell

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

2009-12-13 Thread Heinrich Apfelmus
Jason Dagit wrote: withPending :: (a - Patch - a) - IO a And withPending would start the streaming and make sure that the stream cannot be visible as a data dependency outside of withPending. [...] Heinrich Apfelmus wrote: In other words, exporting only a foldl' -like interface does

  1   2   3   4   >