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

2007-06-03 Thread apfelmus
t;>= lookup k' adjust f (k,k') m = adjust (adjust f k') k m You can lookup the 2nd planet in the 4th galaxy with lookup (4,2) universe :: Maybe Planet and you can update it via adjust (\planet -> planet {name = "Earth"}) (4,2) universe Thanks to type-classes and overloading, you can still access 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 > > instanc

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

2007-06-05 Thread apfelmus
tree or some other data structure, you can implement many operations without using per-element 'delete' or 'insert' although every operation can 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
contradict each other. The situation is similar to the knapsack problem. Regards, 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 -&

[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] Re: Keys and Maps [Was: Re: I just don't get it (data structures and OO)]

2007-06-07 Thread apfelmus
Grzegorz wrote: > apfelmus quantentunnel.de> writes: > > [ .. lengthy discussion and implementation .. ] > >> As an example, we have >> >> Just "Earth" == lookup (at "Milky Way" at "Sun") universe >> >> assuming that

[Haskell-cafe] Re: Construct all possible trees

2007-06-13 Thread apfelmus
"convolution" is lazy enough. Unfortunately, the Prelude function "inits" is *too strict* inits (1:_|_) == []:_|_ and not inits (1:_|_) == []:[1]:_|_ as one would expect. I think that this counts as bug in the Prelude. Here's a correct definition inits' xs = []:ca

[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 >> wh

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

2007-06-16 Thread apfelmus
should I just bite the bullet and change my priority queue > implementation into a sorted list 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' Sie

[Haskell-cafe] Re: String Hashing

2007-06-18 Thread apfelmus
ies.ps.gz Currently, 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

[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 dif

[Haskell-cafe] Re: Collections

2007-06-20 Thread apfelmus
eally want is "join" being the dual > of split - i.e. requiring all the keys in the rhs to be greater than > the keys in the lhs. My own AVL tree implementation has this operation > which is O(log n), which is rather better than union's O(n log n). 2-3-Finger trees support ef

[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
nymore (because f might inspect its argument). Also, having "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] Re: haskell crypto is reaaaaaaaaaally slow

2007-06-21 Thread apfelmus
ve to operate directly 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] 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
lize = return . Just That being said, serialization of function values is a practical problem. GHC's internal representation changes often and it would be very tedious to keep serialization 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
state of the world" to be part of the arguments. > If two programs behave differently for the same arguments and the same > state 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 th

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

2007-06-21 Thread apfelmus
unction: fmap compile . serialize = return . Just To illustrate the point, here's a serialize for integers: serialize :: Int -> IO String serialize n = do k <- randomRIO (1,n-1) return $ "(" ++show k ++ "+" ++ 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
rrent querying and updates, > and trying to manage the locking is quite hard enough as it is, > without trying to keep track of which postings vectors have closures > pointing to them! I guess you have considered Software Transactional Memory for atomic operations? http:/

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

2007-06-23 Thread apfelmus
you're generating a list of size N and then sorting > it. Lists are just not nice data structures to sort, nor are they nice to > have for large N. > > To get better speed and memory use, I think you'd want to avoid the > intermediate list in favor of some sort of stric

[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

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

2007-06-24 Thread apfelmus
ngly normalizing languages and dependent types are an active 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 syste

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

2007-06-24 Thread apfelmus
riants. I wanted to say that the code of minimum is likely to be shorter than 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
<$> performActionA <*> performActionB <*> performActionC 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
Sudo String etc. and that can only be run with sudo :: Sudo a -> IO (Either String a) sudo m = do b <- makeMeRoot if b then liftM Right $ act m else return $ Left "Could not become Root" Putting Sudo into a module and making it abstract ensures that y

[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

[Haskell-cafe] Re: Practical Haskell question.

2007-06-25 Thread apfelmus
oal possible. > And can it be done somehow in Haskell? Most 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
*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 strongly connected components. Regards, apfelmus ___ Haskell-Cafe ma

[Haskell-cafe] Re: Propositional logic question

2007-06-26 Thread apfelmus
X \/ Y } >A /\ B => C > > E. That works for classical 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

[Haskell-cafe] Re: Tree Guidance

2007-06-26 Thread apfelmus
ch node, but I have no idea how expensive this would > be in Haskell, or if it's necessary 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] Re: Tree Guidance

2007-06-27 Thread apfelmus
Chris Kuklewicz wrote: > apfelmus wrote: >> 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? > > "pointers" don't exist in Haskell, though they do exist in

[Haskell-cafe] Re: Abstraction leak

2007-06-30 Thread apfelmus
. Note that this not only RLE-encodes the Huffman table but also (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 maili

[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 A

[Haskell-cafe] Re: Abstraction leak

2007-07-01 Thread apfelmus
(n - length xs) return (xs ++ xss) To parse a huffman table, run the actual parser on the result of parseRLEAmount: parseHuffmanHeader = runParser parseHuffmanTable `liftM` parseRLEAmount (2^8) 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
, and it seems that it reduces clutter quite well compared to a bare TwoCont. A final question remains: does the dimonad abstraction cover the full power of TwoCont? I mean, it still seems like there's 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) -&

[Haskell-cafe] Re: Sparse documentation

2007-07-04 Thread apfelmus
t; version just sucks for me, especially for the intended haddock editing. The dream is to have WYSIWYG editing in-place (modulo keyboard/mouse control. 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

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

2007-07-05 Thread apfelmus
#x27; where (+) = Plus ... or in its bare essence newtype DiffInt = DI { unDI :: Int -> Int } 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] Nix for Hackage/Cabal

2007-07-06 Thread apfelmus
rs and such. The only drawback 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://w

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

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

2007-07-08 Thread apfelmus
nterfaces (or Interfaces ... > those two seem to overlap ;-). For me, a single page makes it difficult to browse the list to "see what's interesting" or to see what package would fit my current needs most. Scrambled categorizations have the same effect. Also, I'd f

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

2007-07-10 Thread apfelmus
mp.lang.haskell.general/15007 For primes , the heap shape has to be chosen carefully in order to ensure termination. It's the same problem that forces you to use foldr1 merge' instead of foldr1 merge . There's also a long thread about 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
nce ApproxEq (Floating Eps10) where x ≈ y = abs (x-y) < 1e-10 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 -&

[Haskell-cafe] Re: Maintaining the community

2007-07-13 Thread apfelmus
that are eligible 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.

[Haskell-cafe] Re: Indentation Creep

2007-07-14 Thread apfelmus
rie l m r -> delmin' l `mplus` delminMaybe m `mplus` delmin' r `mplus` (lift (writeTVar p Empty) >> mzero) Note that the step of replacing a trie with empty children with the constructor Empty is delayed since this is nicer to write down :) Regards, apfe

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

2007-07-15 Thread apfelmus
olfram.com/about/erics_commentary.html In the end, copyright 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
eam-based one toRobot :: String -> (BattleField -> String -> (Action,String)) -> 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

[Haskell-cafe] Re: Maintaining the community

2007-07-16 Thread apfelmus
best way to avoid trouble with hGetContents is to be introduced to it in a textbook chapter "IO and Files". Regards, apfelmus PS: hGetContents-hClose is particularly strange since you need operational semantics of lazy evaluation to understand it.

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

2007-07-16 Thread apfelmus
iring that they don't commute consL x . consR y ≠ consR y . consL x Or rather, one should require that the observation observe :: Mux x y -> Stream (Either x y) respects consL and consR: observe . consL x = (Left x :>) observe . consR y = (Right y :>) Regards, apfelmus

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

2007-07-16 Thread apfelmus
where add price = Map.unionsWith (++) . take (purse `div` 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, apfelm

[Haskell-cafe] Re: External Sort and unsafeInterleaveIO

2007-07-17 Thread apfelmus
n >> f ++ (kM next (if null b then Splay.deleteMin h >>else (Splay.insert b $ Splay.deleteMin h))) >> >> kMergeSort :: (Ord a) => [a] -> [a] >> kMergeSort l = kMerge $ blockify blocksize l Oh, I would have expected a lazy merges

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

2007-07-18 Thread apfelmus
ay to implement takeUntilConvergence is to zip the list with its tail: takeUntilConvergence epsilon xs = fst . head . dropUntil ((< epsilon) . snd) $ zipWith (\x x' -> (x,abs(x-x')) xs (tail xs) Regards, apfelmus ___ H

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

2007-07-18 Thread apfelmus
ll is not such a language. > I'd love it, however, if someone could surprise me by showing me the > idiom I'm missing here. Well, you can "reify" things by using constructors in the first place data Heap a = One a | Merge (Heap a) (Heap a) foldHeap = foldTree Merge . map

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

2007-07-18 Thread apfelmus
e, grouping words by length first and pairing the resulting groups is more efficient than filtering out all the pairs where length w /= length w'. But you restrict fingerspell 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
ux x y = Mux (Muy x y) data Muy x y = y :- Muy x y | x :~ Mux y x Probably, since Xum would be declared as data Yum x y = Yum (Xum x y) 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
bs) as The exact specification can be found at http://www.haskell.org/onlinereport/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
not . uncurry (zipWith (==)) wanted ws = [ (w,v) | (w:vs) <- tails ws, v <- vs, difference w v <= 1 ] 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
gt;> will always be at least O(n * log n), whereas a more 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://thr

[Haskell-cafe] Re: Equational Reasoning goes wrong

2007-07-22 Thread apfelmus
not . p) and break p := break p are clearly different, since the latter implies break p = _|_ . 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

[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

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

2007-07-23 Thread apfelmus
uctures are already abstract too. While the implementation of the abstract data structures themselves is unlikely to change, views make it much easier to use them. I think it would be a big win to have ByteStrings or Data.Sequence pattern matched like ordinary lists and I think that Data.Graph will

[Haskell-cafe] Re: filterFirst

2007-07-23 Thread apfelmus
rameters. The first parameter is a function (a -> Bool), the second is a list [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

[Haskell-cafe] Re: Code and Perf. Data for Prime Finders (was: Genuine Eratosthenes sieve)

2007-07-24 Thread apfelmus
inite list data Stream a = a :> Stream a triples ~(x :> ~(y :> ~(z :> zs))) = mergeA x y z : triples zs group ~(x :> ~(y :> ys)) = x :> y :> group (triples ys) root (A x xt) yss = x :> (root xt yss) root (B xs) ~(ys :> ~(zs :> zss) = ro

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

2007-07-24 Thread apfelmus
t because I'm fond of the proposal but simply because they're implemented and the pain of not using views is too big. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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

2007-07-25 Thread apfelmus
Jules Bean wrote: > Have you tried using pattern guards for views? > > f s | y :< ys <- viewl s = > | EmptyL <- viewl s = Hm, I'd simply use a plain old case-expression here f s = case viewl s of y :< ys -> ... EmptyL -> ... In other words, case-expressions are as po

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

2007-07-25 Thread apfelmus
Benjamin Franksen wrote: > apfelmus wrote: >> >> In other words, case-expressions are as powerful as any view pattern may >> be in the single-parameter + no-nesting case. > > This is how I do it, no pattern guards, no view patterns: > > zip :: Seq a -> Seq b -&

[Haskell-cafe] Re: Order of evaluation

2007-07-26 Thread apfelmus
27;s probably better to state it with denotational semantics alone: _|_ || b = _|_ Maybe you also want to know whether the second argument "is evaluated". This is answered by True || _|_ = True False || _|_ = _|_ Regards, apfelmus __

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

2007-07-26 Thread apfelmus
Dan Licata wrote: > apfelmus wrote: >> The idea is to introduce a new language extension, namely the ability to >> pattern match a polymorphic type. For demonstration, let >> >> class ViewInt a where >> view :: Integer -> a >> >> instance Vi

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

2007-07-25 Thread apfelmus
for > overloaded functions should be just as transparent as for > non-overloaded ones. That's what the real views would do modulo the probably minor inconvenience that one would need to use (:<) and (EmptyL) instead of (:) and []. I doubt that the latter can be reused. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Zippers, Random Numbers & Terrain

2007-07-30 Thread apfelmus
ugh. One problem is probably having a "point of reference", i.e. one needs a point (0,0) with a fixed height 0. In the bounded case, one has a rectangle to subdivide instead. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@hask

[Haskell-cafe] Re: infinite list of random elements

2007-07-31 Thread apfelmus
if you use IO a . Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: RLE in Haskell: why does the type variable get instantiated?

2007-07-31 Thread apfelmus
the monomorphism restriction only applies to constant applicative forms, i.e. point-free definitions of values. In other words, encode x = map (length &&& head) . group $ x will result in the proper polymorphic type. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Zippers, Random Numbers & Terrain

2007-08-01 Thread apfelmus
e 2D objects instead of intervals to split into two or more pieces. For instance, one can divide equilateral triangles into 4 smaller ones. In fact, it doesn't matter whether the starting triangle is equilateral or not when using the midpoints of the three sides to split it into four smaller trian

[Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread apfelmus
x27;m quite > eager to do it. This sounds suspicious, since the order of effects is of course important in the STM monad. Can you post an example of code you intend to abandon due to ugliness? I'd be astonished if there's no better way to write it. Regards, apfelmus __

[Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread apfelmus
ll. In fact, applicative functors are a very useful and powerful abstraction and to some extend, they exactly solve the problem of programming with monads in an applicative style. I would be sad if you'd ignore them in case they solve your STM-code problem without compiler extension. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: monad subexpressions

2007-08-04 Thread apfelmus
difference to $ is that <*> is left associative and allows for currying. I.e. <*> is like $ used in the following way ((foo $ x0) $ x1) $ x2 Note that you can even incorporate the TVar by defining your own generalized function application: apT :: STM (a -> b) -> TVar a -> STM

[Haskell-cafe] Re: Developing Programs and Proofs Spontaneously using GADT

2007-08-04 Thread apfelmus
plusFn (PlusS x) (PlusS y) = equalS (plusFn x y) with the "trivial" equality proofs for natural numbers equalZ = Proof id newtype Succ f a = InSucc { outSucc :: f (S a) } equalS (Proof eq) = Proof (outSucc . eq . InSucc) The newtype is just for making the type checker recognize that f (S a) is indeed of the form g a for some type constructor g . Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: creating graphics the functional way

2007-08-06 Thread apfelmus
Haskell? I've seen a zlib interface, > should be not too difficult to implement it in Haskell itself. Not that I know of. But gtk2hs has a Cairo-binding and I guess this one supports PNG. Note that this is vector graphics though, your approach is more general. Regards, apfelmus _

[Haskell-cafe] Re: Navigating Haddock

2007-08-06 Thread apfelmus
me functionality) Eh? These two are different types, you have to pack and unpack to convert between. But note that this most likely voids the performance gains from ByteString . In other words, if a library function needs a String , there's not much you can do. However, Henning

[Haskell-cafe] Re: Zippers, Random Numbers & Terrain

2007-08-06 Thread apfelmus
Thomas Conway wrote: > On 8/2/07, apfelmus <[EMAIL PROTECTED]> wrote: >> That concludes the infinite terrain generation for one dimension. For >> higher dimension, one just needs to use 2D objects instead of intervals >> to split into two or more pieces. For instance, on

[Haskell-cafe] Re: Type classes: Missing language feature?

2007-08-07 Thread apfelmus
= Lex Monomial deriving (Eq, Show, Num) I guess that the Show instance will add the constructor Lex , though. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: monad subexpressions

2007-08-08 Thread apfelmus
Bulat Ziganshin wrote: > apfelmus wrote: >> >> avoid the small layer of imperative code, of course. But the more you >> treat imperative code as somewhat pure, the greater the danger that the >> purely functional logic will be buried inside a mess of imperative code. >

[Haskell-cafe] Re: Language support for imperative code. Was: Re: monad subexpressions

2007-08-11 Thread apfelmus
Brian Hulley schrieb: apfelmus wrote: However, most "genuinely imperative" things are often just a building block for a higher level functional model. The ByteString library is a good example: the interface is purely functional, the internals are explicit memory control. It's a

[Haskell-cafe] Re: zip3, zip4 ... -> zipn?

2007-08-11 Thread apfelmus
alue of n at compile-time. I won't dwell into that, though. Also, applicative functors can help GHCi> :m +Control.Applicative GHCi> (\x y z -> x*(y+z)) <$> ZipList [1,2,3] <*> ZipList [-1,0,1] <*> ZipList [1,1,1] ZipList [0,2,6] GHCi> (t

[Haskell-cafe] Re: Language support for imperative code. Was: Re: monad subexpressions

2007-08-13 Thread apfelmus
Isaac Dupree schrieb: apfelmus wrote: Mutable data structures in the sense of ephemeral (= not persistent = update in-place) data structure indeed do introduce the need to work in ST since the old version is - by definition - not available anymore. Not in the quantum/information-theoretic

[Haskell-cafe] Re: a regressive view of support for imperative programming in Haskell

2007-08-13 Thread apfelmus
m (a -> m b) -> (m a -> m b) (@) f x = join (f `ap` x) hPutStr :: IO (Handle -> IO (String -> IO ())) handle :: IO Handle putStr :: IO (String -> IO ()) putStr = hPutStr @ handle With the infix type synonym type (~>) a b = a -> IO b we can also write hP

[Haskell-cafe] Re: a regressive view of support for imperative programming in Haskell

2007-08-13 Thread apfelmus
Stefan O'Rear schrieb: On Mon, Aug 13, 2007 at 04:35:12PM +0200, apfelmus wrote: My assumption is that we have an equivalence forall a,b . m (a -> m b) ~ (a -> m b) because any side effect executed by the extra m on the outside can well be delayed until we are supplied a value

[Haskell-cafe] Re: a regressive view of support for imperative programming in Haskell

2007-08-14 Thread apfelmus
Stefan O'Rear wrote: apfelmus wrote: >> My assumption is that we have an equivalence forall a,b . m (a -> m b) ~ (a -> m b) because any side effect executed by the extra m on the outside can well be delayed until we are supplied a value a. Well, at least when all ar

[Haskell-cafe] Re: Diagnosing stack overflow

2007-08-17 Thread apfelmus
ot;the excess is Just 5 characters" or "the excess is Nothing". Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Diagnosing stack overflow

2007-08-17 Thread apfelmus
Justin Bailey wrote: apfelmus wrote: Extracting the head and tail of ss with a let statement could lead to a huge unevaluated expression like rest = tail (tail (tail (...))) Even though they are probably forced, would breaking the head and tail apart via pattern-matching or a case

[Haskell-cafe] Re: List comprehension desugaring

2007-08-19 Thread apfelmus
pear as an intermediate result in the translation for empty Q. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Bi-directional Maps

2007-08-20 Thread apfelmus
27;t work anyway, what should left_insertWith (\new old -> new) 'a' 1 (fromList [('a',2),('b',1)]) do? I can't yield fromList [('a',1),('b',1)] since 1 has two keys now. Regards, apfelmus __

[Haskell-cafe] Re: Bi-directional Maps

2007-08-21 Thread apfelmus
ary_relation - the former would be a "bijection" http://en.wikipedia.org/wiki/Bijective_map Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Newbie question: Where is StackOverflow on the Wiki?

2007-08-21 Thread apfelmus
I need to find some way to automate making these trails :) ) Yes! We'd need such an automatic tool for the wikibook, too. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Newbie question: Where is StackOverflow on the Wiki?

2007-08-23 Thread apfelmus
g is a lambda abstraction) and only does simply typed lambda calculus (no type applications, no type classes). Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: help understanding lazy evaluation

2007-08-23 Thread apfelmus
on vary with the formalizer :) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: IO inside CGI

2007-08-24 Thread apfelmus
ight?). Is there some incantation I can perform to make this possible? Abracadabra, the incantation is liftIO :: IO a -> CGI a i.e. parse :: Maybe String-> CGI StdGen parse (Just x) = return $ read x parse Nothing = liftIO getStdGen Regards, apfelmus _

  1   2   3   4   5   6   7   8   9   >