[Haskell-cafe] Re: Matrices in Haskell

2007-03-20 Thread apfelmus
/people/okasaki/pubs.html#icfp99 Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Search monad

2007-03-20 Thread apfelmus
. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: How do I do conditional tail recursion in a monad?

2007-03-21 Thread apfelmus
((= 100) . fst) . scanl' (\(s,p) d - (d+s,p*d)) (0,1) . randomRs (1,6) Of course, this has the drawback that you cannot take further random numbers afterwards. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org

[Haskell-cafe] Re: Matrices in Haskell

2007-03-22 Thread apfelmus
and gives O(n) read-access to all elements of a row. If you need single element/row/column writing as well, I guess you're better off with Okasaki's nested square matrices. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: Rank-2-polymorphism problem

2007-03-24 Thread apfelmus
rank-2-variables is beneficial. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: HGL on Mac OS X

2007-04-01 Thread apfelmus
:~ apfelmus$ ghci ___ ___ _ / _ \ /\ /\/ __(_) / /_\// /_/ / / | | GHC Interactive, version 6.6, for Haskell 98. / /_\\/ __ / /___| | http://www.haskell.org/ghc/ \/\/ /_/\/|_| Type :? for help. Loading package base ... linking ... done. Prelude :m +Graphics.HGL

[Haskell-cafe] Re: Josephus problem and style

2007-04-04 Thread apfelmus
() can return a definite answer by looking at the first argument only). Note that this is very different from strict functional languages. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: Profiling makes memory leak go away? Is Haskell a practical language?

2007-04-10 Thread apfelmus
() by inspecting its code. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: k-minima in Haskell

2007-04-12 Thread apfelmus
the whole sort. Some algorithms are better than others for minimising the amount of work if not all of the list is demanded, but ideally, producing the first k elements will take O(n log k + k) time. You mean O(k * log n + n) of course. Regards, apfelmus

[Haskell-cafe] Re: k-minima in Haskell

2007-04-13 Thread apfelmus
[EMAIL PROTECTED] wrote: Quoting apfelmus [EMAIL PROTECTED]: You mean O(k * log n + n) of course. Erm, yes. You can do it in an imperative language by building a heap in O(n) time followed by removing k elements, in O(k log n) time. Ah, sorry, there are indeed to variants not comparable

[Haskell-cafe] Re: k-minima in Haskell

2007-04-14 Thread apfelmus
://article.gmane.org/gmane.comp.lang.haskell.general/15110 Regards, apfelmus ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Tutorial on Haskell

2007-04-16 Thread apfelmus
: With Haskell, I'm not only able to create my slides from scratch, but I can even completely explain the code to you in only 3 hours!. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell-cafe] Re: Tutorial on Haskell

2007-04-17 Thread apfelmus
of Ints table = array ((0,0),(lxs-1,lys-1)) [((i,j), cell i j x y) | (i,x) - zip [0..] xs, (j,y) - zip [0..] ys] ) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell-cafe] Re: GHC 6.7 and Associated Types

2007-04-17 Thread apfelmus
function StateType, you have to give it the required argument m = State s: type StateType (State s) = s get= State $ \s - (s, s) put s = State $ \_ - ((), s) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: GHC 6.7 and Associated Types

2007-04-17 Thread apfelmus
Maxime Henrion wrote: apfelmus wrote: Maxime Henrion wrote: class MonadState m where type StateType m :: * get :: m StateType put :: m StateType - m () As for instances: instance MonadState (State s) where type StateType = s

[Haskell-cafe] Re: Tutorial on Haskell

2007-04-18 Thread apfelmus
Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: How Albus Dumbledore would sell Haskell

2007-04-21 Thread apfelmus
Dan Weston wrote: -- Why is this not in Prelude? dup x = (x,x) It is (almost). It's called join (,) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: How Albus Dumbledore would sell Haskell

2007-04-22 Thread apfelmus
starts with the tutorials, so the audience doesn't know a common talk it could compare the Haskell tutorial to. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Higher order types via the Curry-Howard correspondence

