Re: [Haskell-cafe] forall vs =

2009-05-13 Thread wren ng thornton
Daryoush Mehrtash wrote: What is the difference between forall as in: runST :: (forall s. ST s a) - a and the = as in evalStateT :: Monad m = StateT s m a - s - m a The forall is Rank-2 polymorphism (the argument must be polymorphic in s). The = is for typeclass constraints (restricting

Re: [Haskell-cafe] Structural sharing in haskell data structures?

2009-05-13 Thread wren ng thornton
Jan-Willem Maessen wrote: I wanted to clear up one misconception here... wren ng thornton wrote: In heavily GCed languages like Haskell allocation and collection is cheap, so we don't mind too much; but in Java and the like, both allocation and collection are expensive so the idea of cheap

Re: [Haskell-cafe] Re: List of exports of a module - are there alternatives?

2009-05-13 Thread wren ng thornton
Maurício wrote: I would like a keyword we could add to a single declaration, like: hidden a :: Int - Int a = (...) The 200 names is not the best example. It's more a question of proportion: if you export 5 declarations in a module with 20, it's OK, but if you export 19 declarations in a module

Re: [Haskell-cafe] Re: OT: Languages

2009-05-12 Thread wren ng thornton
Tillmann Rendel wrote: wren ng thornton wrote: Indeed. The proliferation of compound words is noteworthy, but it's not generally considered an agglutinative language. From what (very little) German I know compounds tend to be restricted to nouns, as opposed to languages like Turkish

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

2009-05-10 Thread wren ng thornton
Ketil Malde wrote: wren ng thornton w...@freegeek.org writes: FWIW, the JVM also fails to release memory resources back to the OS. Given all the problems I've seen that one cause for long-running processes, I'm definitely in support of correcting any behavior like this in the GHC RTS. I'm

[Haskell-cafe] Re: OT: Languages

2009-05-10 Thread wren ng thornton
Kalman Noel wrote: wren ng thornton schrieb: Chris Forno (jekor) wrote: That being said, Esperanto, and even Japanese sentence structure perhaps is not as different as an agglutinative language like German. I'll need to study it more to find out. Actually, Japanese is agglutinative too

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

2009-05-07 Thread wren ng thornton
John Lask wrote: Well this is interesting. So what you are saying is that if your haskell application requires a peek memory utilisation of (for example) 1GB, after the memory intesive computation has completed and the GC has run (assuming all references have been dropped) the GHC RTS will

Re: [Haskell-cafe] GC

2009-05-07 Thread wren ng thornton
Daniel Fischer wrote: Am Donnerstag 07 Mai 2009 22:01:11 schrieb Andrew Coppin: Simon Marlow wrote: http://hackage.haskell.org/trac/ghc/ticket/698 I presume that the reason for this is to avoid handing memory back only to immediately need it again? (I.e., we don't want to be constantly

Re: [Haskell-cafe] How difficult would creating a collaborative multi-user online virtual world application be in Haskell?

2009-05-07 Thread wren ng thornton
Benjamin L.Russell wrote: Unfortunately, Smalltalk is an object-oriented language. If possible, I would like to see something similar in a functional programming language such as Haskell. Does anybody know whether duplicating this project in Haskell would be feasible? In terms of technical

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

2009-05-06 Thread wren ng thornton
FFT wrote: Anton van Straaten wrote: The app is written for a client under NDA, so a blog about it would have to be annoyingly vague. No doubt the potential for encountering space leaks goes up as one writes less pure code, persist more things in memory, and depend on more libraries.

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

2009-05-05 Thread wren ng thornton
Chris Forno (jekor) wrote: The idea is that I spent years studying different languages, generally with a textbook. The textbooks tend to focus on teaching rules and grammar, with a little bit of vocabulary and dialog each chapter. I think the focus should be reversed. This varies wildly by

Re: [Haskell-cafe] name for monad-like structure?

2009-04-28 Thread wren ng thornton
Michael Vanier wrote: Luke Palmer wrote: Michael Vanier wrote: Are you sure it supports () :: m a - m b - m b and not mplus :: m a - m a - m a ? Yeah, you're right. It's basically a monad where the type a is fixed to be (), so you just have ()

Re: [Haskell-cafe] Functor and Haskell

2009-04-24 Thread wren ng thornton
Daryoush Mehrtash wrote: Thanks this was helpful. In many of Conal Elliot's writings I see that he shows that his semantic function is a natural transformation. Is that just basically showing the polymorphic nature of his semantic functions, or are there other benifits you get by showing a

Re: [Haskell-cafe] compilation to C, not via-C

2009-04-24 Thread wren ng thornton
Sam Martin wrote: In short, I'd like to use Haskell as a code-generator. I can't see that this would be unachievable, particularly given it's generating C already. Have I missed something? For the case of GHC at least, you may be. The C that GHC compiles Haskell into isn't C in the normal

Re: [Haskell-cafe] Dynamically altering sort order

2009-04-24 Thread wren ng thornton
Denis Bueno wrote: Hi all, Suppose I have the following interface to a sorting function: sort :: (Ord a) = [a] - IO [a] -- sort large, on-disk array of records but I don't have a sortBy where you can simply pass a compare function. Why don't you have sortBy? Wrapped around this is a

[Haskell-cafe] Where to Cabal Install (was: Re: ANNOUNCE: Utrecht Haskell Compiler (UHC) --first release)

2009-04-22 Thread wren ng thornton
Claus Reinke wrote: Installing executable(s) in /home/david/.cabal/bin why the hell would cabal install binaries in a subdirectory of a hidden directory. Why not /home/david/bin or /home/david/local/bin ? Yes, this is clearly suboptimal but getting agreement on where to put it has not proved

Re: [Haskell-cafe] Re: Is 78 characters still a good option? Was: breaking too long lines

2009-04-22 Thread wren ng thornton
Maurí­cio wrote: We have one: urchin.earth.li/~ian/style/haskell.html Yes, it's good. We should publicise it more. Just a tought: I would like to see a guide talking about the code itself, not about the presentation. Maybe this is ignored because it's difficult. It's easy to get bad code

Re: Is 78 characters still a good option? Was: [Haskell-cafe] breaking too long lines

2009-04-21 Thread wren ng thornton
Dusan Kolar wrote: Dear all, reading that according the several style guides, lines shouldn't be too long (longer than 78 characters). http://www.cs.caltech.edu/courses/cs11/material/haskell/misc/haskell_style_guide.html http://www.haskell.org/haskellwiki/Programming_guidelines I

Re: [Haskell-cafe] Functor and Haskell

2009-04-21 Thread wren ng thornton
Daryoush Mehrtash wrote: I am not sure I follow how the endofunctor gave me the 2nd functor. As I read the transformation there are two catagories C and D and two functors F and G between the same two catagories. My problem is that I only have one functor between the Hask and List catagories.

Re: [Haskell-cafe] ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-19 Thread wren ng thornton
Bulat Ziganshin wrote: Hello R.A., Sunday, April 19, 2009, 11:46:53 PM, you wrote: Does anybody know if there are any plans to incorporate some of these extensions into GHC - specifically the existential typing ? it is already here, but you should use forall keyword instead odf exists

Re: [Haskell-cafe] ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-19 Thread wren ng thornton
Dan Doel wrote: On Sunday 19 April 2009 4:56:29 pm wren ng thornton wrote: Bulat Ziganshin wrote: Hello R.A., Sunday, April 19, 2009, 11:46:53 PM, you wrote: Does anybody know if there are any plans to incorporate some of these extensions into GHC - specifically the existential

Re: [Haskell-cafe] Computing a sorted list of products lazily

2009-04-17 Thread wren ng thornton
Jason Dagit wrote: Hello, A colleague of mine recently asked if I knew of a lazy way to solve the following problem: Given two sets of sorted floating point numbers, can we lazily generate a sorted list of the products from their Cartesian product? The algorithm should return the same result

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

2009-04-15 Thread wren ng thornton
Edward Kmett wrote: You might want to start with the Sieve of Atkin: http://en.wikipedia.org/wiki/Sieve_of_Atkin Also worth reading _Lazy wheel sieves and spirals of primes_: http://www.cs.york.ac.uk/ftpdir/pub/colin/jfp97lw.ps.gz -- Live well, ~wren

Re: [Haskell-cafe] tail recursion

2009-04-07 Thread wren ng thornton
Daryoush Mehrtash wrote: Is the call to go in the following code considered as tail recursion? data DList a = DLNode (DList a) a (DList a) mkDList :: [a] - DList a mkDList [] = error must have at least one element mkDList xs = let (first,last) = go last xs first in first

Re: [Haskell-cafe] high probability of installation problems and quality of the glorious implementation

2009-04-05 Thread wren ng thornton
FFT wrote: John Dorsey wrote: Once it's installed and working, GHC's a very decent compiler. My general null hypothesis is, as Alec Baldwin put it, that a loser is a loser, or a buggy project is buggy. If GHC is robust overall (which I'm yet to find out), why is the installation so broken?

[Haskell-cafe] ANN: logfloat 0.12.0.1

2009-04-03 Thread wren ng thornton
-- logfloat 0.12.0.1 This package provides a type for storing numbers in the log-domain, primarily useful for preventing underflow when multiplying many probabilities as in HMMs and other probabilistic

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

2009-04-01 Thread wren ng thornton
David Menendez wrote: On Tue, Mar 31, 2009 at 11:44 PM, wren ng thornton w...@freegeek.org wrote: Another tricky thing for this particular example is answering the question of what you want to call the focus. Usually zippered datastructures are functors, so given F X we can pick one X

Re: [Haskell-cafe] Zippers from any traversable [Was: Looking for practical examples of Zippers]

2009-04-01 Thread wren ng thornton
o...@okmij.org wrote: wren ng thornton wrote: how, for instance, turn a nested Map like Map Int (Map Int (Map String Double) into a zipped version. You can't. Or rather, you can't unless you have access to the implementation of the datastructure itself; and Data.Map doesn't provide

Re: [Haskell-cafe] uvector package appendU: memory leak?

2009-04-01 Thread wren ng thornton
Manlio Perillo wrote: wren ng thornton ha scritto: Manlio Perillo wrote: Since ratings for each customers are parsed at the same time, using a plain list would consume a lot of memory, since stream fusion can only be executed at the end of the parsing. On the other hand, when I

Re: [Haskell-cafe] uvector package appendU: memory leak?

2009-03-31 Thread wren ng thornton
Manlio Perillo wrote: By the way, about insertWith/alter; from IntMap documentation: insertWithKey: O(min(n,W) alter: O(log n) So, alter is more efficient than insertWithKey? And what is that `W` ? As Claus says it's the maximum (value of Int; number of keys). It's in an easily overlooked

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

2009-03-31 Thread wren ng thornton
Gü?nther Schmidt wrote: Thanks Don, I followed some examples but have not yet seen anything that would show me how, for instance, turn a nested Map like Map Int (Map Int (Map String Double) into a zipped version. You can't. Or rather, you can't unless you have access to the

Re: [Haskell-cafe] about the Godel Numbering for untyped lambda calculus

2009-03-31 Thread wren ng thornton
John Tromp wrote: I am reading the book The lambda calculus: Its syntax and Semantics in the chapter about Godel Numbering but I am confused in some points. We know for Church Numerals, we have Cn = \fx.f^n(x) for some n=0, i.e. C0= \fx.x and C 1 = \fx.fx. From the above definition, I could

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

2009-03-26 Thread wren ng thornton
Colin Adams wrote: 2009/3/25 wren ng thornton w...@freegeek.org: Most of the documentation is in research papers, and a normal programmer don't want to read these papers. Yes, and no. There is quite a bit of documentation in research papers, and mainstream programmers don't read

Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-26 Thread wren ng thornton
Jules Bean wrote: wren ng thornton wrote: I have long been disappointed by a number of `error`s which shouldn't be. For example, the fact that `head` and `div` are not total strikes me as a (solvable) weakness of type checking, rather than things that should occur as programmer errors

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

2009-03-26 Thread wren ng thornton
John Lato wrote: From: wren ng thornton w...@freegeek.org Dan Weston wrote: So to be clear with the terminology: inductive = good consumer? coinductive = good producer? So fusion should be possible (automatically? or do I need a GHC rule?) with inductive . coinductive

Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-26 Thread wren ng thornton
Alexander Dunlap wrote: wren ng thornton wrote: Jules Bean wrote: head uses error in precisely the correct, intended fashion. head has a precondition (only call on non-empty lists) And that is *exactly* my complaint: the precondition is not verified by the compiler. Therefore it does

Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-26 Thread wren ng thornton
Luke Palmer wrote: Alexander Dunlap wrote: Ultimately, it's not detectable statically, is it? Consider import Control.Applicative main = do f - lines $ readFile foobar print (head (head f)) You can't know whether or not head will crash until runtime. Static checkers are usually

Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-26 Thread wren ng thornton
Jonathan Cast wrote: Xiao-Yong Jin wrote: Xiao-Yong Jin wrote: So I have another question. Is the following function safe and legitimate? safeDiv :: (Exception e, Integral a) = a - a - Either e a safeDiv x y = unsafePerformIO . try . evaluate $ div x y safeDiv'

Re: [Haskell-cafe] Re: Really need some help understanding a solution

2009-03-26 Thread wren ng thornton
Gü?nther Schmidt wrote: The depth this language has is just amazing and the stuff that is tackled in this language is just aaahhh. Can't quite put it in words, maybe something along the lines the ultimate thing, key to the universe I don't know. Humbling and frustrating especially when

Re: [Haskell-cafe] Really need some help understanding a solution

2009-03-26 Thread wren ng thornton
Thomas Hartman wrote: Luke, does your explanation to Guenther have anything to do with coinduction? -- the property that a producer gives a little bit of output at each step of recursion, which a consumer can than crunch in a lazy way? It has more to do with tying the knot (using laziness to

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

2009-03-25 Thread wren ng thornton
Thomas Hartman wrote: sorry, wrong function. should be partitions [] xs = [] partitions (n:parts) xs = let (beg,end) = splitAt n xs in beg : ( case end of [] - [] xs - partitions parts xs) It's not tail recursive, FWIW. The recursive expression has (:) as

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

2009-03-25 Thread wren ng thornton
Manlio Perillo wrote: The main problem, here, is that: - recursion and pattern matching are explained in every tutorial about functional programming and Haskell. This is the reason why I find them more natural. - high level, Haskell specific, abstractions, are *not* explained in normal

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

2009-03-25 Thread wren ng thornton
Dan Weston wrote: So to be clear with the terminology: inductive = good consumer? coinductive = good producer? So fusion should be possible (automatically? or do I need a GHC rule?) with inductive . coinductive Or have I bungled it? Not quite. Induction means starting from base cases

[Haskell-cafe] [OT] Japanese (was: Re: about Haskell code written to be too smart)

2009-03-25 Thread wren ng thornton
Zachary Turner wrote: On Tue, Mar 24, 2009 at 10:32 PM, wren ng thornton w...@freegeek.orgwrote: Both of these conclusions seem quite natural to me, even from before learning Haskell. It seems, therefore, that naturality is not the proper metric to discuss. It's oft overlooked, but the fact

Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-25 Thread wren ng thornton
Henning Thielemann wrote: Jonathan Cast wrote: Xiao-Yong Jin wrote: Could you elaborate more about why this kind of breakage wouldn't happen if 'try' is used in an IO monad as intended? It would. But it would happen in IO, which is allowed to be non-deterministic. Pure Haskell is not

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

2009-03-24 Thread wren ng thornton
Manlio Perillo wrote: But this may be really a question of personal taste or experience. What is more natural? 1) pattern matching 2) recursion or 1) function composition 2) high level functions Which is more natural: * C-style for-loops (aka assembly while-loops), or * any modern language's

Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-23 Thread wren ng thornton
Xiao-Yong Jin wrote: Hi, I just feel it is not comfortable to deal with exceptions only within IO monad, so I defined tryArith :: a - Either ArithException a tryArith = unsafePerformIO . try . evaluate [...] However, I guess unsafePerformIO definitely has a reason for its name. As I read

Re: [Haskell-cafe] ACM Task for C++ and Java programmers in Haskell. How to make code faster?

2009-03-22 Thread wren ng thornton
Vasyl Pasternak wrote: The entire code I placed on http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2764 Could someone help me to make this code faster? I'd like to see solution that will be elegant and fast, without heavy optimizations, that will make code unreadable. Also, if it possible,

Re: [Haskell-cafe] Re: A guess on stack-overflows - thunks build-up and tail recursion

2009-03-20 Thread wren ng thornton
GüŸnther Schmidt wrote: the point I wanted to stress though is that the stack overflow does actually not occur doing the recursive algorithm, just a build-up of thunks. The algorithm itself will eventually complete without the stack overflow. The problem occurs when the result value is

[Haskell-cafe] Re: categories and monoids

2009-03-17 Thread wren ng thornton
Wolfgang Jeltsch wrote: Am Dienstag, 17. März 2009 10:54 schrieben Sie: I'm reading the Barr/Wells slides at the moment, and they say the following: Thus a category can be regarded as a generalized monoid, What is a “generalized monoid”? According to the grammatical construction (adjective

Re: [Haskell-cafe] Design Patterns by Gamma or equivalent

2009-03-17 Thread wren ng thornton
Gregg Reynolds wrote: Imperative programmers also used it to describe programming patterns. Implementations of things like Observer/VIsitor etc. are ad-hoc, informal constructions; the equivalent in a functional language is a mathematical structure (feel free to fix my terminology). I don't

Re: [Haskell-cafe] symbolic evaluator for Haskell?

2009-03-17 Thread wren ng thornton
Tim Newsham wrote: Is there a symbolic evaluator for Haskell that will perform all applications except on specified functions? Ie. I would love something that would take foldr (+) (6 `div` 5) [1,2,3*4] and (+) (*) and return 1 + (2 + (3*4 + 1)) by performing all the applications

Re: [Haskell-cafe] Design Patterns by Gamma or equivalent

2009-03-16 Thread wren ng thornton
a...@spamcop.net wrote: G'day all. Quoting wren ng thornton w...@freegeek.org: Most of the (particular) problems OO design patterns solve are non-issues in Haskell because the language is more expressive. ...and vice versa. Some of the design patterns that we use in Haskell, for example

Re: [Haskell-cafe] Most elegant funciton for removing adjacent duplicates from a list using foldl and foldr

2009-03-15 Thread wren ng thornton
R J wrote: I need to write an implementation using foldl, and a separate implementation using foldr, of a function, remdups xs, that removes adjacent duplicate items from the list xs. For example, remdups [1,2,2,3,3,3,1,1]= [1,2,3,1]. My approach is first to write a direct recursion, as

Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-15 Thread wren ng thornton
Yusaku Hashimoto wrote: Hello, I was studying about what unsafeInterleaveIO is.I understood unsafeInterleaveIO takes an IO action, and delays it. But I couldn't find any reason why unsafeInterleaveIO is unsafe. I have already read an example in

Re: [Haskell-cafe] Design Patterns by Gamma or equivalent

2009-03-14 Thread wren ng thornton
Mark Spezzano wrote: Because Haskell is not OO, it is functional, I was wondering if there is some kind of analogous “design pattern”/”template” type concept that describe commonly used functions that can be “factored out” in a general sense to provide the same kind of usefulness that Design

Re: [Haskell-cafe] A systematic method for deriving a defintion of foldl using foldr?

2009-03-14 Thread wren ng thornton
R J wrote: 2. I believe that the reverse implementation--namely, implementing foldr in terms of foldl--is impossible. What's the proof of that? As others have said, foldr in terms of foldl is impossible when infinite lists are taken into account. For finite lists it's easy though: (\f z

Re: [Haskell-cafe] Cabal and package changelog

2009-03-08 Thread wren ng thornton
Manlio Perillo wrote: Duncan Coutts ha scritto: On Sun, 2009-03-08 at 10:00 -0400, Gwern Branwen wrote: http://hackage.haskell.org/trac/hackage/ticket/244 http://hackage.haskell.org/trac/hackage/ticket/299 Thanks Gwern. Yes, we're looking for a volunteer to work on implementing this.

Re: [Haskell-cafe] STG's? [was: I want to write a compiler]

2009-03-08 Thread wren ng thornton
Rick R wrote: Where can I find more information on STGs? Google search doesn't bring up anything too enlightening. My curiosity was piqued by http://www.cs.chalmers.se/~gedell/ssc/index.html. Of course it doesn't indicate how these should be built or the format. Perhaps

Re: [Haskell-cafe] I want to write a compiler

2009-03-07 Thread wren ng thornton
Loup Vaillant wrote: - support algebraic data types and case expressions (unless I can get away with encoding them as functions), Which you always can, data Foo = A a1...an | B b1...bn |... == type Foo :: forall r. (a1-...-an - r) - (b1-...-bn - r)

Re: [Haskell-cafe] Re: Interesting problem from Bird (4.2.13)

2009-03-06 Thread wren ng thornton
Gleb Alexeyev wrote: Here's my attempt though it's not really different from using built-in lists: viewCL CatNil = Nothing viewCL (Wrap a) = Just (a, CatNil) viewCL (Cat a b) = case viewCL a of Nothing - viewCL b Just (x, xs) - Just (x, Cat xs b) My

Re: [Haskell-cafe] DSLs with {in,}equalities

2009-03-02 Thread wren ng thornton
Andrew Hunter wrote: Several times now I've had to define an EDSL for working with (vaguely) numeric expressions. For stuff like 2*X+Y, this is easy, looking pretty much like: data Expr = Const Integer | Plus Expr Expr | Times Expr Expr instance Num Expr where fromInterger = Const (+) = Plus

Re: [Haskell-cafe] Stacking State on State.....

2009-03-01 Thread wren ng thornton
Phil wrote: | After some googling it looked like the answer may be Monad Transformers. | Specifically we could add a StateT transform for our Box Muller state to our | VanDerCorput State Monad. | Google didn¹t yield a direct answer here ­ so I¹m not even sure if my | thinking is correct,

Re: [Haskell-cafe] type universes (was Re: MPTC inheritance

2009-03-01 Thread wren ng thornton
Larry Evans wrote: Except that a kind sounds like a universe at level 2 or 3. IOW, I guess haskell types are at level 1, and kines at level 2? Then I guess values would be at level 0? Exactly. Is there some version of haskell that has more levels in its type universe. If not, it there some

Re: [Haskell-cafe] Supplying a default implementation for a typeclass based on another class

2009-03-01 Thread wren ng thornton
Svein Ove Aas wrote: Martin Huschenbett wrote: instance (Show a,Read a) = Binary a where put = put . show get = fmap read get But then you will need the following language extensions: FlexibleInstances, OverlappingInstances, UndecidableInstances Well, isn't there a good chance it'll end

Re: [Haskell-cafe] Stacking State on State.....

2009-03-01 Thread wren ng thornton
Phil wrote: Again I understand that foldl' is the strict version of foldl, and as we are summing elements we can use either foldl or foldr. I'm assuming this is another thunk optimisation. Does foldl not actually calculate the sum, but moreover it creates an expression of the form

Re: [Haskell-cafe] Translating an imperative algorithm - negascout

2009-02-27 Thread wren ng thornton
Holger Siegel wrote: loop alpha b (c:cs) = let alpha' = max(alpha, - negascout c d (-b) (-alpha)) in if alpha' = beta then alpha' else if alpha' = b then let alpha'' = - negascout c d (-beta) (-alpha') in if

Re: [Haskell-cafe] Re: Hoogle and Network.Socket

2009-02-23 Thread wren ng thornton
Achim Schneider wrote: Thomas DuBuisson thomas.dubuis...@gmail.com wrote: I still prefer showing all platform results sorted into separate sections with headers, but understand that I am in the minority. You aren't alone. Labelling them prominently with POSIX, UNIX, Linux, *BSD, OSX resp.

Re: [Haskell-cafe] Stacking StateTs

2009-02-23 Thread wren ng thornton
Luis O'Shea wrote: One way to do this is to stack two StateTs on top of m. Another way, what might be easier to reason about, is to crush those two layers together and use a tuple for the state: StateT s1 (StateT s2 m) a == StateT (s1,s2) m a Then the only thing you'll have to worry

Re: [Haskell-cafe] memory-efficient data type for Netflix data - UArray Int Int vs UArray Int Word8

2009-02-23 Thread wren ng thornton
Kenneth Hoste wrote: Well, I'm using UArray, but I'm willing to consider other suitable containers... As long as they are memory efficient. :-) The typical usage of a UArray will be getting all it's contents, and converting it to a list to easily manipulate (filter, ...). So, maybe another

Re: [Haskell-cafe] Data.Binary poor read performance

2009-02-23 Thread wren ng thornton
Neil Mitchell wrote: 2) The storage for String seems to be raw strings, which is nice. Would I get a substantial speedup by moving to bytestrings instead of strings? If I hashed the strings and stored common ones in a hash table is it likely to be a big win? Bytestrings should help. The big

Re: [Haskell-cafe] Re: A typeclass for Data.Map etc?

2009-02-21 Thread wren ng thornton
Achim Schneider wrote: wren ng thornton w...@freegeek.org wrote: (b) allows instances to have a fixed type for keys (like Data.Trie and Data.IntMap have), Can't we do some type magic to automagically select Data.Trie if the key is a (strict) bytestring? Uh, sure. I was thinking more

Re: [Haskell-cafe] A typeclass for Data.Map etc?

2009-02-19 Thread wren ng thornton
Eugene Kirpichov wrote: Looks like such a thing would be useful; as for now, I see at least two applications: Data.Map and Data.Trie (bytestring-trie) - it's a pity that they have rather similar interfaces, but the latter lacks many methods and some are named in a different way. Are there any

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

2009-02-16 Thread wren ng thornton
Isaac Dupree wrote: Natural numbers under min don't form a monoid, only naturals under max do (so you can have a zero element) Though, FWIW, you can use Nat+1 with the extra value standing for Infinity as the identity of min (newtype Min = Maybe Nat). I bring this up mainly because it can

Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread wren ng thornton
Louis Wasserman wrote: I follow. The primary issue, I'm sort of wildly inferring, is that use of STT -- despite being pretty much a State monad on the inside -- allows access to things like mutable references? That's exactly the problem. The essential reason for ST's existence are STRefs

Re: [Haskell-cafe] Re: Can this be done?

2009-02-14 Thread wren ng thornton
Chung-chieh Shan wrote: wren ng thornton wrote: It's ugly, but one option is to just reify your continuations as an ADT, where there are constructors for each function and fields for each variable that needs closing over. Serializing that ADT should be simple (unless some of those

Re: [Haskell-cafe] Re: Overloading functions based on arguments?

2009-02-14 Thread wren ng thornton
John A. De Goes wrote: On Feb 13, 2009, at 2:11 PM, Jonathan Cast wrote: The compiler should fail when you tell it two mutually contradictory things, and only when you tell it two mutually contradictory things. By definition, it's not a contradiction when the symbol is unambiguously

Re: [Haskell-cafe] Re: [Haskell] Google Summer of Code 2009

2009-02-12 Thread wren ng thornton
Matthew Elder wrote: would love to see this. basic features first i suppose. here are some of my ideas: 1. browseable change history with preview pane (preview pane shows diff and patch message) Extending this idea, I'd like to see some 3D visualization of the file hierarchy and the

Re: [Haskell-cafe] Changing version numbering schemes for HackageDB packages?

2009-02-11 Thread wren ng thornton
Corey O'Connor wrote: Part of the reason they seem awkward to me is that I expect the difference between version numbers to indicate something about what has changed between the two versions. This only ends up being a heuristic but a useful one. Date based version numbers don't communicate much

Re: [Haskell-cafe] Can this be done?

2009-02-11 Thread wren ng thornton
Cristiano Paris wrote: Manlio Perillo wrote: Cristiano Paris ha scritto: I'm interested in the possibility of stopping/pickling/unpickling/resuming a computation. Not sure this is a good thing in a web application. I'm thinking of complex workflows and inversion of control. A

Re: [Haskell-cafe] Monad explanation

2009-02-10 Thread wren ng thornton
Richard O'Keefe wrote: Gregg Reynolds wrote: Sure, you can treat a morphism as an object, but only by moving to a higher (or different) level of abstraction. False as a generalisation about mathematics. False about functional programming languages, the very essence of which is treating

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

2009-02-10 Thread wren ng thornton
minh thu wrote: Joachim Breitner: I thought about Zippers, but I understand that they improve _navigating_ in a Tree-like structure, or to refrence _one_ position in a tree. But if I would deconstruct my tree to the list of _all_ locations, with type Loc a = (Tree a, Cxt a) and then run

Re: [Haskell-cafe] evaluation semantics of bind

2009-02-10 Thread wren ng thornton
Alberto G. Corona wrote: forwarded: Yes! if no state is passed, the optimization makes sense and the term is not executed, like any lazy evaluation. For example, I used the debugger (that is, without optimizations) to verify it with the Maybe monad: op x= x+x print $ Just (op 1) = \y- return

Re: [Haskell-cafe] evaluation semantics of bind

2009-02-09 Thread wren ng thornton
Gregg Reynolds wrote: Tillmann Rendel wrote: An example where it would be wrong to ignore e: sum ([1, 2] = const [21]) This expression should evaluate to sum [21, 21] = 42, not sum [21] = 21. Sigh. I hate it when this happens. Just when I thought I had it figured out, it turns out I'm

Re: [Haskell-cafe] Monad explanation

2009-02-06 Thread wren ng thornton
Tim Newsham wrote: The only difference with IO then is that to get IO programs to run, you have to do it inside another IO program. Almost. Add to your mental model a runIO that is invoked when your program runs as: runIO main. Your haskell compiler or interpretter arranges this for

Re: [Haskell-cafe] Re: evaluation semantics of bind

2009-02-05 Thread wren ng thornton
Gregg Reynolds wrote: Right, but that's only because the compiler either somehow knows about side effects or there is some other mechanism - e.g. an implicit World token that gets passed around - that prevents optiimization. As far as the formal semantics of the language are concerned, there's

Re: [Haskell-cafe] Purely funcional LU decomposition

2009-02-05 Thread wren ng thornton
Rafael Gustavo da Cunha Pereira Pinto wrote: What I miss most is a data structure with O(1) (amortized) direct access. Finger trees get close, O(log(min(i,n-i))): http://hackage.haskell.org/packages/archive/containers/latest/doc/html/Data-Sequence.html (And Theta(1) amortized for all

Re: [Haskell-cafe] Switching from Mercurial to Darcs

2009-02-05 Thread wren ng thornton
Roman Cheplyaka wrote: * Peter Verswyvelen bugf...@gmail.com [2009-02-05 16:35:34+0100] On Thu, Feb 5, 2009 at 4:32 PM, Ketil Malde ke...@malde.org wrote: Peter Verswyvelen bugf...@gmail.com writes: 1) hg st darcs cha -s That seems to list all changes in the history. hg st lists local

Re: [Haskell-cafe] Re: evaluation semantics of bind

2009-02-05 Thread wren ng thornton
Gregg Reynolds wrote: On Thu, Feb 5, 2009 at 7:19 PM, wren ng thornton w...@freegeek.org wrote: Gregg Reynolds wrote: as the formal semantics of the language are concerned, there's no essential difference between getChar = \x - getChar and Foo 3 = \x - Foo 7 for some data constructor Foo

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

2009-02-03 Thread wren ng thornton
Thomas Davie wrote: I can imagine the styling language having the meaning function from documents onto geometry, but the document description language is harder. Ideally what I'd like to do with it is to make it describe *only* the logical structure of the information being conveyed –

Re: [Haskell-cafe] Bytestrings vs String? parameters within package names?

2009-02-03 Thread wren ng thornton
Marc Weber wrote: wren ng thornton wrote: I'd just stick with one (with a module for hiding the conversions, as desired). Duplicating the code introduces too much room for maintenance and compatibility issues. That's the big thing. The more people that use ByteStrings the less need

Re: [Haskell-cafe] type metaphysics

2009-02-03 Thread wren ng thornton
Gregg Reynolds wrote: On Mon, Feb 2, 2009 at 2:25 PM, Ketil Malde ke...@malde.org wrote: Gregg Reynolds d...@mobileink.com writes: Just shorthand for something like data Tcon a = Dcon a, applied to Int. Any data constructor expression using an Int will yield a value of type Tcon Int.

Re: [Haskell-cafe] type and data constructors in CT

2009-02-02 Thread wren ng thornton
Gregg Reynolds wrote: On Sat, Jan 31, 2009 at 4:26 PM, wren ng thornton w...@freegeek.org wrote: But a data constructor Dcon a is an /element/ mapping taking elements (values) of one type to elements of another type. So it too can be construed as a functor, if each type itself

Re: [Haskell-cafe] type metaphysics

2009-02-02 Thread wren ng thornton
Gregg Reynolds wrote: Hi, The concept of type seems to be a little like porno: I know it when I see it, but I can't define it (apologies to Justice Stewart). I've picked through lots of documents that discuss types in various ways, but I have yet to find one that actually says what a type

Re: [Haskell-cafe] Bytestrings vs String?

2009-02-02 Thread wren ng thornton
Marc Weber wrote: A lot of people are suggesting using Bytestrings for performance, strictness whatsoever reasons. However how well do they talk to other libraries? I'm not sure how you mean? For passing them around: If someone's trying to combine your library (version using ByteStrings)

Re: [Haskell-cafe] type and data constructors in CT

2009-01-31 Thread wren ng thornton
Gregg Reynolds wrote: Hi, I think I've finally figured out what a monad is, but there's one thing I haven't seen addressed in category theory stuff I've found online. That is the relation between type constructors and data constructors. As I understand it, a type constructor Tcon a is

[Haskell-cafe] ANN: logfloat 0.10, 0.11

2009-01-29 Thread wren ng thornton
-- logfloat 0.10, 0.11 This package provides a type for storing numbers in the log-domain, primarily useful for preventing underflow when multiplying many probabilities as in HMMs and other probabilistic

Re: [Haskell-cafe] How outdated is Hugs?

2009-01-28 Thread wren ng thornton
Bryan O'Sullivan wrote: On Tue, Jan 27, 2009 at 1:18 PM, Duncan Coutts duncan.cou...@worc.ox.ac.ukwrote: Not since then, no. However a lot of things work fine, especially if you use a newer Cabal version. I've been unable to figure out how to build Cabal with Hugs 2006.09.04: $ *runhugs

Re: [Haskell-cafe] How outdated is Hugs?

2009-01-28 Thread wren ng thornton
wren ng thornton wrote: Bryan O'Sullivan wrote: On Tue, Jan 27, 2009 at 1:18 PM, Duncan Coutts duncan.cou...@worc.ox.ac.ukwrote: Not since then, no. However a lot of things work fine, especially if you use a newer Cabal version. I've been unable to figure out how to build Cabal with Hugs

[Haskell-cafe] Bugs in Hugs

2009-01-28 Thread wren ng thornton
In testing some of my packages against Hugs, I've uncovered bugs[1]. Unfortunately the bug tracker at: http://hackage.haskell.org/trac/hugs/newticket?type=defect doesn't seem to allow normal users to submit tickets. Does anyone know how to submit bug reports to Hugs these days? [1]

<    4   5   6   7   8   9   10   11   >