[Haskell-cafe] Re: Classes: functional dependency (type - value)

2009-05-12 Thread Heinrich Apfelmus
! Instances are then simply a concrete value, like for example thething :: SomeThing Foo Bar Baz thething = SomeThing { f1 = id , f2 = filter (3) . map length , ... , role = Role1 } Regards, apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: I love purity, but it's killing me.

2009-05-29 Thread Heinrich Apfelmus
was first discovered/used when designing the DSL Lava, if I am informed correctly.) Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: using phantom types to validate html

2009-06-07 Thread Heinrich Apfelmus
/#washhtml which can statically ensure that only well-formed (with a few minor caveats I think) HTML is generated. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: Monoid wants a (++) equivalent

2009-07-02 Thread Heinrich Apfelmus
not equals from other languages. Forget Pascal: think of it as a diamond. I too like shiny diamonds, as exemplified in http://apfelmus.nfshost.com/monoid-fingertree.html Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list

[Haskell-cafe] Re: A Strict GCL Interpreter in Haskell

2009-07-03 Thread Heinrich Apfelmus
/wadler/papers/marktoberdorf/baastad.pdf Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: excercise - a completely lazy sorting algorithm

2009-07-07 Thread Heinrich Apfelmus
in xs !! k and only ask about the number of comparisons it takes to evaluate xs !! k , then it is possible to make the standard quicksort slightly lazier so that this works, too. Details in the link given above.) Regards, apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Implementing Las Vegas algorithms in Haskell

2009-07-07 Thread Heinrich Apfelmus
with these values. For a concrete example, http://apfelmus.nfshost.com/random-permutations.html might help. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: excercise - a completely lazy sorting algorithm

2009-07-08 Thread Heinrich Apfelmus
) | otherwise= Nothing or an ordinary sort qsort :: Ord a = [a] - [a] qsort = quicksort (\x a b - snd a ++ [x] ++ snd b) [] Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: excercise - a completely lazy sorting algorithm

2009-07-09 Thread Heinrich Apfelmus
is essentially what you coded. To read about hylo f g = cata g . ana f with quicksort as example again in a slightly different light, see also the following blog post by Ulisses Costa http://ulissesaraujo.wordpress.com/2009/04/09/hylomorphisms-in-haskell/ Regards, apfelmus -- http

[Haskell-cafe] Re: excercise - a completely lazy sorting algorithm

2009-07-11 Thread Heinrich Apfelmus
this. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: excercise - a completely lazy sorting algorithm

2009-07-12 Thread Heinrich Apfelmus
Raynor Vliegendhart wrote: On 7/9/09, Heinrich Apfelmus apfel...@quantentunnel.de wrote: Of course, some part of algorithm has to be recursive, but this can be outsourced to a general recursion scheme, like the hylomorphism hylo :: Functor f = (a - f a) - (f b - b) - (a - b) hylo f g

[Haskell-cafe] Re: Hylomorphisms (was: excercise - a completely lazy sorting algorithm)

2009-07-13 Thread Heinrich Apfelmus
repeat head = cata head . ana repeat and the intermediate data structure is Fix [] which is an infinite nested tower of infinite lists. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: Haskell Zippers on Wikibooks: teasing! :)

2009-07-16 Thread Heinrich Apfelmus
://www.cse.chalmers.se/~patrikj/poly/afp98/ It's a bit verbose at times, but you only need the first few chapters to get an idea about polynomial functors (sums and pairs) and mu . Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe

[Haskell-cafe] Re: can there be (hash-table using) O(n) version of this (I think currently) n log n algo?

2009-07-19 Thread Heinrich Apfelmus
of LT - sweep xs (y:ys) EQ - (x,y) : sweep xs ys GT - sweep (x:xs) ys This algorithm needs a proof of correctness, though. And it's longer that the Data.Set version, too. Regards, apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Proposal: TypeDirectedNameResolution

2009-07-28 Thread Heinrich Apfelmus
Just k - insertWith x (+1) m Nothing - insert x 1 m In the scope of with , ambiguous qualifications default to Data.Map . Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing

