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

2009-10-19 Thread Heinrich Apfelmus
count yesRed yesBlue hd1); } 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 use bracket properly ?

2009-10-20 Thread Heinrich Apfelmus
://www.haskell.org/onlinereport/lexemes.html#sect2.7 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: ANN: Data.Stream 0.4

2009-10-23 Thread Heinrich Apfelmus
they operationally the same: tail undefined = undefined and: tailStrict undefined = undefined I concur, a strict tail is enough. Writing foo xs = bar (tail xs) has the same effect as foo xs = bar (tailStrict xs) since the evaluation of xs is deferred in both cases. Regards, apfelmus -- http

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

2009-10-23 Thread Heinrich Apfelmus
as O(n + k log n) ): http://apfelmus.nfshost.com/quicksearch.html The remark about O(k) space complexity of the other algorithm is interesting, since this means that it's not even allowed to copy its argument of size O(n) . Regards, apfelmus -- http://apfelmus.nfshost.com

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

2009-10-29 Thread Heinrich Apfelmus
to find, though. 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: Applicative but not Monad

2009-10-31 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: Experiments with defunctionalization, church-encoding and CPS

2009-11-01 Thread Heinrich Apfelmus
the fromJust will reduce the run-time of the data Maybe benchmark by 75%. Comments? 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: 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
have an easier time wrangling all the different variants you want. Note that Control.Monad.Omega is not a monad. The law of associativity is broken, at least in a direct sense. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe

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

2009-11-10 Thread Heinrich Apfelmus
in the first place. But once proven, the former can be reused ad libitum. 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: Long running Haskell program

2009-11-12 Thread Heinrich Apfelmus
: Prelude.undefined 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: (state) monad and CPS

2009-11-12 Thread Heinrich Apfelmus
recursion is less important. Also, code that looks tail recursive in a strict language will actually not be tail recursive in Haskell. A well-known example is the definition foldl and applied in the fashion of foldl (+) 0 [0..10] Regards, apfelmus -- http://apfelmus.nfshost.com

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

2009-11-18 Thread Heinrich Apfelmus
, which I hope to upload shortly. Any reason for the name change? I liked normal form being part of NFData and rnf . Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

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