2007-05-12 Thread apfelmus
and and at some point, languages like Epigram or Omega will take over the Haskell mailing list ;) But there is still lots of research to do for that. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: Lazy HTML parsing with HXT, HaXML/polyparse, what else?

2007-05-12 Thread apfelmus
. applicative parser combinators if you want to derive both passes from one parser description. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Higher order types via the Curry-Howard correspondence

2007-05-13 Thread apfelmus
Stefan Holdermans wrote: Apfelmus, Types like () or Int do not have a logical counterpart in propositional logic, although they can be viewed as a constant denoting truth. In other words, they may be thought of as being short-hand for the type expression (a,a) (where a is a fresh variable

[Haskell-cafe] Re: ANNOUNCE: Harpy -- run-time code generation library

2007-05-14 Thread apfelmus
[Relocated to haskell-cafe] Dirk Kleeblatt wrote: apfelmus wrote: Note that even currently, your operations cannot be strict in the address a label refers to because this may be determined later than the first use of the label. In other words, your example code fac = do [...] (1) jmp

[Haskell-cafe] Re: ANNOUNCE: Harpy -- run-time code generation library

2007-05-16 Thread apfelmus
Dirk Kleeblatt wrote: apfelmus wrote: Dirk Kleeblatt wrote: apfelmus wrote: I also think that having liftIO in the CodeGen-monad is plain wrong. I mean, CodeGen is a monad that generates code without any execution note that runCodeGen runs the code _generation_, executing the generated

[Haskell-cafe] Re: reversing big list with constant heap space used

2007-05-17 Thread apfelmus
though. Indeed, the list data structure is intended to be used from the left only. For double-end access, there are queues and Data.Sequence. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: Editor

2007-05-22 Thread apfelmus
them via keyboard shortcuts is faster. The answer is: * Test subjects consistently report that keyboarding is faster than mousing. * The stopwatch consistently proves mousing is faster than keyboarding. Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: Editor

2007-05-22 Thread apfelmus
Jules Bean wrote: apfelmus wrote: I can't know whether that's the case, but the fact that virtually all commands are invoked with the keyboard clashes with HID research reported at http://www.asktog.com/TOI/toi06KeyboardVMouse1.html It adresses the question whether selecting commands

[Haskell-cafe] Re: CYK-style parsing and laziness

2007-05-23 Thread apfelmus
j have to be sets is not related to laziness. (Although the code above exploits that (not $ null [k | ...]) returns True as soon as possible thanks to lazy evaluation). Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: CYK-style parsing and laziness

2007-05-26 Thread apfelmus
Steffen Mazanek wrote: apfelmus wrote The key point of the dynamic programming algorithm is indeed to memoize the results gs i j for all pairs of i and j. In other words, the insight that yields a fast algorithm is that for solving the subproblems gs i j (of which there are n^2), solution

[Haskell-cafe] Re: Slower with ByteStrings?

2007-05-26 Thread apfelmus
= interact $ unlines . filter (ubuntu `superset`) . lines Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Memoization

2007-05-27 Thread apfelmus
. Generalizing generalized tries. http://www.informatik.uni-bonn.de/~ralf/publications.html#J4 Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Memoization

2007-05-27 Thread apfelmus
/Existential_types http://en.wikibooks.org/wiki/Haskell/Existentially_quantified_types Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Language extensions [was: Memoization]

2007-05-27 Thread apfelmus
Dependencies. http://web.cecs.pdx.edu/~mpj/pubs/fundeps.html Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: GADT and typeclasses [was: Language extensions]

2007-05-28 Thread apfelmus
.) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Slower with ByteStrings?

2007-05-29 Thread apfelmus
for the intended application. This way, (sort ubuntu) is only computed once and the running time over many ys approaches O(n + m*log m).) Regards, apfelmus PS: Some exercises for the interested reader: 1) Still, the algorithm super has an advantage over superset. Which one? 2) Put xs into a good data structure

[Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread apfelmus
doesn't depend on whether y is declared or not. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread apfelmus
Mark T.B. Carroll wrote: apfelmus [EMAIL PROTECTED] writes: (snip) This not a correct Pascal program, nevertheless the parse succeeds just fine. The missing declaration for y will be detected when processing the abstract syntax tree further. The key point is that the shape of the abstract

[Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread apfelmus
Isaac Dupree wrote: apfelmus wrote: Mark T.B. Carroll wrote: I've been playing with Text.Parsers.Frisby to see how it stacks against other options and, while it's been great so far, I am finding that I can't encode a grammar where what's acceptable depends on what's already been parsed

[Haskell-cafe] Re: Language extensions

2007-05-30 Thread apfelmus
that doesn't match them. Dependent types for world-domination! :) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Has anyone looked into adding subtyping to Haskell?

2007-05-31 Thread apfelmus
a reappearance here (although not always explicitly mentioned). http://haskell.org/haskellwiki/Research_papers/ /Generics#Scrap_your_boilerplate.21 Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: I just don't get it (data structures and OO)

2007-06-03 Thread apfelmus
single galaxies with lookup 4 universe :: Maybe Galaxy Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: I just don't get it (data structures and OO)

2007-06-03 Thread apfelmus
apfelmus wrote: {-# OPTIONS_GHC -fglasgow-exts -#} import Prelude hiding (lookup) class Map map key a | map key - a where lookup :: key - map - Maybe a adjust :: (a - a) - key - map - map instance (Map m k m', Map m' k' a) = Map m (k,k') a where

[Haskell-cafe] Re: I just don't get it (data structures and OO)

2007-06-05 Thread apfelmus
in principle be built up from those. Maybe it helps if you elaborate on your concrete problem? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Finding points contained within a convex hull.

2007-06-06 Thread apfelmus
, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Keys and Maps [Was: Re: I just don't get it (data structures and OO)]

2007-06-06 Thread apfelmus
apfelmus wrote: I mean, if the problem is indeed to store all known planets in the universe, then it's indeed a database in nature and you have to support fine grained operations like delete :: Key - Database - Database insert :: Key - Item - Database - Database ... and so

[Haskell-cafe] Re: standard function

2007-06-06 Thread apfelmus
Steffen Mazanek wrote: is there a function f::[a-b]-a-[b] in the libraries? There is, it's called 'sequence' :) You need to import Control.Monad.Instances though, to get the famous reader monad ((-) a). Regards, apfelmus ___ Haskell-Cafe mailing list

[Haskell-cafe] Re: Keys and Maps [Was: Re: I just don't get it (data structures and OO)]

2007-06-07 Thread apfelmus
Grzegorz wrote: apfelmus apfelmus at quantentunnel.de writes: [ .. lengthy discussion and implementation .. ] As an example, we have Just Earth == lookup (at Milky Way / at Sun) universe assuming that universe :: Data.Map String (Data.Map String String) All this hard work

[Haskell-cafe] Re: Construct all possible trees

2007-06-13 Thread apfelmus
) - map (x:) $ inits' xs Regards, apfelmus PS: There is at least one other way to solve the problem. It works by generating all permutations first and parsing the resulting permutations in all possible ways as trees. PSS: A naive parsing algorithm is not as efficient as it good be because parses

[Haskell-cafe] Re: Construct all possible trees

2007-06-13 Thread apfelmus
Mirko Rahn wrote: apfelmus wrote: data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving (Show) permTrees xs = concat . takeWhile (not . null) . map (flip evalStateT xs . Traversable.sequence) $ trees select where select = StateT $ \xs - [(z

[Haskell-cafe] Re: Literate Priority Queue, plus question

2007-06-16 Thread apfelmus
or is there a way to actually use a binary tree there? To some extend, this would be pointless as well because that would make the Eratosthenes' Sieve inefficient again. It's much easier to stick with the old version then. Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: String Hashing

2007-06-18 Thread apfelmus
, there's no standard Data.Trie library but it's already under consideration http://hackage.haskell.org/trac/ghc/ticket/721 Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: String Hashing

2007-06-18 Thread apfelmus
Thomas Conway wrote: On 6/18/07, apfelmus [EMAIL PROTECTED] wrote: Do you need the hash function for a hash table or for fingerprints/signatures? In the former case, Tries are a much better choice. For launching your own trie, see also I'm actually using them for bucket addressing

[Haskell-cafe] Re: String Hashing

2007-06-19 Thread apfelmus
Thomas Conway wrote: On 6/19/07, apfelmus [EMAIL PROTECTED] wrote: Trie it is, not balanced tree. A logarithm in this would be new to me. :) True enough, my braino. So, accessing a key in a trie is O(key size in bits), not much different from a hash table. As a side node, Mr. Exp

[Haskell-cafe] Re: Collections

2007-06-20 Thread apfelmus
-Finger trees support efficient splits and concatenations: http://www.soi.city.ac.uk/~ross/papers/FingerTree.html In fact, you can build a plethora of data structures from them. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: To yi or not to yi, is this really the question? A plea for a cooperative, ubiquitous, distributed integrated development system.

2007-06-20 Thread apfelmus
serialize somehow check whether intensionally different arguments are extensionally the same and should have a unique serialization is no option because this problem is undecidable. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: haskell crypto is reaaaaaaaaaally slow

2007-06-21 Thread apfelmus
on the ByteString to get decent performance, for instance with a fold. Compare import Data.ByteString.Lazy as BS -- very slow checksum = foldl' xor 0 . BS.unpack -- blazingly fast checksum' = BS.foldl' xor 0 Regards, apfelmus ___ Haskell-Cafe mailing list

[Haskell-cafe] Re: To yi or not to yi, is this really the question? A plea for a cooperative, ubiquitous, distributed integrated development system.

2007-06-21 Thread apfelmus
working. But Clean can serialize function values. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Haskell serialisation, was: To yi or not to yi...

2007-06-21 Thread apfelmus
of the world, then they're not equivalent. You do want your compiler to preserve equivalence, don't you? You can put the internal representation of the argument into the state of the world. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Re: Haskell serialisation, was: To yi or not to yi...

2007-06-21 Thread apfelmus
++ + ++ show (n-k) ++ ) that gives intentionally different representations. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Collections

2007-06-22 Thread apfelmus
operations? http://research.microsoft.com/~simonpj/papers/stm/index.htm Also, write-once-read-many data structures (like lazy evaluation uses them all the time) are probably very easy to get locked correctly. Regards, apfelmus ___ Haskell-Cafe mailing list

[Haskell-cafe] Re: Need for speed: the Burrows-Wheeler Transform

2007-06-23 Thread apfelmus
Andrew Coppin wrote: apfelmus wrote: Note that the one usually adds an end of string character $ in the Burrows-Wheeler transform for compression such that sorting rotated strings becomes sorting suffices. Yeah, I noticed that the output from by program can never actually be reverted

[Haskell-cafe] Re: Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-24 Thread apfelmus
research area for exactly these problems. In the end, I think that strong types is only one thing that makes Haskell programs work after compilation. The other ones are higher-order functions and *purity*. No type system can achieve what purity offers. Regards, apfelmus

[Haskell-cafe] Re: Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-24 Thread apfelmus
a computer-checkable proof that shows that its result is indeed the smallest element from the list. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Practical Haskell question.

2007-06-25 Thread apfelmus
, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Practical Haskell question.

2007-06-25 Thread apfelmus
Could not become Root Putting Sudo into a module and making it abstract ensures that you can't break the invariant that stuff of type Sudo a will either be run as root or not at all. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread apfelmus
Claus Reinke wrote: apfelmus wrote: True enough, in a sense, a dynamically typed language is like a statically typed language with only one type (probably several by distinguishing function types) and many incomplete pattern matches. So, you can embed a dynamically typed language

[Haskell-cafe] Re: Practical Haskell question.

2007-06-25 Thread apfelmus
likely, and Haskell even tells you when your approach doesn't work without further specification :) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Collections

2007-06-25 Thread apfelmus
*code* is often cyclic...) So what does a compiler do to typecheck it? It represents your code as a graph and calculates strongly connected components. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org

[Haskell-cafe] Re: Propositional logic question

2007-06-26 Thread apfelmus
logic where ¬A \/ A always holds, but the task here is to prove it for intuitionistic logic. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Collections

2007-06-26 Thread apfelmus
Andrew Coppin wrote: apfelmus wrote: Andrew Coppin wrote: I see lots of *trees*, but no general graphs. (As in, *data* structures having cycles in them. My *code* is often cyclic...) So what does a compiler do to typecheck it? It represents your code as a graph and calculates

[Haskell-cafe] Re: Tree Guidance

2007-06-26 Thread apfelmus
at all. Up-pointers won't work in Haskell, you'll need a different approach. Can you elaborate on what your tree looks like and what it stores? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: Abstraction leak

2007-06-30 Thread apfelmus
(needlessly) the data stream. In case you only want to RLE the table, a simple Word32 field tracking the size of the Huffman table should be enough. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: Abstraction leak

2007-07-01 Thread apfelmus
Andrew Coppin wrote: apfelmus wrote: Am I missing something or why wouldn't encode, decode :: String - String encode = encodeRLE . encodeHuffman decode = decodeHuffman . decodeRLE do the job? This is probably what Andrew intends to do in his Java version. Note that this not only RLE

[Haskell-cafe] Re: Parsers are monadic?

2007-07-02 Thread apfelmus
an operation missing that supplies new left and right continuations at once. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Parsers are monadic?

2007-07-02 Thread apfelmus
apfelmus wrote: class DiMonad m where returnR :: a - m e a bindR :: m e a - (a - m e b) - m e b returnL :: e - m e a bindL :: m e a - (e - m e' a) - m e' a type TwoCont e a = (e - R) - (a - R) - R A final question remains: does the dimonad abstraction cover

[Haskell-cafe] Re: Sparse documentation

2007-07-04 Thread apfelmus
. Mathematica's front-end comes close to what I have in mind.). Why to learn and adjust wiki markup on a separate page? It's not difficult but it's unnecessary and thus wasted time. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Re: Deadlock in real number multiplication (Was: Where's the problem ?)

2007-07-05 Thread apfelmus
} instance Num DiffInt where (+) f g k = DI $ unDI g $! unDI f k evalDI :: DiffInt - Int evalDI f = unDI f 0 Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Nix for Hackage/Cabal

2007-07-06 Thread apfelmus
is that Nix uses a home-brew functional language for package descriptions. Of course, it would be ideal to have a Haskell DSL for that :) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell-cafe] Re: Nix for Hackage/Cabal