[Haskell-cafe] Re: Proposal: TypeDirectedNameResolution

2009-07-31 Thread Heinrich Apfelmus
= ... For each ambiguous function, the compiler creates a type class and corresponding instances and type inference will sort out the rest (or throw a type error). Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell

[Haskell-cafe] Re: Proposal: TypeDirectedNameResolution

2009-07-31 Thread Heinrich Apfelmus
that names only need to be qualified when they are ambiguous, which Map and ByteString are not. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Cyclic data declarations

2009-08-02 Thread Heinrich Apfelmus
page that concisely explains it right now. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Proposal: TypeDirectedNameResolution

2009-08-04 Thread Heinrich Apfelmus
Henning Thielemann wrote: Heinrich Apfelmus schrieb: Note that there are alternative solution for this particular problem. For instance, a version of qualified with different semantics will do; something like this import Data.List import sometimes qualified Data.Map as Map

[Haskell-cafe] Re: Cyclic data declarations

2009-08-04 Thread Heinrich Apfelmus
that you need to annotate them with the extraneous constructor. In fact, that's exactly the purpose of the constructor; think of it as an aid for the type checker. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: Improving MPTC usability when fundeps aren't appropriate?

2009-08-05 Thread Heinrich Apfelmus
= I :: Instance Bar moo bar ... -- usage Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: DDC compiler and effects; better than Haskell? (was Re: unsafeDestructiveAssign?)

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

[Haskell-cafe] Re: DDC compiler and effects; better than Haskell?

2009-08-13 Thread Heinrich Apfelmus
) = f x : map f xs ? Whenever I write a pure higher order function, I'd also have to document the order of effects. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: Keeping an indexed collection of values?

2009-08-20 Thread Heinrich Apfelmus
. That shouldn't happen if used correctly, but might give a headache when debugging. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Keeping an indexed collection of values?

2009-08-21 Thread Heinrich Apfelmus
Heinrich Apfelmus wrote: Job Vranish wrote: I've been in a situation a lot lately where I need to keep a collection of values, and keep track of them by a persistent index. module Store (Key, Store, empty, add, delete, lookup) where newtype Key = Key { int :: Int } empty

[Haskell-cafe] Re: Mapping over multiple values of a list at once?

2009-08-28 Thread Heinrich Apfelmus
hask...@kudling.de wrote: You are asked to iterate over the list and calculate the average value of each 3 neighbouring values. Lambda Fu, form 72 - three way dragon zip averages3 xs = zipWith3 avg xs (drop 1 xs) (drop 2 xs) where avg a b c = (a+b+c) / 3 Regards, apfelmus -- http

[Haskell-cafe] Re: hmatrix on os x

2009-09-08 Thread Heinrich Apfelmus
-options: -framework vecLib to the hmatrix.cabal file and possibly remove the other library flags. I suggest nagging the maintainer about this. (Also, I had to remove and Intel specific opcode when compiling on PowerPC.) Regards, apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Writing tool question (may be out of scope here)

2009-09-29 Thread Heinrich Apfelmus
, then have a paperback/PDF version. This might be what you're looking for: http://www.realworldhaskell.org/blog/2008/02/10/about-our-comment-system/ A pity the web interface wasn't written in Haskell. ;) Regards, apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Splitting data and function declarations over multiple files

2009-10-01 Thread Heinrich Apfelmus
not what you meant. Regards, 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 causes loop?

2008-12-03 Thread Apfelmus, Heinrich
it helps finding the loop. Regards, H. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Functional version of this OO snippet

2008-12-05 Thread Apfelmus, Heinrich
#Using_constructors_and_combinators Regards, H. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Functional version of this OO snippet

2008-12-05 Thread Apfelmus, Heinrich
or something. Regards, H. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Haskell haikus

2008-12-07 Thread Apfelmus, Heinrich
have a haiku I missed? Or even better, is anyone feeling poetically inspired tonight? :) drop autumn leaves until . all . pure . color . Left fail . frost otherwise Regards, H. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Re: Updating doubly linked lists

