Re: [Haskell-cafe] Re: Bathroom reading

2007-08-17 Thread Albert Y. C. Lai
Dan Weston wrote: I hate to be a party pooper, but isn't this just: f = foldr (\a z - (a:snd z,fst z)) ([],[]) This takes less time to grok and takes no longer to run. For each type with exported constructors, one can always write deconstructors for it, if not already found in libraries.

Re: [Haskell-cafe] Re: Bi-directional Maps

2007-08-21 Thread Albert Y. C. Lai
apfelmus wrote: Hugh Perkins wrote: Arguably there are two possible implementations, one that enforces one-to-one mapping, and one which allows multiple values, in either direction. Terminology reminder :) - the latter is called (binary) relation http://en.wikipedia.org/wiki/Binary_relation

Re: [Haskell-cafe] #haskell irc channel reaches 400 users

2007-08-21 Thread Albert Y. C. Lai
Andrew Coppin wrote: ...does this mean Haskell is officially harder to understand than Lisp, Java, Perl and O'Caml? :-} (OTOH, does this mean Haskell is easier to understand than PHP or C++?) Or, Haskell is the easiest to understand of them all. Reason: Extremely large channel means so hard

Re: [Haskell-cafe] GHC optimisations

2007-08-22 Thread Albert Y. C. Lai
Neil Mitchell wrote: Other rules that could be interesting are: forall a b. fromInteger a + fromInteger b = fromInteger (a + b) forall a b. fromInteger a * fromInteger b = fromInteger (a * b) This is wrong, since the class function can do what it wants. Imagine: instance Num String where

Re: [Haskell-cafe] Parsec is being weird at me

2007-08-25 Thread Albert Y. C. Lai
Andrew Coppin wrote: Prelude :m Text.ParserCombinators.Parsec Prelude Text.ParserCombinators.Parsec parseTest (endBy anyToken (char '#')) abc# Loading package parsec-2.0 ... linking ... done. parse error at (line 1, column 1): unexpected b expecting # I read the doc and determined that it is

Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Albert Y. C. Lai
Peter Hercek wrote: So the question is what am I missing? Any nice use cases where fixed point search is so good that it is worth the trouble with figuring out new and new variable names for essentially the same stuff? When I write functional code, I do find myself writing recursions much

Re: [Haskell-cafe] interaction between OS processes

2007-09-01 Thread Albert Y. C. Lai
Andrea Rossato wrote: loop s = do putStrLn s Most likely, the content of s sits in a local buffer and never leaves this process, following most OS conventions and as others point out. Another process waiting for it will deadlock. Most similar process deadlock problems are not

Re: [Haskell-cafe] let and fixed point operator

2007-09-01 Thread Albert Y. C. Lai
Mitar wrote: I did once try to learn Prolog. And failed. Miserably. You should backtrack at this point and try again differently. :-) There is likely a problem if he has inadvently walked past a cut. XD ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] interaction between OS processes

2007-09-02 Thread Albert Y. C. Lai
Bryan O'Sullivan wrote: Your problem may be buffering-related (I haven't read your code to check), but if so, there's a fair likelihood that it has nothing to do with the OS. GHC's runtime does its own buffer management on Handles. It's quite possible that your deadlock lies at that level,

Re: [Haskell-cafe] interaction between OS processes

2007-09-02 Thread Albert Y. C. Lai
Albert Y. C. Lai wrote: It is similar to saying, if you use Haskell, you don't have to learn dependent typing. Ah, but knowing dependent typing informs you of certain typing issues and how to use the Haskell type system more successfully. This is despite tutorials on dependent typing talk

Re: [Haskell-cafe] Learning advice

2007-09-07 Thread Albert Y. C. Lai
Brent Yorgey wrote: Then one day he met someone else who said she was also a race car driver, but her car was different -- she called it a Haskar. It had a top speed of 400 miles per hour, no steering wheel (you just lean whichever way you want to go, she said), I wish I could just lean

Re: [Haskell-cafe] Where would I find fromInt?

2007-09-09 Thread Albert Y. C. Lai
To the tune of the theme song of Ghostbusters: You've got an Int But you want Double Who do you call? fromIntegral! (The inverse conversion requires you to think about rounding first.) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Monad.Reader 8: Haskell, the new C++

2007-09-12 Thread Albert Y. C. Lai
ok wrote: So we have C++ : imperative language whose type system is a Turing-complete functional language (with rather twisted syntax) Haskell: functional language whose type system is a Turing- complete logic programming language (with rather twisted

Re: [Haskell-cafe] What on earth

2007-09-20 Thread Albert Y. C. Lai
Miguel Mitrofanov wrote: tfoldr (-) 1 [4,3] = 4-3-(-1) = 2 Erm? You mean foldr? Blame it on OCR. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] 'data' syntax - a suggestion