2009-11-25 Thread Heinrich Apfelmus
, but it would be handy to have support for impredicativity in GHC if someone stumbles upon a useful one. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[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
Nicolas Pouillard wrote: Henning Thielemann wrote: @Apfelmus: For practical purposes I think Train should have swapped type parameters in order to make Functor act on the type of the list elements. data Train b a = Wagon a (Train b a) | Loco b The functor on the Loco

[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

[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

[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: 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: 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: 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: 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: 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: 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: 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: 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-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: 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: 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: 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] 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: 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] 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: philosophy of Haskell

2010-08-18 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: philosophy of Haskell

2010-08-20 Thread Heinrich Apfelmus
Ertugrul Soeylemez wrote: Heinrich Apfelmus wrote: In particular, the World - (a,World) model is unsuitable even without concurrency because it cannot distinguish loop, loop' :: IO () loop = loop loop' = putStr c loop' I interpret the EDSL model to be the operational semantics

[Haskell-cafe] Re: Fwd: Semantics of iteratees, enumerators, enumeratees?

2010-08-23 Thread Heinrich Apfelmus
to the iteratee abstraction. 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: Semantics of iteratees, enumerators, enumeratees?

2010-08-23 Thread Heinrich Apfelmus
Luke Palmer wrote: Heinrich Apfelmus wrote: Conal Elliott wrote: For anyone interested in iteratees (etc) and not yet on the iteratees mailing list. I'm asking about what iteratees *mean* (denote), independent of the various implementations. In my world view, iteratees are just a monad M

[Haskell-cafe] Re: Fwd: Semantics of iteratees, enumerators, enumeratees?

2010-08-24 Thread Heinrich Apfelmus
xs assuming a function fromString :: String - Enumerator To get an actual result from an Iteratee, we only need a way to run it on the empty stream. runOnEmptyString :: Iteratee a - Maybe a Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Fwd: Semantics of iteratees, enumerators, enumeratees?

2010-08-24 Thread Heinrich Apfelmus
[] where go xs EOF= Yield xs EOF go xs (Chunk ys) = Continue $ go (xs++ys) (using the API from http://ianen.org/articles/understanding-iteratees/ ) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe

[Haskell-cafe] Re: Higher-order algorithms

2010-08-24 Thread Heinrich Apfelmus
/okasaki/jfp98.ps 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: Semantics of iteratees, enumerators, enumeratees?

2010-08-25 Thread Heinrich Apfelmus
the number of elements in the input count :: Monad m = Iteratee m Int count = go 0 where go n = eof = \b - case b of True - return n False - symbol go $! (n+1) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Fwd: Semantics of iteratees, enumerators, enumeratees?

2010-08-25 Thread Heinrich Apfelmus
Jason Dagit wrote: Heinrich Apfelmus wrote: I'm curious, can you give an example where you want to be explicit about chunking? I have a hard time imagining an example where chunking is beneficial compared to getting each character in sequence. Chunking seems to be common in C for reasons

[Haskell-cafe] Re: Fwd: Semantics of iteratees, enumerators, enumeratees?

2010-08-25 Thread Heinrich Apfelmus
Nicolas Pouillard wrote: Heinrich Apfelmus wrote: There are also enumerators and enumeratees. I think that purpose of enumerator = run an iteratee on multiple sources (i.e. first part of the input from a Handle , second part from a String ) I would say

[Haskell-cafe] Re: Fwd: Semantics of iteratees, enumerators, enumeratees?

2010-08-26 Thread Heinrich Apfelmus
Daniel Fischer wrote: John Lato wrote: Heinrich Apfelmus wrote: Do you have an example where you want chunking instead of single character access? I am unable to think of any examples where you want chunking for any reason other than efficiency. For many hashing or de/encryption algorithms

[Haskell-cafe] Re: Crypto-API is stabilizing

2010-08-27 Thread Heinrich Apfelmus
- B.ByteString, decrypt :: B.ByteString - B.ByteString, keyLength :: BitLength, serialize :: B.ByteString} rsa :: RandomGen g = BitLength - g - ((Key,Key), g) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Fwd: Semantics of iteratees, enumerators, enumeratees?

2010-08-27 Thread Heinrich Apfelmus
Daniel Fischer wrote: Heinrich Apfelmus wrote: Daniel Fischer wrote: For many hashing or de/encryption algorithms, chunking is more natural than single-character access. Even when the chunk lengths are unpredictable? After all, unlike with fread in C, you can't request the next chunk

[Haskell-cafe] Re: Fwd: Semantics of iteratees, enumerators, enumeratees?

2010-09-01 Thread Heinrich Apfelmus
]: http://www.reddit.com/r/haskell/comments/ar4wb/understanding_iteratees/c0j0f3r 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: Crypto-API is stabilizing

2010-09-08 Thread Heinrich Apfelmus
examples that use buildKeyPair and type classes can be reformulated in terms of Key with this additional field. That's because buildKeyPair actually expects a type argument; the cipher filed merely shifts that argument to the value level. Regards, Heinrich Apfelmus -- http

[Haskell-cafe] Re: recommendations for reading list?

2010-09-09 Thread Heinrich Apfelmus
(unless you are indeed a working mathematician), his choice of topics and examples does not really help understanding the Haskell side of category theory. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: Introducing The Monads Presentation Slides

2010-09-17 Thread Heinrich Apfelmus
aditya siram wrote: Ok, I feel dumb. I have the slides hosted elsewhere now and I can't figure out how to change the Reddit link. Any help is appreciated! You can't change the link on Reddit, but you can delete the old submission and make a new one. Regards, Heinrich Apfelmus -- http

[Haskell-cafe] Re: Distribution needs

2010-09-30 Thread Heinrich Apfelmus
(The link doesn't seem to work, only http://gwolf.org/blog is available.) 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: I still cannot seem to get a GUI working under Windows.

2010-10-02 Thread Heinrich Apfelmus
, but it is a more forthright form of showing that your work is valued than a silent download or virtual nod. [1]: http://flattr.com Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: I still cannot seem to get a GUI working under Windows.

2010-10-02 Thread Heinrich Apfelmus
revisit projects I value a lot every month anyway, which boils down to a larger share in the end. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: I still cannot seem to get a GUI working under Windows.

2010-10-02 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: ANNOUNCE: Haskell XML Toolbox Version 9.0.0

2010-10-09 Thread Heinrich Apfelmus
://www.haskell.org/HaXml/icfp99.html but it appears to me that representing them as type Filter a b = a - [b] allows the use of the list monad, which would highlight the similarity between list comprehensions and working with XML trees. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Who is afraid of arrows, was Re: ANNOUNCE: Haskell XML Toolbox Version 9.0.0

2010-10-13 Thread Heinrich Apfelmus
= instead of = . 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: Who is afraid of arrows, was Re: ANNOUNCE: Haskell XML Toolbox Version 9.0.0

2010-10-15 Thread Heinrich Apfelmus
f x `orElse` deep f x 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: Who is afraid of arrows, was Re: ANNOUNCE: Haskell XML Toolbox Version 9.0.0

2010-10-18 Thread Heinrich Apfelmus
C. McCann wrote: Heinrich Apfelmus wrote: Combined with = / you have multiple reading direction in the same expression, as in expression ( c . b . a ) `liftM` a1 = a2 = a3 reading order 6 5 41 2 3 That's why I'm usually using = instead of = . Does

[Haskell-cafe] Re: Who is afraid of arrows, was Re: ANNOUNCE: Haskell XML Toolbox Version 9.0.0

2010-10-18 Thread Heinrich Apfelmus
Malcolm Wallace wrote: Heinrich Apfelmus wrote: Personally, I would be much happier with the slogan HXT = XML transformations with filters. Browsing through Manuel's thesis, I discover that your combinators are quite slick ( , choiceA , when, guards ), it's just that they are a very

[Haskell-cafe] Re: A rant against the blurb on the Haskell front page

2010-10-19 Thread Heinrich Apfelmus
to finishing it: http://www.haskell.org/haskellwiki/Haskell_a_la_carte 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.com idea: strike forces

2010-10-30 Thread Heinrich Apfelmus
everything that comes up on the fly. There is no better way to ensure usability of an application than to write it while heavily using it (and aiming for a large usability / features ratio). Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

[Haskell-cafe] Re: Parsing workflow

2010-11-01 Thread Heinrich Apfelmus
is very useful for avoiding capturing input in the second argument of manyTill 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: Haskell is a scripting language inspired by Python.

2010-11-04 Thread Heinrich Apfelmus
from Haskell. Haskell itself (or rather the design committee) got the idea from SASL (1976) and Miranda (1986), though it goes way back to the 1960s, as described in section 4.1 Layout of http://www.haskell.org/haskellwiki/History_of_Haskell Regards, Heinrich Apfelmus -- http

Re: [Haskell-cafe] Making type-incompatible strategies interchangeable

2010-12-18 Thread Heinrich Apfelmus
again.) 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] V.I.P.s and the associativity of merge'