2009-01-01 Thread Apfelmus, Heinrich
. Regards, H. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Updating doubly linked lists

2009-01-02 Thread Apfelmus, Heinrich
) or to implement zippers for the structure I need (probably too hard for me). It's not too hard for you. You've got a whole haskell-cafe and #haskell at your fingertips, after all. ;) Regards, H. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: Updating doubly linked lists

2009-01-03 Thread Apfelmus, Heinrich
. :) Regards, H. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Updating doubly linked lists

2009-01-06 Thread Apfelmus, Heinrich
from the origin, n the side length of the grid) instead of O(1). Put differently, using Data.Tree.Zipper.parent on B will move you to C, not to A. I mean, O(d) may be fine for you, but it's not O(1) for everything as advertised. :) Regards, H. Apfelmus

[Haskell-cafe] Re: Updating doubly linked lists

2009-01-07 Thread Apfelmus, Heinrich
not constant time. Regards, H. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Monads aren't evil? I think they are.

2009-01-11 Thread Apfelmus, Heinrich
. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Haskell and C++ program

2009-01-15 Thread Apfelmus, Heinrich
disappeared completely. :) Regards, H. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Haskell and C++ program

2009-01-15 Thread Apfelmus, Heinrich
. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-15 Thread Apfelmus, Heinrich
monad and hoping that using it somehow gives an insight into the problem domain. Regards, H. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Comments from OCaml Hacker Brian Hurt

2009-01-16 Thread Apfelmus, Heinrich
/base/Data-Monoid.html I think it would be great if the haddock documentation itself were a wiki, so everyone can edit it right in place. Regards, H. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: Comments from OCaml Hacker Brian Hurt

2009-01-16 Thread Apfelmus, Heinrich
edition). http://www.amazon.com/ Introduction-Functional-Programming-using-Haskell/dp/0134843460 I think that this book is a good benchmark for measuring the amount of practice to be invested in learning Haskell. Regards, H. Apfelmus ___ Haskell

[Haskell-cafe] Re: Comments from OCaml Hacker Brian Hurt

2009-01-16 Thread Apfelmus, Heinrich
that I would try to learn a programming language, for example Python, without obtaining a paper book on it. Regards, H. Apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Functors [Comments from OCaml Hacker Brian Hurt]

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

[Haskell-cafe] Re: Comments from OCaml Hacker Brian Hurt

2009-01-18 Thread Heinrich Apfelmus
Paul Moore wrote: Apfelmus, Heinrich wrote: How to learn? The options are, in order of decreasing effectiveness university course teacher in person book irc mailing list online tutorial haskell wiki haddock documentation Reason

[Haskell-cafe] Re: Functors [Comments from OCaml Hacker Brian Hurt]

2009-01-18 Thread Heinrich Apfelmus
Andrew Coppin wrote: Heinrich Apfelmus wrote: Andrew Coppin wrote: instance (Monad m) = Functor m where fmap f ma = do a - ma; return (f a) While that's quite interesting from a mathematical point of view, how is this useful for programming purposes? Surely, you agree

[Haskell-cafe] Re: Improved documentation for Bool (Was: Comments from OCaml Hacker Brian Hurt)

2009-01-18 Thread Heinrich Apfelmus
) What is SQL, do they mean the SesQuiLinear forms that I'm familiar with? But what does it have to do with TerminalObjectCoSquared? I'm confused. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Re: Comments from OCaml Hacker Brian Hurt

2009-01-19 Thread Heinrich Apfelmus
david48 wrote: Apfelmus, Heinrich wrote: Hm, what about the option of opening Bird's Introduction on Functional Programming using Haskell in the section about fold? Monoid is on page 62 in the translated copy I've got here. I don't think that I would try to learn a programming language

[Haskell-cafe] Re: Comments from OCaml Hacker Brian Hurt

2009-01-20 Thread Heinrich Apfelmus
, and all the different data structures mentioned above arise by different choices for this monoid. Let me explain this monoid magic, albeit not in this message which would become far too long, but at http://apfelmus.nfshost.com/monoid-fingertree.html Regards, apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Comments from OCaml Hacker Brian Hurt