2007-09-27 Thread Albert Y. C. Lai
[EMAIL PROTECTED] wrote: Data with where? You haven't heard about GADTs? To avoid clashing with GADT's where, I propose to rename ok's keyword to wherein, or wheretype, or something data B k v = E | F b b wherein type b = B k v data B k v = E | F b b wheretype b = B k v (I also propose

Re: [Haskell-cafe] New slogan for haskell.org

2007-10-05 Thread Albert Y. C. Lai
Don Stewart wrote: It was raised at CUFP today that while Python has: Python is a dynamic object-oriented programming language that can be used for many kinds of software development. It offers strong support for integration with other languages and tools, comes with extensive

Re: [Haskell-cafe] New slogan for haskell.org

2007-10-05 Thread Albert Y. C. Lai
The Hackathon is a good opportunity to collect preliminary data. Imagine: All other communities are still at the stage of we feel productivity. We have our data shows productivity. That puts us at a completely different level --- light-years above the crowd. Haskell --- because we put the

Re: [Haskell-cafe] Dual Parser Failure???

2007-10-12 Thread Albert Y. C. Lai
PR Stanley wrote: failure :: (Parser a) failure = \inp - [] The code might contain some syntax errors and I'd be grateful for any corrections. It looks right conceptually. Depending on the definition of Parser, you may need failure = P (\inp - []) or whatever constructor name instead of

Re: [Haskell-cafe] New slogan for haskell.org

2007-10-12 Thread Albert Y. C. Lai
Tim Newsham wrote: You are not expected to understand this. http://swtch.com/unix/ Hehehe! Elite system programmers understand it. If it is rephrased in terms of continuations, elite lambda calculus programmers will also understand it. You are not expected to be convinced this, but it

Re: [Haskell-cafe] Can every monad can be implemented with Cont? (was: New slogan for haskell.org)

2007-10-13 Thread Albert Y. C. Lai
jeff p wrote: I think this is referring to Andrzej Filinski's paper Representing Layered Monads in which it shown that stacks of monads can be implemented directly (no layering) by using call/cc and mutable state. I have been unable to see how to bring its crucial reify and reflect to

Re: [Haskell-cafe] Functional Programming Books

2007-10-16 Thread Albert Y. C. Lai
Richard Bird's Introduction to Functional Programming using Haskell, second edition exceeds other introductory books by introducing laws (e.g., fold laws, fusion laws), efficiency issues (including the stack overflow question, deforestation), and monad transformers. IMO these are

Re: [Haskell-cafe] Re: Suspected stupid Haskell Question

2007-10-18 Thread Albert Y. C. Lai
Thomas Hartman wrote: Since I'm interested in the stack overflow issue, and getting acquainted with quickcheck, I thought I would take this opportunity to compare your ordTable with some code Yitzchak Gale posted earlier, against Ham's original problem. As far as I can tell, they're the

Re: [Haskell-cafe] Automatic file closing after readFile

2007-10-21 Thread Albert Y. C. Lai
Magnus Therning wrote: I'll certainly try to look into all of that. However, I suspect your suggestion doesn't scale very well. On my original code it's easy, it was less than 10 lines, but how do I know where to start looking if it's a program of 100 lines, or 1000 lines? The problem could

Re: [Haskell-cafe] More on Fibonacci numbers

2007-11-08 Thread Albert Y. C. Lai
Stefan O'Rear wrote: On Wed, Nov 07, 2007 at 10:30:30AM +0100, [EMAIL PROTECTED] wrote: [I changed the subject, so (hopefully) rare people who just follow the thread may miss it, but I couldn't look at the name of Fibonacci with two errors in it anymore...] People with real e-mail clients

Re: [Haskell-cafe] Re: New slogan for haskell.org

2007-12-05 Thread Albert Y. C. Lai
Combinators get my code done, tralalalala, laughing out loud! Quickcheck locates all of my bugs, tralalalala, laughing out loud! Fusion laws make my code run fast, tralala, lalala, lololol! Folks, I'm so done, Merry Christmas, tralalalala, laughing out loud!

Re: [Haskell-cafe] [OT] A nice organized collection of threads in Haskell-Cafe

2007-12-09 Thread Albert Y. C. Lai
Bryan O'Sullivan wrote: Albert Y. C. Lai wrote: I can't blame you for being not observant. Afterall, this is precisely what I'm alluding to with everyone can haz PC [...] Please don't flame people on the list. I'm flaming an idea, not people on the list