2010-12-30 Thread Heinrich Apfelmus
as it sounds, since we didn't know them well in the first place anyway). More worryingly, changing the tree shape now affects correctness. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe

Re: [Haskell-cafe] V.I.P.s and the associativity of merge'

2010-12-31 Thread Heinrich Apfelmus
Will Ness wrote: Heinrich Apfelmus writes: Here an example where the VIP merge would give a different result bad = tfold $ (1:10:undefined) : (2:3:5:undefined) : (4:undefined) : error bad We have ghci bad [1,2*** Exception: bad but the VIP version would give

Re: [Haskell-cafe] V.I.P.s and the associativity of merge'

2010-12-31 Thread Heinrich Apfelmus
Will Ness wrote: Heinrich Apfelmus writes: Here an example where the VIP merge would give a different result bad = tfold $ (1:10:undefined) : (2:3:5:undefined) : (4:undefined) : error bad We have ghci bad [1,2*** Exception: bad but the VIP version would give

Re: [Haskell-cafe] Type System vs Test Driven Development

2011-01-08 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: Overriding a Prelude function?

2009-04-23 Thread Heinrich Apfelmus
it an instance of Monad . :D 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: Overriding a Prelude function?

2009-04-23 Thread Heinrich Apfelmus
hiding (()) interactive:1:0: parse error on input `import' Prelude Not on the command line, you have to put import Prelude hiding ((), (=), return) into your rand.hs file. Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe

[Haskell-cafe] Re: Overriding a Prelude function?

2009-04-23 Thread Heinrich Apfelmus
Achim Schneider wrote: Well, you obviously need an initial seed: rollDie 0xdeadbeef ~ (rollDie ~ rollDie) Achim means (rollDie ~ (rollDie ~ rollDie)) 0xdeadbeef Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list

[Haskell-cafe] Re: Is Haskell a Good Choice for Web Applications? (ANN: Vocabulink)

2009-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

[Haskell-cafe] Re: Is Haskell a Good Choice for Web Applications? (ANN: Vocabulink)

2009-05-07 Thread Heinrich Apfelmus
. Is that an accurate description? Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

<    1   2   3   4   5   6   7   8   9   >