2009-01-20 Thread Heinrich Apfelmus
, thanks. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Why binding to existing widget toolkits doesn't make any sense

2009-02-03 Thread Heinrich Apfelmus
a 0th order language. Layout combinators in the spirit of TeX or Lout are more flexible while being simpler. In any case, a simple primitive grid :: [[Rect a]] - Rect a that arranges widgets in a rectangular grid should be enough for GUIs. Regards, apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Why binding to existing widget toolkits doesn't make any sense

2009-02-03 Thread Heinrich Apfelmus
nothing about usability. :-) Hehe, well given that CSS doesn't even have such a primitive... :) Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Elegant powerful replacement for CSS

2009-02-04 Thread Heinrich Apfelmus
bytecode consisting of 2 and 1. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Haddock Markup

2009-02-09 Thread Heinrich Apfelmus
this as a DSL? sumFor x xs f = \sum_{ ++ x ++ = ++ head xs ++ }^{ ++ last xs ++ } ++ f x Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: Painting logs to get a coloured tree

2009-02-10 Thread Heinrich Apfelmus
the list? The idea is that most of the tree structure survives in the list and can be reconstructed. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: Haskell.org GSoC

2009-02-12 Thread Heinrich Apfelmus
not. The goal is simply to drastically lower the bar of participation. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Haskell.org GSoC

2009-02-12 Thread Heinrich Apfelmus
/manual/en/function.preg-match.php But I'm not sure whether this form of commenting is the best way to write/improve documentation. (The many proposed regular expressions for validating e-mail addresses sure have a certain hilarity to them...) Regards, apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Looking for pointfree version

2009-02-12 Thread Heinrich Apfelmus
(dup op) That what you're looking for? :-) The pairs are of course an applicative functor (*) = uncurry (***) -- from Control.Arrow pure x = (x,x) pointwise op x y = pure op * x * y Regards, apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Haddock Markup

2009-02-13 Thread Heinrich Apfelmus
in practice. Writing a proper parser is too complicated if your language doesn't have parser combinators. :) Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: permuting a list

2009-02-15 Thread Heinrich Apfelmus
Jon Fairbairn wrote: Heinrich Apfelmus writes: The answer is a resounding yes and the main idea is that shuffling a list is *essentially the same* as sorting a list; the minor difference being that the former chooses a permutation at random while the latter chooses a very particular

[Haskell-cafe] Re: permuting a list

2009-02-15 Thread Heinrich Apfelmus
Felipe Lessa wrote: Heinrich Apfelmus wrote: It's fair, but may duplicate elements, i.e. it doesn't necessarily create a permutation. For example, rs could be something like rs = [5,3,3,3,2,4] But our sort doesn't discard values when the keys are the same. For example, [1,2,3,4

[Haskell-cafe] Re: forall ST monad

2009-02-16 Thread Heinrich Apfelmus
these existentially quantified types and how the ST monad works? Maybe http://en.wikibooks.org/wiki/Haskell/Polymorphism can help? Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

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

2009-02-16 Thread Heinrich Apfelmus
that is the Monad.Reader. :( Or can it? Thanks to the Simple Permissive License under which the Monad.Reader publishes, this is not necessarily a dichotomy, though. We can always convert it to hypertext afterwards. Regards, apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: forall ST monad

2009-02-17 Thread Heinrich Apfelmus
[a]) - T' = forall a. (T[a] - T') Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: How to create an online poll

2009-02-19 Thread Heinrich Apfelmus
think that's because FP is guilty of inventing the circular time traveling knots^1 used to correctly predict future election results in the first place. ^1 See also Russel O'Connor's article in http://www.haskell.org/sitewiki/images/1/14/TMR-Issue6.pdf Regards, apfelmus -- http

[Haskell-cafe] Re: forall ST monad

2009-02-25 Thread Heinrich Apfelmus
exists a. (a - _|_) = exists a. not a ? I mean, a can be a proposition now, so what about taking a = forall b.b = _|_ ? Does exists a imply that the example proposition constructed should true or is it enough to be able to construct a proposition at all? Regards, apfelmus -- http