Re: [Haskell-cafe] [OT] A nice organized collection of threads in Haskell-Cafe

2007-12-10 Thread Albert Y. C. Lai
Vimal wrote: What is the difference between In-Reply-To and References? There was a time In-Reply-To was for emails and References was for Usenet. Nowadays emails have both In-Reply-To and References. Usenet still sticks with just References. ___

Re: role of seq, $!, and bangpatterns illuminated with lazy versus strict folds Re: [Haskell-cafe] What is the role of $!?

2007-12-10 Thread Albert Y. C. Lai
Thomas Hartman wrote: -- (myfoldl f q ) is a curried function that takes a list -- If I understand currectly, in this lazy fold, this curried function isn't applied immediately, because -- by default the value of q is still a thunk myfoldl f z [] = z myfoldl f z (x:xs) = ( myfoldl f q ) xs

Re: [Haskell-cafe] Re: MonadFix

2007-12-19 Thread Albert Y. C. Lai
Joost Behrends wrote: @Daniel: no, this doesn't solve the stack problem. These are the primefactors of 2^120+1: [97,257,673,394783681,4278255361,46908728641]. oddFactors k n | otherwise = oddFactors (k+2) n could eventually push 394783681-673 function calls onto the stack before finding the

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Albert Y. C. Lai
Justin Bailey wrote: Given this function: dropTest n = head . drop n $ [1..] I get a stack overflow when n is greater than ~ 550,000 . Is that inevitable behavior for large n? Is there a better way to do it? Just for fun, throw in dropTest :: Int - Int and experiment again! :)

Re: [Haskell-cafe] Re: Wikipedia on first-class object

2007-12-27 Thread Albert Y. C. Lai
Achim Schneider wrote: [n..] == [m..], the first thing I notice is n == m n+1 == m+1 , which already expresses all of infinity in one instance and can be trivially cancelled to n == m , which makes the whole darn thing only _|_ if n or m is _|_, which no member of [n..] can be as long as

Re: [Haskell-cafe] Haskell-cafe reply-to etiquette

2007-12-28 Thread Albert Y. C. Lai
Justin Bailey wrote: When I joined the haskell-cafe mailing list, I was surprised to see the reply-to header on each message was set to the sender of a given message to the list, rather than the list itself. That seemed counter to other mailing lists I had been subscribed to, but I didn't think

Re: [Haskell-cafe] Missing join and split

2007-12-28 Thread Albert Y. C. Lai
Mitar wrote: I am really missing the (general) split function built in standard Haskell. I do not understand why there is something so specific as words and lines but not a simple split? The same goes for join. Don't forget Text.Regex.splitRegex.

Re: [Haskell-cafe] Re: Re: Re[2]: Wikipedia on first-class object

2007-12-29 Thread Albert Y. C. Lai
Ben Franksen wrote: Of course this doesn't prove that humans can, in principle, decide equality for any pair of functions. But neither has the opposite been proved. Premise: The human should still give the reasoning behind his/her decisions. The reasoning should be within a proof system

Re: [Haskell-cafe] Re: Difference lists and ShowS

2008-01-03 Thread Albert Y. C. Lai
apfelmus wrote: I don't know a formalism for easy reasoning about time in a lazy language. Anyone any pointers? Note that the problem is already present for difference lists in strict languages. http://homepages.inf.ed.ac.uk/wadler/topics/strictness-analysis.html especially strictness

Re: [Haskell-cafe] Re: Quanta. Was: Wikipedia on first-class object

2008-01-07 Thread Albert Y. C. Lai
Achim Schneider wrote: Erm... There is this story about some military (US afair) training a neural net to detect tanks in images, I can't find the link right now. It worked, with amazing 100% accuracy. Then they threw another batch of images at the net. It worked, with devastating 50%

Re: [Haskell-cafe] Please allow beginners to vocalize code. = :: - - -

2008-01-08 Thread Albert Y. C. Lai
Richard Kelsall wrote: Imagine two experienced Haskell programmers on the phone, one reading a Haskell program snippet to the other. u can txt msg XD ^^--- unworded symbol people grasp just fine. ___ Haskell-Cafe mailing list

[Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-28 Thread Albert Y . C . Lai
Some docs are in a miserable state of being incomplete. And then some programmers are in a miserable state of not respecting docs when the docs are complete. Why should anyone expect deleteBy (=) 5 [0..10] to accomplish anything meaningful, if he/she respects the written docs? Today someone

[Haskell-cafe] Cabal lib (Setup.hs), --package-db, --enable-shared, haskell platform

2010-07-17 Thread Albert Y . C . Lai
I accidentally found a rarely encountered omission in Cabal (the lib, because via Setup.hs) by building Haskell Platform as shared libs from source. It is rare because you have to use both --enabled-shared and --package-db=blah together to run into it. --package-db=blah is already rare enough

[Haskell-cafe] Re: Cabal lib (Setup.hs), --package-db, --enable-shared, haskell platform

2010-07-17 Thread Albert Y . C . Lai
and I forgot to say the Cabal lib tried is already version 1.8.0.6 ghc is 6.12.3 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Problem with reloading modules in GHC API

2010-07-21 Thread Albert Y . C . Lai
Try adding more delay between the two loadings, e.g., make me press enter, and hope I am not faster than a computer: main = do     writeTarget arg     func0 - compileTarget     putStrLn $ show $ func0 2 getLine     writeTarget arg*2     func1 - compileTarget     putStrLn $ show $ func1 2

Re: [Haskell-cafe] Heavy lift-ing

2010-07-23 Thread Albert Y. C. Lai
On 10-07-23 02:43 PM, michael rice wrote: liftM2 :: Monad m = (a1 - a2 - r) - m a1 - m a2 - m r [...] What does it mean to promote a function to a monad? liftM2 f m1 m2 is canned code for do a1 - m1 a2 - m2 return (f a1 a2) for example liftM2 f [s,t] [x,y] is [f s x, f s y, f t x, f

Re: [Haskell-cafe] Laziness question

2010-07-31 Thread Albert Y. C. Lai
On 10-07-31 01:30 PM, Brandon S Allbery KF8NH wrote: On 7/31/10 12:59 , michael rice wrote: But since both still have eval x to *thunk* : *thunk*, g evaluates to a deeper level? The whole point of laziness is that f *doesn't* have to eval x. To elaborate, in computer-friendly syntax: f x

Re: [Haskell-cafe] Preview the new haddock look and take a short survey

2010-08-04 Thread Albert Y. C. Lai
On 10-08-04 01:00 AM, Mark Lentczner wrote: Sample pages: http://www.ozonehouse.com/mark/snap-xhtml/index.html On the Contents page, among the collapsable trees: when I click on a link that is also a parent, such as Snap.Http.Server and Text.Templating.Heist, it has the undesirable side

Re: [Haskell-cafe] Network.CGI.Compat.pwrapper

2007-02-12 Thread Albert Y. C. Lai
Bjorn Bringert wrote: pwrapper is not an HTTP server, though the Haddock comment can make you think so. pwrapper allows you to talk *CGI* over a TCP port, but I have no idea why anyone would like to do that. Here is a scenerio. I want a basic web application: someone makes a request, and my

Re: [Haskell-cafe] functional database queries

2007-02-21 Thread Albert Y. C. Lai
Henning Thielemann wrote: At http://www.haskell.org/hawiki/HaskellDbTutorial it is described, how database queries can be modelled with a monad. However, I wonder if this is also possible without monads. Say, writing DB.map col1 $ DB.filter (\row - col2 row == 10+2) myTable for SELECT col1

Re: [Haskell-cafe] Re: functional database queries

2007-02-21 Thread Albert Y. C. Lai
[EMAIL PROTECTED] wrote: Albert Y. C. Lai wrote: If and only if the database is a purely functional immutable data structure, this can be done. [...] Many interesting databases are not purely functional immutable; most reside in the external world and can spontaneously change behind your

Re: [Haskell-cafe] process

2007-02-22 Thread Albert Y. C. Lai
h. wrote: But it does not work as I expected. As long as there is no need to put some input after having received some output it is no problem, but real interaction seems not possible. Right, this particular program works just for a particular interaction. What real interaction do you have

Re: [Haskell-cafe] A real Haskell Cookbook

2007-02-22 Thread Albert Y. C. Lai
Call me a technophile, but it saddens me that ASCII has already held us back for too many decades, and looks like it will still hold us back for another. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread Albert Y. C. Lai
All record fields are in the same namespace, and furthermore this is also the same namespace of functions and class methods. In other words you cannot have two record types containing the same field name, and you cannot have a record field and a function using the same name, and you cannot

Re: [Haskell-cafe] Re: Trouble with record syntax and classes

2007-02-27 Thread Albert Y. C. Lai
Thomas Nelson wrote: data ISine = Sine Integer Integer Integer String | MetaSine Integer Integer Integer [ISine] Having advised you to use different field names for different record types last time, I now confuse you by saying you can share field names in the different cases

Re: [Haskell-cafe] ghc6.8: hiding uninstalled package?

2008-01-17 Thread Albert Y. C. Lai
Magnus Therning wrote: This might seem like a silly question, but what's the reasoning behind the following behaviour? % ghc-pkg list dataenc /usr/lib/ghc-6.8.2/package.conf: % ghc --make -hide-package dataenc -isrc UT.hs ghc-6.8.2 : unknown package: dataenc Hiding an uninstalled package

Re: [Haskell-cafe] hxt memory useage

2008-01-24 Thread Albert Y. C. Lai
Matthew Pocock wrote: I've been using hxt to process xml files. Now that my files are getting a bit bigger (30m) I'm finding that hxt uses inordinate amounts of memory. I have 8g on my box, and it's running out. As far as I can tell, this memory is getting used up while parsing the text,

Re: [Haskell-cafe] parsec3 pre-release [attempt 2]

2008-02-06 Thread Albert Y. C. Lai
Is it good or bad to add: instance (MonadIO m) = MonadIO (ParsecT s u m) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Response to unexpected doubt in haskell-cafe (was: Doubting Haskell)

2008-02-16 Thread Albert Y. C. Lai
Alan Carter wrote: if((fp = fopen(...)) != NULL) { if(fgets(...) != NULL) { printf(...); } fclose(...) } This reminds me of a 1976 article written by David Parnas and Harald Würges: Response to undesired events in software systems. Since it's old, it is harder to

Re: [Haskell-cafe] Error I haven't seen before

2008-02-28 Thread Albert Y. C. Lai
Jefferson Heard wrote: Main: No match in record selector Protein.go_terms data R = A { sa :: Int } | B { sb :: Int } sa (A 0) works (as expected). sa (B 0) gives *** Exception: No match in record selector Main.sa I think that explains your problem.

Re: [Haskell-cafe] Generating a random list

2008-03-01 Thread Albert Y. C. Lai
The following is in ghci 6.8.2 with default options (e.g., default heap and stack). G denotes the ghci prompt. At some points ghci will use 500MB of memory. Be sure you have enough physical memory. G :m + Data.List System.Random G let f n = take n randoms (mkStdGen 0)) :: [Float] I define f

Re: [Haskell-cafe] HXT and types in Control.Arrow.ArrowTree

2008-03-23 Thread Albert Y. C. Lai
Robert Vollmert wrote: In short, I'm constantly running into what appear to be artificial type restrictions in Control.Arrow.ArrowTree. For example, the signature of deep is deep :: (Tree t, ArrowTree a) = a (t b) (t b) - a (t b) (t b) instead of the more general deep :: (Tree t, ArrowTree

Re: [Haskell-cafe] Parsec (Zero or One of)

2008-03-25 Thread Albert Y. C. Lai
Paul Keir wrote: I’m having some difficulty using the Parsec library, perhaps you could help. I’ve reduced my problem as shown below. I would like the ‘only_prod’ parser to require the reserved string “only”, _optionally_ followed by an identifier. As part of ‘mytest’, this should then be

Re: [Haskell-cafe] getChar

2008-03-25 Thread Albert Y. C. Lai
Cetin Sert wrote: is there a version of getChar that doesn't buffer keyboard input until enter is pressed? Look into hSetBuffering (module System.IO or IO). As a quick start: hSetBuffering stdin NoBuffering ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Help understanding sharing

2008-04-14 Thread Albert Y. C. Lai
Patrick Surry wrote: I've seen other discussions that suggest that lists are always shared while in scope (so the fibs trick works). But is that just a feature of the standard compilers, or is it somewhere mandated in the Hakell spec (I don't see anything obvious in the Haskell Report tho

Re: [Haskell-cafe] Processing XML with HXT

2008-04-22 Thread Albert Y. C. Lai
rodrigo.bonifacio wrote: I´m just starting with HXT. My question is, how can I expose a use case from the main function below (the XmlPickler for UseCase has been already defined): main :: IO () main = do runX ( xunpickleDocument xpUseCase [ (a_validate,v_0) ], uc.xml ) return ()

Re: [Haskell-cafe] question about GHC and Unicode

2008-04-29 Thread Albert Y. C. Lai
John Goerzen wrote: That's a wonderful interface, but unfortunately it appears to assume that your Unicode I/O is always UTF-8, and never UTF-16. I happen to deal with more UTF-16 data than UTF-8 over here at the moment. http://hackage.haskell.org/cgi-bin/hackage-scripts/package/encoding

Re: [Haskell-cafe] Stack vs Heap allocation

2008-05-08 Thread Albert Y. C. Lai
Edsko de Vries wrote: sum :: Tree - Int sum t = sum' [t] 0 where sum' [] acc = acc sum' (Leaf i : ts) acc = sum' ts $! (i + acc) sum' (Node l r : ts) acc = sum' (l : r : ts) acc Because of $!, you should compare the Leaf case to foldl', not foldl. The Node case can be said to

Re: [Haskell-cafe] Order of Evaluation

2008-05-09 Thread Albert Y. C. Lai
Lennart Augustsson wrote: Even so, it's instructive to study how the normal order reduction of this expression would proceed under the assumption that all 4 elements will be used. I think it's useful to try normal order until weak head normal form. Not all steps are shown. Definitions of

Re: [Haskell-cafe] GHC predictability

2008-05-13 Thread Albert Y. C. Lai
Advanced technology ought to look like unpredictable magic. My experience with lazy evaluation is such that every time a program is slower or bulkier than I presumed, it is not arbitrariness, it is something new to learn. My experience with GHC is such that every surprise it gives me is a

Re: [Haskell-cafe] Re: GHC predictability

2008-05-13 Thread Albert Y. C. Lai
Andrew Coppin wrote: 2. Does anybody know how to actually read GHC's Core output anyway? To me, it looks almost exactly like very, very complicated Haskell source with a suspicious concentration of case expressions - but I understand that in the Core language, many constructs actually mean

Re: [Haskell-cafe] Two-iteration optimisation (was: GHC Predictability)

2008-05-14 Thread Albert Y. C. Lai
Paul Johnson wrote: The solution is for the programmer to rewrite mean to accumulate a pair containing the running total and count together, then do the division. This makes me wonder: could there be a compiler optimisation rule for this, collapsing two iterations over a list into one. Do

Re: [Haskell-cafe] Re: Endianess

2008-05-14 Thread Albert Y. C. Lai
Claus Reinke wrote: Germans have no problems with sentences which though started at the beginning when observed closely and in the light of day (none of which adds anything to the content of the sentence in which the very parenthetical remark you -dear reader- are reading at this very moment

Re: [Haskell-cafe] newbie: maintaining relationships

2008-05-24 Thread Albert Y. C. Lai
Neil Mitchell wrote: Sounds like a bidirectional Map to me - fortunately hackage already has one of these: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bimap Yes, bimap is even better. Save lots of work. ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] newbie: maintaining relationships

2008-05-24 Thread Albert Y. C. Lai
geoffrey wrote: Give the following code below, my question is - how do i setup a dependency of User on Common? Perhaps a first attempt should not have Common store a reference to User, nor User store a reference to Common. Instead, have two Data.Map.Map's: one looks up from Common to User,

Re: [Haskell-cafe] Laziness leaks

2008-06-03 Thread Albert Y. C. Lai
Ronald Guida wrote: I was looking at the real time queues in [1] and I wanted to see what would happen if I tried to write one in Haskell. The easy part was translating the real time queue from [1], p43 into Haskell. The hard part is testing to see if the rotations really happen what they

Re: [Haskell-cafe] More on performance

2008-06-04 Thread Albert Y. C. Lai
Jon Harrop wrote: IRL the specification often dictates the complexity. If your code fails to satisfy the spec then it is wrong. Are you saying that Haskell code can never satisfy any such specification? In addition to RL, it it should and it can in theory too:

Re: [Haskell-cafe] Re: Laziness leaks

2008-06-04 Thread Albert Y. C. Lai
apfelmus wrote: I haven't heard the terms laziness leak and strictness leak before, imho they sound a bit spooky because it's not clear to me what the situation without leak would be. (Time vs Space? Is an O(n) algorithm a strictness leak compared to an O(log n) algorithm?) Leak refers to a

Re: [Haskell-cafe] message passing style like in Haskell?

2008-06-19 Thread Albert Y. C. Lai
Adam Vogt wrote: While we are kind of on this topic, what makes the characters ħ þ prefix operator by default, while º and most other odd ones infix? alphanumeric vs non-alphanumeric ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] data Color3 a = Color3 !a !a !a