2007-07-06 Thread apfelmus
Duncan Coutts wrote: On Fri, 2007-07-06 at 16:47 +0200, apfelmus wrote: http://nix.cs.uu.nl/index.html I was under the impression that it didn't work on Windows. From another quick look at the website, it looks like that's right. Does anybody happen to know otherwise? I have no idea

[Haskell-cafe] Re: Too many packages on hackage? :-)

2007-07-08 Thread apfelmus
categorizations have the same effect. Also, I'd favor a greater distinction between applications and libraries. For browsing libraries, I like the wiki pages much more than hackage. Can't those two be merged into one? Regards, apfelmus ___ Haskell-Cafe mailing

[Haskell-cafe] Re: no-coding functional data structures via lazyness

2007-07-10 Thread apfelmus
prime sieves http://thread.gmane.org/gmane.comp.lang.haskell.cafe/19699 Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Defaulting to Rational [was: Number overflow]

2007-07-12 Thread apfelmus
Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Defaulting to Rational [was: Number overflow]

2007-07-12 Thread apfelmus
Bryan O'Sullivan wrote: apfelmus wrote: In a sense, the instances of Eq and Ord for floating point numbers are wrong. What about rolling new classes for approximate equality and ordering? class ApproxEq a where (≈) :: a - a - Bool -- almost equal to The problems