[Haskell-cafe] Re: Zippers

2009-03-04 Thread Heinrich Apfelmus
the purpose of a zipper. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Zippers

2009-03-05 Thread Heinrich Apfelmus
believe with your code that it still equals 1. As apfelmus said, update needs to completely re-construct the zipper structure with the tied knot, which defeats the purpose of using a zipper in the first place. I got it. I dont't know what your expression tied knot is referring to but I got

[Haskell-cafe] Re: Zippers

2009-03-07 Thread Heinrich Apfelmus
Cristiano Paris wrote: Heinrich Apfelmus wrote: ... Such self-reference is usually called tying the knot, see also http://www.haskell.org/haskellwiki/Tying_the_Knot I didn't know. Would you call this Tying the knot as well? http://yi-editor.blogspot.com/2008/12/prototypes-encoding-oo

[Haskell-cafe] Re: A non-inductive Haskell proof?

2009-03-16 Thread Heinrich Apfelmus
++ ys)) ~= zip xs (tail xs) ++ [(last xs, head ys)] ++ zip ys (tail ys) Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Haskell Logo Voting has started!

2009-03-17 Thread Heinrich Apfelmus
for this vote, but I'm afraid that without assisting technology (instant and visual feedback), the voting process will more or less deteriorate to that due to the difficulty of creating quality input votes. Regards, apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Haskell Logo write-in candidate

2009-03-20 Thread Heinrich Apfelmus
Anton Tayanovskyy wrote: Didn't Haskell have a syntax king? I vote for a logo king: let Don Steward decide which logo is best. --A I propose to use concordet voting to appoint a new king from the 100 aspiring candidates ... ;) Regards, apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: about Haskell code written to be too smart

2009-03-25 Thread Heinrich Apfelmus
is (should be) high quality content. :) Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: about Haskell code written to be too smart

2009-03-25 Thread Heinrich Apfelmus
-liner and the explicit version. It says exactly what it means, almost in English. I couldn't agree more. In other words, splitAt is really to be thought of as a function that lives in the state monad. Regards, apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: about Haskell code written to be too smart

2009-03-25 Thread Heinrich Apfelmus
Manlio Perillo wrote: Heinrich Apfelmus ha scritto: I think you'd have had a much easier time by starting with a proper book right away, like Richard Bird's Introduction to Functional Programming in Haskell, accompanied by Real World Haskell. Unfortunately, one year ago Real World Haskell

[Haskell-cafe] Re: Grouping - Map / Reduce

2009-03-26 Thread Heinrich Apfelmus
developments like the blueprint technique by Bertram Felgenhauer. http://thread.gmane.org/gmane.comp.lang.haskell.cafe/15135 Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org

[Haskell-cafe] Re: Looking for practical examples of Zippers

2009-03-31 Thread Heinrich Apfelmus
the focus to the site from scratch does not take constant time, obviously. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Referential Transparency and Monads

2009-04-09 Thread Heinrich Apfelmus
that loop :: IO () loop = loop and loop' :: IO () loop' = putStr o loop' are indistinguishable in the IO a ~ World - (a, World) semantics. Both expressions would be _|_. But clearly, the latter produces some output while the former just hangs. Regards, apfelmus -- http

[Haskell-cafe] Re: Looking for the fastest Haskell primes algorithm

2009-04-16 Thread Heinrich Apfelmus
:: [Integer] primes' :: () - [Integer] for casual (i.e. throwaway program to solve a Project Euler problem) and for memory aware use respectively. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Proving correctness

2011-02-12 Thread Heinrich Apfelmus
. Admittedly, I don't know how many people actually do so... I did, I did! http://projects.haskell.org/operational/Documentation.html#proof-of-the-monad-laws-sketch Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing

Re: [Haskell-cafe] Haskell GUI

2011-02-16 Thread Heinrich Apfelmus
, though. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] A practical Haskell puzzle