2008-07-08 Thread Albert Y. C. Lai
Daryoush Mehrtash wrote: Can some one explain what the !a does in this: data Color3 a = Color3 !a !a !a Shameless plug: http://www.vex.net/~trebla/haskell/strict-field.xhtml ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Unnecessarily strict implementations

2010-09-02 Thread Albert Y. C. Lai
On 10-09-02 12:10 PM, Stephen Sinclair wrote: Sorry to go a bit off topic, but I find it funny that I never really noticed you could perform less-than or greater-than comparisons on Bool values. What's the semantic reasoning behind allowing relative comparisons on booleans? In what context

Re: [Haskell-cafe] ANNOUNCE: Haddock version 2.8.0

2010-09-03 Thread Albert Y. C. Lai
On 10-09-02 09:57 PM, John Millikin wrote: Is there any particular reason you're using XHTML instead of HTML? You're using a transitional doctype, invalid IDs, and the .html file extension -- in short, HTML with an incorrect doctype. The markup doesn't even validate. [...] XHTML is supported

Re: [Haskell-cafe] ANNOUNCE: Haddock version 2.8.0

2010-09-04 Thread Albert Y. C. Lai
On 10-09-04 01:31 AM, John Millikin wrote: It's not correct. Here's the exact same XHTML document (verify by viewing the source), served with different mimetypes: http://ianen.org/temp/inline-svg.html http://ianen.org/temp/inline-svg.xhtml This relies on xhtml+svg. While it is in the xhtml