[Haskell-cafe] Re: Maintaining the community

2007-07-13 Thread apfelmus
to make it into the wiki. For mailing lists, archiving and quoting are considered fair use. Explicit permission from the author is required to put posts on the wiki since that means to license them under the Simple Permissive License. Regards, apfelmus

[Haskell-cafe] Re: List of authors happy to have work moved to theHaskell wiki

2007-07-15 Thread apfelmus
and laws in general aren't for the case when everybody behaves nicely, but for the case when things go awfully wrong. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Haskell shootout game

2007-07-16 Thread apfelmus
)) - Robot toRobot s doturn = Robot $ \arena - let (action, s') = doturn bf s in (action, toRobot s' doturn) The drawback is that it's no longer possible to save a snapshot of each program's state to disk and resume the fight later. Regards, apfelmus

[Haskell-cafe] Re: Maintaining the community

2007-07-16 Thread apfelmus
, apfelmus PS: hGetContents-hClose is particularly strange since you need operational semantics of lazy evaluation to understand it. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Clearly, Haskell is ill-founded

2007-07-16 Thread apfelmus
) respects consL and consR: observe . consL x = (Left x :) observe . consR y = (Right y :) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: xkcd #287 NP-Complete

2007-07-16 Thread apfelmus
` price + 1) . iterate (additem price) additem price = Map.map (map (price:)) . Map.mapMaybeWithKey clip . Map.mapKeysMonotonic (price +) clip cost x = if cost = purse then Just x else Nothing Regards, apfelmus ___ Haskell-Cafe mailing

[Haskell-cafe] Re: External Sort and unsafeInterleaveIO

2007-07-17 Thread apfelmus
, this will work like a tournament heap. See also http://article.gmane.org/gmane.comp.lang.haskell.cafe/24180 Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Is this haskelly enough?

2007-07-18 Thread apfelmus
: takeUntilConvergence epsilon xs = fst . head . dropUntil (( epsilon) . snd) $ zipWith (\x x' - (x,abs(x-x')) xs (tail xs) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: no-coding functional data structures via lazyness

2007-07-18 Thread apfelmus
that would destroy referential transparency. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Practise fingerspelling with Haskell! (Code cleanup request)

2007-07-18 Thread apfelmus
to a fixed word length anyway, so it doesn't matter. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Mux, was Re: Clearly, Haskell is ill-founded

2007-07-19 Thread apfelmus
) codata Xum x y = y :- Yum x y | x :~ Xum y x Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Practise fingerspelling with Haskell! (Code cleanup request)

2007-07-19 Thread apfelmus
/exps.html#list-comprehensions Of course, this is not very different from monadic expressions in the []-monad. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Practise fingerspelling with Haskell! (Code cleanup request)

2007-07-19 Thread apfelmus
] Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Producing MinimumValue

2007-07-20 Thread apfelmus
straightforward algorithm would be O(n). Actually, since Haskell is lazy and only the first element is required for minimumValue, the above algorithm should be O(n). Just for reference: http://thread.gmane.org/gmane.comp.lang.haskell.general/15007 Regards, apfelmus

[Haskell-cafe] Re: Equational Reasoning goes wrong

2007-07-22 Thread apfelmus
= _|_ . It seems that de-inlining can make things less defined. But I think that this phenomenon is an artifact of working with named functions, similar to name capture. I guess it's not present for anonymous lambda terms. Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: Practise fingerspelling with Haskell! (Code cleanup request)

2007-07-23 Thread apfelmus
Mirko Rahn wrote: apfelmus wrote: Note that using Peano-numbers can achieve the same effect of stopping the length calculation as soon as more than one character is different. data Nat = Zero | Succ Nat deriving (Eq, Ord) instance Num Nat where (Succ x) + y = Succ (x+y

[Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-23 Thread apfelmus
to have ByteStrings or Data.Sequence pattern matched like ordinary lists and I think that Data.Graph will blossom with proper view patterns. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: filterFirst

2007-07-23 Thread apfelmus
[a]. The error message complains that xs , which you actidentially gave as first parameter, is a list [a] and not a function (a - Bool). Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

<    1   2   3   4   5   6   7   8   9   >