2011-02-28 Thread Heinrich Apfelmus
to wrestle with the existential types for takeC and dropC a bit, but that shouldn't be much of a problem. For instance, you can fuse these functions into runLayers and hide the existential types somewhere in the recursion. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Re: [Haskell-cafe] A practical Haskell puzzle

2011-02-28 Thread Heinrich Apfelmus
quantification ). You have to encode it in some way, for instance with a data type data Exists f = forall c . Exists (f c) takeC :: Int - Compoz a b - Exists (Compoz a) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe

Re: [Haskell-cafe] A practical Haskell puzzle

2011-03-04 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

Re: [Haskell-cafe] A practical Haskell puzzle

2011-03-04 Thread Heinrich Apfelmus
that GHC has long supported existential types, just not the explicit syntax. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Computational Physics in Haskell

2011-04-01 Thread Heinrich Apfelmus
://hackage.haskell.org/package/hmatrix Best 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] Testing Implementation vs Model - Records or Type Classes?

2011-04-08 Thread Heinrich Apfelmus
of IO, it is a bit harder to test automatically, so the model might be useful to have. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

Re: [Haskell-cafe] Testing Implementation vs Model - Records or Type Classes?

2011-04-09 Thread Heinrich Apfelmus
with this is that I need the FlexibleContexts extension to do that. There goes Haskell2010 compatibility. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

Re: [Haskell-cafe] Why not Darcs?

2011-04-23 Thread Heinrich Apfelmus
that way. At some point, you need something that works at another level than pure functions. What the *hell* do you do? I think a better invective would be amazing. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe

Re: [Haskell-cafe] More ideas for controlled mutation

2011-04-25 Thread Heinrich Apfelmus
obligation! (At least, I don't see any obvious one. Maybe a clever abuse of parametricity helps.) It might be an option in Agda, though. In that light, it is entirely reasonable that you have to use unsafePerformIO . Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Re: [Haskell-cafe] Inputs to classic FRP: unsafeInterleaveIO/unsafePerformIO

2011-04-26 Thread Heinrich Apfelmus
://apfelmus.nfshost.com/blog/2011/04/24-frp-push-driven-sharing.html Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Inputs to classic FRP: unsafeInterleaveIO/unsafePerformIO

2011-04-27 Thread Heinrich Apfelmus
Ryan Ingram wrote: Apfelmus, I hope you don't abandon your efforts, at least for the selfish reason that I enjoy reading your blog entries about trying to implement it! :D My reasoning was that a temporary demand-driven implementation would allow me to release the library sooner; I want

Re: [Haskell-cafe] Inputs to classic FRP: unsafeInterleaveIO/unsafePerformIO

2011-04-29 Thread Heinrich Apfelmus
Ryan Ingram wrote: Heinrich Apfelmus wrote: However, even in a demand-driven implementation, there is one optimization that I would like make: when there are multiple external events, say e1 and e2, the network splits into subnetworks that react only to one of the inputs. For instance, your

Re: [Haskell-cafe] ANNOUNCE: iterIO-0.1 - iteratee-based IO with pipe operators

2011-05-06 Thread Heinrich Apfelmus
on the Producer/Transformer/Consumer trilogy. I'd love to hear thoughts on the issue, especially from David. I vastly prefer the names Producer/Transformer/Consumer over the others. Then again, I never quite understood what Iteratees were all about in the first place. Best regards, Heinrich Apfelmus

Re: [Haskell-cafe] Server hosting

2011-05-07 Thread Heinrich Apfelmus
Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Status of Haskell + Mac + GUIs graphics

2011-05-18 Thread Heinrich Apfelmus
be worth to include the extra hoops (EnableGUI) in the GLFW package. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Status of Haskell + Mac + GUIs graphics

2011-05-18 Thread Heinrich Apfelmus
Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Status of Haskell + Mac + GUIs graphics

2011-05-19 Thread Heinrich Apfelmus
cross-platform GUI toolkits is that they embed a lot of wisdom about platform quirks (Cocoa is particularly annoying) that you would have to solve again. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list

<    2   3   4   5   6   7   8   9   >