Re: [Haskell-cafe] ANNOUNCE: Haddock version 2.8.0

2010-09-04 Thread Albert Y. C. Lai
On 10-09-04 05:46 PM, Jeremy Shaw wrote: Mark suggested that it was easier to achieve multi-browser compatibility using xhtml instead of html, but I am quite certain he is mistaken. There are really three different rendering modes found in browsers: 1. standards mode 2. quirks mode 3.

Re: [Haskell-cafe] Unnecessarily strict implementations

2010-09-04 Thread Albert Y. C. Lai
On 10-09-03 06:11 AM, Henning Thielemann wrote: Yes, something this way. () suggests a notion of magnitude for me, which some orderings do not have. Like for example -1000 has a larger magnitude than -0.0001, therefore you also reject the common ordering -1000 -0.0001?

Re: [Haskell-cafe] malicious JS on haskell site

2010-09-09 Thread Albert Y. C. Lai
On 10-09-09 05:30 PM, Keith Sheppard wrote: Maybe malicious isn't the right word but there is a JS based web counter on http://www.haskell.org/complex/why_does_haskell_matter.html which likes to show pop up adverts. They must have switched over from counting visitors to showing adverts at some

Re: [Haskell-cafe] capture of idioms and patterns

2010-09-24 Thread Albert Y. C. Lai
On 10-09-23 04:57 PM, Andrew Coppin wrote: If you think that sounds silly, ask some random person (not a computer programmer, just some random human) how find the sum of a list of numbers. My reply: to sum 10 numbers, sum 9 numbers, then account for the 10th. More at:

Re: [Haskell-cafe] who's in charge?

2010-10-27 Thread Albert Y. C. Lai
On 10-10-27 06:31 AM, Günther Schmidt wrote: this may be an odd question to some, but I think it's actually quite an un-extraordinary one. Who's in charge? Of Haskell I mean. If there was some alien from Planet Java to land on Planet Haskell and demand to be taken to our leader, whom would we

Re: [Haskell-cafe] Haskell is a scripting language inspired by Python.

2010-11-04 Thread Albert Y. C. Lai
On 10-11-03 10:00 PM, Jonathan Geddes wrote: It's called The *Ultimate* Computer Language Guide, and it's on the internets, so it must be correct, right? The correct conclusion: it's on the internets, so it must be LOL. I also invite you to play with my:

Re: [Haskell-cafe] Cabal and using a throw-away package database during distro package building

2010-11-05 Thread Albert Y. C. Lai
On 10-11-05 06:43 AM, Magnus Therning wrote: runhaskell Setup register --gen-script runhaskell Setup unregister --gen-script [...] Except that the generated register/unregister scripts now also point to my-temp-db, and there seems to be no way to prevent this. I solved it for now

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Albert Y. C. Lai
Typed-directed name resolution brings Haskell closer to a write-only language; that is, an ambiguous phrase made total sense to the author when the author wrote it, but an independent reader will need extraordinary effort to disambiguate. {-# LANGUAGE TypeDirectedNameResolution #-} import

[Haskell-cafe] Rename When Import (was: Type Directed Name Resolution)

2010-11-10 Thread Albert Y. C. Lai
A better solution to import-induced name clashes is Rename When Import. You can already rename the module when importing. Let's rename the imported names too. Assume I want to import this module: module SinisterlyNamedModule where data Parsec = State { stdin :: () } | Cont {

Re: [Haskell-cafe] Rename When Import

2010-11-10 Thread Albert Y. C. Lai
On 10-11-10 02:51 PM, Albert Y. C. Lai wrote: import SinisterlyNamedModule( par...@goodtype(st...@caseone(st...@gfa), c...@casetwo(ru...@gfb, froml...@gfc) ), Sorry, that part was mistaken, and not in line with standard Haskell. Here is the correction

Re: [Haskell-cafe] Musings on type systems

2010-11-19 Thread Albert Y. C. Lai
On 10-11-19 04:39 PM, Matthew Steele wrote: TAPL is also a great book for getting up to speed on type theory: http://www.cis.upenn.edu/~bcpierce/tapl/ I am no type theorist, and I nonetheless found it very approachable. TAPL is surprisingly easy-going. It is long (many pages and many

Re: [Haskell-cafe] Downloading web page in Haskell

2010-11-20 Thread Albert Y. C. Lai
On 10-11-20 02:54 PM, José Romildo Malaquias wrote: In order to download a given web page, I wrote the attached program. The problem is that the page is not being full downloaded. It is being somehow intettupted. The specific website and url

Re: [Haskell-cafe] Downloading web page in Haskell

2010-11-20 Thread Albert Y. C. Lai
Most likely you also have the zlib package (cabal-install needs it), so let's use it. Attached therefore.hs import qualified Data.ByteString.Lazy as LB import Codec.Compression.GZip(decompress) import Network.URI(parseURI) import Network.HTTP url =

Re: [Haskell-cafe] How to cabal fetch mtl==2.0.0.0?

2010-11-25 Thread Albert Y. C. Lai
On 10-11-24 08:52 PM, Iain Alexander wrote: F:\Util\Haskellcabal fetch mtl==2.0.0.0 Resolving dependencies... cabal: internal error: could not construct a valid install plan. cabal fetch mtl-2.0.0.0 ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Re: Can't install Leksah

2010-11-27 Thread Albert Y. C. Lai
On 10-11-27 09:20 AM, jutaro wrote: ghc is a package, which exposes Ghc-Api as a library. It gets usually installed, when you install Ghc or Haskell platform. As I remeber , it is usually in a hidden state, but ghc-pkg list should show it. Except that Fedora's GHC really doesn't come with the

Re: [Haskell-cafe] Re: Unable to install packages

2010-11-29 Thread Albert Y. C. Lai
On 10-11-28 09:55 AM, Ketil Malde wrote: Joachim Breitnerm...@joachim-breitner.de writes: I would not recommend using --global on Debian/Ubuntu-systems, as it might interfere with packages installed by Debian. But 'cabal install --global' installs in /usr/local/, does it not? And official

Re: [Haskell-cafe] Re: Unable to install packages

2010-11-29 Thread Albert Y. C. Lai
On 10-11-29 03:15 PM, Albert Y. C. Lai wrote: cabal install --global binary apt-get install libghc6-binary-dev They are the same version (at the time of writing, and assume Ubuntu 10.10) and they will fight for the unique throne of binary-0.5.0.2 in the metadata. Oh bother, Debian/Ubuntu's

Re: [Haskell-cafe] Unable to install packages

2010-12-01 Thread Albert Y. C. Lai
On 10-11-30 05:19 AM, Ketil Malde wrote: It seems to me that while there are *three* ways to install stuff: apt-get install, cabal install --global, and cabal install --user, there are just *two* ways things get installed, globally and user(ly?). The obvious solution would be to have three

[Haskell-cafe] the beginning of the end (was: Hackage down?)

2010-12-04 Thread Albert Y. C. Lai
On 10-12-04 01:03 PM, Antoine Latter wrote: Here's a Reddit post: http://www.reddit.com/r/haskell/comments/efw38/reminder_hackagehaskellorg_outage_tomorrow_due_to/ This is the second consecutive time a planned downtime is not announced on either mailing lists. This seems to me planned

Re: [Haskell-cafe] the beginning of the end

2010-12-05 Thread Albert Y. C. Lai
On 10-12-05 12:34 PM, Daniel Peebles wrote: Oh yeah, the 2.0 stuff that snobby techies love to hate :) hrrmpf back in my day we programmed in binary using a magnetized needle on the exposed tape! I don't need any of this newfangled bull. I kid! But I am curious to see why people are so

Re: [Haskell-cafe] dot-ghci files

2010-12-09 Thread Albert Y. C. Lai
Perhaps ghc should also ignore all group-writable *.hs, *.lhs, *.c, *.o, *.hi files. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

  1   2   3   4   >