Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-10 Thread wren ng thornton
Wolfgang Jeltsch wrote: Hello, some time ago, it was pointed out that generalized newtype deriving could be used to circumvent module borders. Now, I found out that generalized newtype deriving can even be used to define functions that would be impossible to define otherwise. To me, this is

[Haskell-cafe] If wishes were horses... (was: Re: definition of sum)

2010-03-11 Thread wren ng thornton
David Leimbach wrote: Note that foldl' has a ' to indicate that it's not the same as foldl exactly. I would propose that sum' exist as well as sum, and that sum be lazy. I wish Haskell allowed ! to occur (non-initially) in alphanum_' identifiers as well as in symbolic ones. Then we could be

Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-12 Thread wren ng thornton
Wolfgang Jeltsch wrote: Am Donnerstag, 11. März 2010 00:37:18 schrieb wren ng thornton: Wolfgang Jeltsch wrote: Hello, some time ago, it was pointed out that generalized newtype deriving could be used to circumvent module borders. Now, I found out that generalized newtype deriving can even

Re: [Haskell-cafe] Re: If wishes were horses...

2010-03-12 Thread wren ng thornton
Ketil Malde wrote: What should the type look like? If memory serves, Clean allows bangs in type signatures, something like: foldl' :: (a - b - a) - !a - [b] - a but I thought it just added a seq under the hood, much like bang patterns like foldl' f !z xs = ... do in Haskell, so it's

Re: [Haskell-cafe] Re: If wishes were horses...

2010-03-15 Thread wren ng thornton
Ben Millwood wrote: In general, laziness behaviour can get complicated quickly and so I'm not convinced that the type signature is a good home for that information. Certainly it can. A lot of the same problems arise in the logic programming community under the topic of modes, i.e. whether a

Re: [Haskell-cafe] Parsec to parse tree structures?

2010-03-17 Thread wren ng thornton
david fries wrote: My my concern was how you would perform random access in a functional parser. You're points are interesting too. I guess if we really had wanted to work with parsed objects, retaining the shared references would have been a must. Out of curiosity, was there *really* a need

Re: [Haskell-cafe] Parsec to parse tree structures?

2010-03-18 Thread wren ng thornton
Stephen Tetley wrote: hi wren Where I've used it, random access does seem conceptual more satisfactory than trying to avoid it. I was thinking more about performance issues (avoiding disk seeks) which would also alleviate the problem of needing random access when it's not available. For

Re: [Haskell-cafe] haskell platform questions

2010-03-21 Thread wren ng thornton
Gregory Collins wrote: Warren Harris warrensomeb...@gmail.com writes: I downloaded the new haskell-platform-2010.1.0.0-i386.dmg today... ran the uninstaller, ghc installer and the platform installer. When I run ghci, it seems to work fine, but when I try cabal, I get this crash: $ cabal

Re: [Haskell-cafe] haskell platform questions

2010-03-22 Thread wren ng thornton
Gregory Collins wrote: wren ng thornton w...@freegeek.org writes: I'm still on 10.5.8. I don't have cabal-install installed yet, but I just installed GHC-6.12.1/HP-2010.1.0.0. I can verify that ghci works fine so far. I'll check out cabal-install in the next couple days. If there is an issue

Re: [Haskell-cafe] haskell platform questions

2010-03-24 Thread wren ng thornton
Gregory Collins wrote: wren ng thornton w...@freegeek.org writes: w...@semiramis:~ $ ls /usr/local ls: /usr/local: No such file or directory w...@semiramis:~ $ ls /usr/bin/cabal ls: /usr/bin/cabal: No such file or directory But http://hackage.haskell.org/platform/new/contents.html tells me

Re: [Haskell-cafe] haskell platform questions

2010-03-24 Thread wren ng thornton
Don Stewart wrote: You should file a bug on the Haskell Platform bug tracker. http://haskell.org/haskellwiki/Haskell_Platform#Trouble_shooting And I'm CC'ing the dmg maintainer -- it may also be a GHC issue as well. -- Don warrensomebody: I downloaded the new

Re: [Haskell-cafe] GHC vs GCC

2010-03-27 Thread wren ng thornton
David Menendez wrote: On Sat, Mar 27, 2010 at 12:56 AM, Thomas DuBuisson thomas.dubuis...@gmail.com wrote: Using bang patterns didn't help almost anything here. Using rem instead of mod made the time go from 45s to 40s. Now, using -fvia-C really helped (when I used rem but not using mod). It

Re: [Haskell-cafe] Are there any female Haskellers?

2010-03-27 Thread wren ng thornton
Alberto G. Corona wrote: because math abilities are not a -primary- reason for survival. Tools engineering and mastering is. I don't see the difference. Being able to use a lever, wheel, pulley, fire,... is obviously helpful for survival. But intellectual tools like mathematics, logic, and

Re: [Haskell-cafe] Are there any female Haskellers?

2010-03-27 Thread wren ng thornton
wren ng thornton wrote: Alberto G. Corona wrote: because math abilities are not a -primary- reason for survival. Tools engineering and mastering is. I don't see the difference. (That is, the difference between CS and mathematics. Conversely, I don't see the similarity between physical

Re: [Haskell-cafe] Re: Are there any female Haskellers?

2010-03-28 Thread wren ng thornton
Jon Fairbairn wrote: Another (provocative) observation is that most of the women programmers I've known were good at it and thought they might not be, but most of the men claimed to be good at it but were not. I've observed this too, but it's a bit droll. Let: p = proportion of people who

Re: [Haskell-cafe] Re: Are there any female Haskellers?

2010-03-28 Thread wren ng thornton
Günther Schmidt wrote: One thing that I keep hearing is I'm not trying to be offensive. I think it's easy to get caught up on not being offensive so that we don't make any progress. It's impossible not to offend people -- but it is possible to take the time to listen and correct problematic

Re: [Haskell-cafe] Re: Are there any female Haskellers?

2010-03-28 Thread wren ng thornton
Jason Dagit wrote: On Sun, Mar 28, 2010 at 8:29 PM, wren ng thornton w...@freegeek.org wrote: Jon Fairbairn wrote: Another (provocative) observation is that most of the women programmers I've known were good at it and thought they might not be, but most of the men claimed to be good

Re: [Haskell-cafe] More Language.C work for Google's Summer of Code

2010-03-30 Thread wren ng thornton
Stephen Tetley wrote: Much of the behaviour of CPP is not defined and often inaccurately described, certainly it wouldn't appear to make an ideal one summer, student project. But to give Language.C integrated support for preprocessing, one needn't implement CPP. They only need to implement the

Re: [Haskell-cafe] Data Structures GSoC

2010-03-31 Thread wren ng thornton
Nathan Hunter wrote: Hello. I am hoping to take on the Data Structures project proposed two years ago by Don Stewart herehttp://hackage.haskell.org/trac/summer-of-code/ticket/1549, this summer. Before I write up my proposal to Google, I wanted to gauge the reaction of the Haskell community to

[Haskell-cafe] ANN: logfloat 0.12.1

2010-03-31 Thread wren ng thornton
-- logfloat 0.12.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] Apparently, Erlang does not have a static type system, since with hot code loading, this is intrinsically difficult.

2010-04-05 Thread wren ng thornton
Jason Dusek wrote: 2010/04/03 Casey Hawthorne cas...@istar.ca: Apparently, Erlang does not have a static type system, since with hot code loading, this is intrinsically difficult. It is doubtless hard to statically check a program that is not statically available :) Well, so long as you

Re: [Haskell-cafe] Re: Hackage accounts and real names

2010-04-06 Thread wren ng thornton
Ertugrul Soeylemez wrote: Human identity is much more than just a file descriptor or a map key, and people from academia often don't get this, because they don't have to fear using their real names. Particularly in economically illiberal countries being known as the author of a certain Haskell

Re: [Haskell-cafe] Re: Haskell.org re-design

2010-04-08 Thread wren ng thornton
Ivan Lazar Miljenovic wrote: Thomas Schilling nomin...@googlemail.com writes: http://i.imgur.com/kFqP3.png Didn't know about CSS's rgba to describe transparency. Very useful. It's a vely nice!! (in a Borat voice) +1. Both for the design, and for the content. -- Live well, ~wren

Re: [Haskell-cafe] haskell gsoc proposal for richer numerical type classes and supporting algorithms

2010-04-08 Thread wren ng thornton
Gregory Crosswhite wrote: On Apr 8, 2010, at 12:25 PM, Casey McCann wrote: Seriously, floating point so-called numbers don't even have reflexive equality! They don't? I am pretty sure that a floating point number is always equal to itself, with possibly a strange corner case for things

Re: [Haskell-cafe] Cabal dependency hell

2010-04-13 Thread wren ng thornton
Duncan Coutts wrote: On Sun, 2010-04-11 at 18:43 +0200, Maciej Piechotka wrote: - Privacy problem. I don't want the software to call home with data without asking. Obviously it is important that the data be anonymous and that we do not send stuff without the user's knowledge. While there is

Re: [Haskell-cafe] Cabal dependency hell

2010-04-13 Thread wren ng thornton
Ketil Malde wrote: Perhaps it would also be possible to suggest library upgrades likely to remedy the problem in case of a build failure? +1 for good error messages. +2 for should I try upgrading libfoo? [yn] integration (if configurable as AlwaysYes, AlwaysAsk, or AlwaysNo). -- Live

[Haskell-cafe] Re: Move MonadIO to base

2010-04-18 Thread wren ng thornton
This bounced because I have different emails registered for cafe@ and libraries@, so forwarding it along to the cafe. wren ng thornton wrote: wren ng thornton wrote: Heinrich Apfelmus wrote: Anders Kaseorg wrote: This concept can also be generalized to monad transformers: class MonadTrans

Re: [Haskell-cafe] Re: cabal: other-modules

2010-04-18 Thread wren ng thornton
Ivan Lazar Miljenovic wrote: Why are people suddenly using the term morally when they mean why doesn't this do what I think it should? None of its definitions seem to match what you mean: The usage on this thread seems a bit nonstandard, but I'm assuming it's based off the more general idiom

Re: [Haskell-cafe] Re: Move MonadIO to base

2010-04-19 Thread wren ng thornton
Anders Kaseorg wrote: Isaac Dupree wrote: Do you see the difference? The effects are sequenced in different places. The return/join pair moves all the effects *outside* the operations such as catch... thus defeating the entire purpose of morphIO. Yes; my question is more whether Wren has a

Re: [Haskell-cafe] Re: Move MonadIO to base

2010-04-19 Thread wren ng thornton
wren ng thornton wrote: Anders Kaseorg wrote: Isaac Dupree wrote: Do you see the difference? The effects are sequenced in different places. The return/join pair moves all the effects *outside* the operations such as catch... thus defeating the entire purpose of morphIO. Yes; my question

Re: [Haskell-cafe] Bulk Synchronous Parallel

2010-04-23 Thread wren ng thornton
Peter Gammie wrote: Alice/ML is the place to look for this technology. http://www.ps.uni-saarland.de/alice/ The project may be dead (I don't know), but they did have the most sophisticated take on pickling that I've seen. It's an ML variant, with futures, running on top of the same platform

Re: [Haskell-cafe] Proper Handling of Exceptional IEEE Floating Point Numbers

2010-04-23 Thread wren ng thornton
Casey McCann wrote: The only correct solution would be to strip floating point types of their instances for Ord, Eq, and--therefore, by extension--Num. For some reason, no one else seems to like that idea. I can't imagine why... I'm not terribly opposed to it. But then, I've also defined

Re: [Haskell-cafe] IO (Either a Error) question

2010-05-09 Thread wren ng thornton
Brandon S. Allbery KF8NH wrote: It's not a call, it's a definition as shown above. The simpler translation is: x - y becomes y = \x - (note incomplete expression; the next line must complete it) and the refutable pattern match takes place in the lambda binding. But because of the

Re: [Haskell-cafe] Haskell and the Software design process

2010-05-09 Thread wren ng thornton
Rafael Cunha de Almeida wrote: I don't think that safeSecondElement is worse than secondElement. I think it's better for the program to crash right away when you try to do something that doesn't make sense. Getting the secondElement of a list with one or less elements doesn't make sense, so you

Re: [Haskell-cafe] Haskell and the Software design process

2010-05-09 Thread wren ng thornton
Gregory Crosswhite wrote: Yes, but I think that it is also important to distinguish between cases where an error is expected to be able to occur at runtime, and cases where an error could only occur at runtime *if the programmer screwed up*. Well sure, but how can you demonstrate that you (the

Re: [Haskell-cafe] mixing map and mapM ?

2010-05-09 Thread wren ng thornton
Pierre-Etienne Meunier wrote: This way : do times-mapM PF.getFileStatus filenames = return.(map PF.modificationTime) Or also : do times-mapM (PF.getFileStatus = (return.(PF.modificationTime))) filenames let sorted=... I do not know exactly how ghc compiles the IO

Re: [Haskell-cafe] Speed of Error handling with Continuations vs. Eithers

2010-05-11 Thread wren ng thornton
Max Cantor wrote: Based on some discussions in #haskell, it seemed to be a consensus that using a modified continuation monad for Error handling instead of Eithers would be a significant optimization since it would eliminate a lot of conditional branching (everytime = is called in the Either

Re: [Haskell-cafe] Speed of Error handling with Continuations vs. Eithers

2010-05-11 Thread wren ng thornton
wren ng thornton wrote: Here's one big difference: newtype ErrCPS e m a = ErrCPS { runErrCPS :: forall r . (e - m r) -- error handler - (a - m r) -- success handler - m r } The analogous version I use is: newtype MaybeCPS a = MaybeCPS (forall r. (a - Maybe r

Re: [Haskell-cafe] Speed of Error handling with Continuations vs. Eithers

2010-05-13 Thread wren ng thornton
Andrea Vezzosi wrote: wren ng thornton wrote: With this change [1] I can't notice any difference for your benchmark[2]. Then again, all the runTest calls take 0 msec and I've had no luck making the computation take much time; perhaps your computer can detect a difference. On my machine

Re: [Haskell-cafe] Speed of Error handling with Continuations vs. Eithers

2010-05-13 Thread wren ng thornton
Antoine Latter wrote: While I also offer a transformer version of MaybeCPS, the transformer *does* suffer from significant slowdown. Also, for MaybeCPS it's better to leave the handlers inline in client code rather than to abstract them out; that helps to keep things concrete. So perhaps you

Re: [Haskell-cafe] Speed of Error handling with Continuations vs. Eithers

2010-05-13 Thread wren ng thornton
Andrea Vezzosi wrote: On Thu, May 13, 2010 at 10:51 AM, wren ng thornton w...@freegeek.org wrote: Andrea Vezzosi wrote: wren ng thornton wrote: With this change [1] I can't notice any difference for your benchmark[2]. Then again, all the runTest calls take 0 msec and I've had no luck making

Re: [Haskell-cafe] double2Float is faster than (fromRational . toRational)

2010-05-23 Thread wren ng thornton
Daniel Fischer wrote: There are more rules elsewhere. If you compile with optimisations, GHC turns your realToFrac into double2Float# nicely, so it's okay to use realToFrac. However, without optimisations, no rules fire, so you'll get (fromRational . toRational). That must be new, because it

Re: [Haskell-cafe] currying combinators

2010-05-27 Thread wren ng thornton
David Sankel wrote: keep :: ((t - b) - u - b) - ((t1 - t) - b) - (t1 - u) - b On Wed, May 26, 2010 at 12:49 PM, Lennart Augustsson lenn...@augustsson.net wrote: There are no interesting (i.e. total) functions of that type. I wonder how one would prove that to be the case. I tried and

Re: [Haskell-cafe] currying combinators

2010-05-27 Thread wren ng thornton
wren ng thornton wrote: David Sankel wrote: keep :: ((t - b) - u - b) - ((t1 - t) - b) - (t1 - u) - b Lennart Augustsson wrote: There are no interesting (i.e. total) functions of that type. I wonder how one would prove that to be the case. I tried and didn't come up with anything

Re: [Haskell-cafe] currying combinators

2010-05-27 Thread wren ng thornton
Dan Doel wrote: On Thursday 27 May 2010 3:27:58 am wren ng thornton wrote: By parametricty, presumably. Actually, I imagine the way he proved it was to use djinn, which uses a complete decision procedure for intuitionistic propositional logic. The proofs of theorems for that logic

Re: [Haskell-cafe] Re: Chuch encoding of data structures in Haskell

2010-05-27 Thread wren ng thornton
Stefan Monnier wrote: churchedBool :: t - t - t Important detail: the precise type is ∀t. t → t → t. encodeBool x = \t e - if x then t else e So the type of encodeBool should be: Bool → ∀t. t → t → t whereas Haskell will infer it to be ∀t. Bool → t → t → t Those are the same type.

Re: [Haskell-cafe] currying combinators

2010-05-27 Thread wren ng thornton
Dan Doel wrote: On Thursday 27 May 2010 1:49:36 pm wren ng thornton wrote: Sure, that's another option. But the failure of exhaustive search isn't a constructive/intuitionistic technique, so not everyone would accept the proof. Djinn is essentially an implementation of reasoning

Re: [Haskell-cafe] currying combinators

2010-05-28 Thread wren ng thornton
Lennart Augustsson wrote: So what would you consider a proof that there are no total Haskell functions of that type? Or, using Curry-Howard, a proof that the corresponding logical formula is unprovable in intuitionistic logic? It depends on what kind of proof I'm looking for. If I'm looking

Re: [Haskell-cafe] Re: Chuch encoding of data structures in Haskell

2010-05-28 Thread wren ng thornton
Ivan Miljenovic wrote: On 28 May 2010 15:18, wren ng thornton w...@freegeek.org wrote: Stefan Monnier wrote: churchedBool :: t - t - t Important detail: the precise type is ∀t. t → t → t. encodeBool x = \t e - if x then t else e So the type of encodeBool should be: Bool → ∀t. t → t → t

Re: [Haskell-cafe] currying combinators

2010-05-28 Thread wren ng thornton
Lennart Augustsson wrote: Yes, of course you have to trust Djinn to believe its proof. That's no different from having to trust me if I had done the proof by hand. Our you would have to trust yourself if you did the proof. True, though I think I didn't make my point clearly. The question is,

Re: [Haskell-cafe] A question on existential types and Church encoding

2010-05-30 Thread wren ng thornton
Jason Dagit wrote: In Church's λ-calc the types are ignored, Not so. Church-style lambda calculus is the one where types matter; Curry-style is the one that ignores types and evaluates as if it were the untyped lambda calculus. Church encodings are based on the untyped LC rather than

[Haskell-cafe] ANN: list-extras 0.4.0

2010-06-01 Thread wren ng thornton
-- list-extras 0.4.0 A minor (but interface-changing) release for common not-so-common functions for lists. -- Changes (since 0.3.0)

Re: [Haskell-cafe] Proposal: Sum type branches as extended types (as Type!Constructor)

2010-06-03 Thread wren ng thornton
Jake McArthur wrote: On 06/03/2010 10:14 AM, Gabriel Riba wrote: No need for runtime errors or exception control hd :: List!Cons a - a hd (Cons x _) = x This is already doable using GADTs: data Z data S n data List a n where Nil :: List a Z Cons :: a -

Re: [Haskell-cafe] ANN: random-fu 0.1.0.0

2010-06-03 Thread wren ng thornton
Richard O'Keefe wrote: There's something in that package that I don't understand, and I feel really stupid about this. data RVarT m a type RVar = RVarT Identity class Distribution d t where rvar :: d t - RVar t rvarT :: d t - RVarT n t Where does n come from? Presumably from

Re: [Haskell-cafe] Re: Proposal: Sum type branches as extended types (as Type!Constructor)

2010-06-07 Thread wren ng thornton
Gabriel Riba wrote: New proposal draft: Proposal: Type supplement for constructor specific uses of sum types Purpose: Avoid error clauses (runtime errors), exception control or Maybe types in partially defined (constructor specific) functions on sum types. As an example, with data List a

Re: [Haskell-cafe] ANN: random-fu 0.1.0.0

2010-06-07 Thread wren ng thornton
James Andrew Cook wrote: In particular, functions such as 'uniform' and 'normal' which directly construct RVars are very useful in defining the rvar implementation of other types. I have been reluctant to drop the rvar function from the Distribution class because it is very useful to be able

Re: [Haskell-cafe] Span function

2010-06-07 Thread wren ng thornton
R J wrote: Can someone provide a hand calculation of: span ( 0) [-1, -2, -3, 0, 1, 2, -3, -4, -5]? I know the result is ([-1, -2, -3], [0, 1, 2, -3, -4, -5]), but the recursion flummoxes me. Here's the Prelude definition: First, let's simplify the definition. span _ [] = ([],

[Haskell-cafe] QuickCheck 2

2010-06-10 Thread wren ng thornton
Since GHC 6.12 ships with QC2 it looks like it's finally time to get around to converting some old testing scripts. Unfortunately, one of the things I couldn't figure out last time I looked (and hence why I haven't switched) is how to reconfigure the configuration parameters to the driver

Re: [Haskell-cafe] QuickCheck 2

2010-06-10 Thread wren ng thornton
wren ng thornton wrote: Since GHC 6.12 ships with QC2 it looks like it's finally time to get around to converting some old testing scripts. Unfortunately, one of the things I couldn't figure out last time I looked (and hence why I haven't switched) is how to reconfigure the configuration

Re: [Haskell-cafe] QuickCheck 2

2010-06-10 Thread wren ng thornton
Ivan Lazar Miljenovic wrote: wren ng thornton w...@freegeek.org writes: Since GHC 6.12 ships with QC2 it looks like it's finally time to get around to converting some old testing scripts. Well, the Haskell Platform does, not GHC... Fair enough (it was one of the two :) Unfortunately

[Haskell-cafe] ANN: bytestring-trie 0.2.2 (major bugfix)

2010-06-10 Thread wren ng thornton
-- bytestring-trie 0.2.2 (major bugfix) Another release for efficient finite maps from (byte)strings to values. This version corrects a major bug affecting all users who merge tries.

Re: [Haskell-cafe] GATD and pattern matching

2010-06-12 Thread wren ng thornton
Felipe Lessa wrote: Well, I guess it can't be compiled at all :( [...] T.lhs:4:12: Duplicate instance declarations: instance [incoherent] (Show a) = MaybeShow a -- Defined at T.lhs:4:12-32 instance [incoherent] MaybeShow a -- Defined at T.lhs:7:12-22 Indeed,

Re: [Haskell-cafe] Re: Mining Twitter data in Haskell and Clojure

2010-06-15 Thread wren ng thornton
braver wrote: On Jun 14, 11:40 am, Don Stewart d...@galois.com wrote: Oh, you'll want insertWith'. You might also consider bytestring-trie for the Graph, and IntMap for the AdJList ? Yeah, I saw jsonb using Trie and thought there's a reason for it. But it's very API-poor compared with Map,

Re: [Haskell-cafe] Terminology

2010-06-15 Thread wren ng thornton
Emmanuel Castro wrote: I am looking for the name of the property linking two functions f and g when : [f(a),f(b),f(c)] = g([a,b,c]) Is there a standard name? Generally these sorts of things are called homomorphisms. It's a terribly general term, but that's the one I've always seen to

Re: [Haskell-cafe] Re: How does one get off haskell?

2010-06-18 Thread wren ng thornton
Edward Z. Yang wrote: Excerpts from Paul Lotti's message of Thu Jun 17 15:33:30 -0400 2010: Same feelings here. I work in a company that uses C++/Java and the best I could manage was to use Haskell for prototyping and then deliver in Java. This worked out twice so far. The downside is having

Re: [Haskell-cafe] Re: Mining Twitter data in Haskell and Clojure

2010-06-18 Thread wren ng thornton
braver wrote: Wren -- thanks for the clarification! Someone said that Foldable on Trie may not be very efficient -- is that true? That was probably me saying that I had worked on some more efficient implementations than those currently in use. Alas, the more efficient ones seem to alter the

Re: [Haskell-cafe] lecture notes for Finally Tagless - benefit of explicit fix combinator

2010-06-19 Thread wren ng thornton
Günther Schmidt wrote: Hi Stephen, I'm glad I asked. This sure sounds more interesting than I had anticipated. Is this an old hat for your off-the-shelf haskeller or something only found in the more seasoned haskellers tool box? I think it's pretty much the first time I encounter it. It

Re: [Haskell-cafe] Type-Level Programming

2010-06-25 Thread wren ng thornton
Jason Dagit wrote: On Fri, Jun 25, 2010 at 2:26 PM, Walt Rorie-Baety black.m...@gmail.comwrote: I've noticed over the - okay, over the months - that some folks enjoy the puzzle-like qualities of programming in the type system (poor Oleg, he's become #haskell's answer to the Chuck Norris meme

Re: [Haskell-cafe] Type-Level Programming

2010-06-26 Thread wren ng thornton
Gregory Crosswhite wrote: On 6/25/10 9:49 PM, wren ng thornton wrote: [1] http://eclipse-clp.org/ is currently down, but can be accessed at http://87.230.22.228/ [2] http://www.mercury.csse.unimelb.edu.au/ [3] http://www.lix.polytechnique.fr/~dale/lProlog/ [4] http://www-ps.informatik.uni

Re: [Haskell-cafe] Type-Level Programming

2010-06-26 Thread wren ng thornton
Andrew Coppin wrote: Stephen Tetley wrote: On 26 June 2010 08:07, Andrew Coppin andrewcop...@btinternet.com wrote: Out of curiosity, what the hell does dependently typed mean anyway? How about: The result type of a function may depend on the argument value (rather than just the argument

Re: [Haskell-cafe] Type-Level Programming

2010-06-26 Thread wren ng thornton
Andrew Coppin wrote: I think I looked at Coq (or was it Epigram?) and found it utterly incomprehensible. Whoever wrote the document I was reading was obviously very comfortable with advanced mathematical abstractions which I've never even heard of. One of the things I've found when dealing

Re: [Haskell-cafe] Type-Level Programming

2010-07-01 Thread wren ng thornton
Andrew Coppin wrote: wren ng thornton wrote: Andrew Coppin wrote: It's a bit like trying to learn Prolog from somebody who thinks that the difference between first-order and second-order logic is somehow common knowledge. (FWIW, I have absolutely no clue what that difference is. First

Re: [Haskell-cafe] Type-Level Programming

2010-07-01 Thread wren ng thornton
Andrew Coppin wrote: I did wonder what the heck a type function is or why you'd want one. And then a while later I wrote some code along the lines of class Collection c where type Element c :: * empty :: c - Bool first :: c - Element c So now it's like Element is a function that

Re: [Haskell-cafe] Re: chart broken under 6.12 according to criterion

2010-07-01 Thread wren ng thornton
Neil Brown wrote: On 01/07/10 10:19, Tom Doris wrote: According to the criterion.cabal file shipped with the latest (0.5.0.1) version of criterion, the Chart package is broken under GHC 6.12: flag Chart description: enable use of the Chart package -- Broken under GHC 6.12 so far Does

Re: [Haskell-cafe] How easy is it to hire Haskell programmers

2010-07-02 Thread wren ng thornton
Andrew Coppin wrote: Hmm, interesting. Applicative and Traversable are two classes I've never used and don't really understand the purpose of. Their main purpose is to avoid the list bias so prevalent from the Lispish side of FP. Namely, there are many different kinds of collections which

Re: [Haskell-cafe] Re: Rewriting a famous library and using the same name: pros and cons

2010-07-05 Thread wren ng thornton
Ivan Lazar Miljenovic wrote: Stephen Tetley stephen.tet...@gmail.com writes: I think it was Hugs compliant as least for some revisions - I seem to remember looking at it before I switched to GHC. People still use Hugs? :p MPJ uses it for teaching Haskell because it's a lot easier to

Re: [Haskell-cafe] Re: Rewriting a famous library and using the same name: pros and cons

2010-07-05 Thread wren ng thornton
Ivan Lazar Miljenovic wrote: Stephen Tetley stephen.tet...@gmail.com writes: On 3 July 2010 14:00, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote: So this argument isn't valid ;-) I think it was Hugs compliant as least for some revisions - I seem to remember looking at it before I

Re: [Haskell-cafe] More experiments with ATs

2010-07-05 Thread wren ng thornton
Andrew Coppin wrote: Brent Yorgey wrote: On Sun, Jul 04, 2010 at 10:31:34AM +0100, Andrew Coppin wrote: I have literally no idea what a type family is. I understand ATs (I think!), but TFs make no sense to me. ATs are just TFs which happen to be associated with a particular class. So

Re: [Haskell-cafe] cereal vs. binary

2010-07-06 Thread wren ng thornton
braver wrote: I dump results of a computation as a Data.Trie of [(Int,Float)]. It contains about 5 million entries, with the lists of 35 or less pairs each. It takes 8 minutes to load with Data.Binary and lookup a single key. What can take so long? If I change from compressed to uncompressed

[Haskell-cafe] Re: The state of Hugs

2010-07-06 Thread wren ng thornton
Ketil Malde wrote: wren ng thornton w...@freegeek.org writes: A bit more seriously: is there any listing anywhere of which extensions Hugs supports? Cabal has a partial listing embedded in its code, though I can't seem to find a textual version at the moment. In general, Hugs has all

[Haskell-cafe] Re: the state of Hugs 2

2010-07-06 Thread wren ng thornton
Daniel Fischer wrote: On Tuesday 06 July 2010 07:04:18, wren ng thornton wrote: Cabal has a partial listing embedded in its code, though I can't seem to find a textual version at the moment. In general, Hugs has all the features of GHC 6.6: FFI, CPP, MPTCs, FunDeps, OverlappingInstances,... I'm

Re: [Haskell-cafe] Functional dependencies and Peano numbers

2010-07-09 Thread wren ng thornton
Brandon S Allbery KF8NH wrote: On 7/6/10 15:37 , Oscar Finnsson wrote: but can they also be on a form similar to a b c d e f g h| b c - d e f | b d g - h (i.e. d,e,f are decided by the b,c-combination while h is decided by the b,d,g-combination)? I think the answer to this is yes, but if

Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-09 Thread wren ng thornton
Julian Fleischer wrote: Hi, 8. [...] Saying 0**0 is undefined seems reasonable, but why 0**y? I agree on 0**y being 0 (not undefined), but why should 0**0 be undefined? x**0 := 1, by convention. I'm not familiar with that convention. So far as I'm aware, the x**0=1 vs 0**y=0 conflict

Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-09 Thread wren ng thornton
Christopher Done wrote: On 10 July 2010 01:22, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote: Brandon S Allbery KF8NH allb...@ece.cmu.edu writes: On 7/8/10 22:25 , Alex Stangl wrote: 1. I.E. and e.g. should be followed by commas -- unless UK usage differs from US standards. (Page 3

Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: jhc 0.7.4

2010-07-10 Thread wren ng thornton
Brandon S Allbery KF8NH wrote: -BEGIN PGP SIGNED MESSAGE- Hash: SHA1 On 7/10/10 17:01 , Antoine Latter wrote: * The way you use sed doesn't work with the BSD sed that ships with my Mac Book. Installing GNU sed and using it works. Similarly, BSD find doesn't know about '-name', so make

Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: jhc 0.7.4

2010-07-10 Thread wren ng thornton
John Meacham wrote: On Sat, Jul 10, 2010 at 04:01:53PM -0500, Antoine Latter wrote: * running DrIFT on src/E/TypeCheck.hs fails with an illegal bytesequence in hGetContents. I'm guessing that this is only an issue when building DrIFT with GHC 6.12+, and that the file contains bytes illegal in

Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: jhc 0.7.4

2010-07-15 Thread wren ng thornton
Brandon S Allbery KF8NH wrote: wren is half right: at the level of Unixy APIs (and this includes anything that goes on in a Terminal window and anything that you will be doing from Haskell) you use UTF8, but OSX APIs --- that is, Carbon and Cocoa --- use UTF16. So for the purposes of ghc/jhc

Re: [Haskell-cafe] Re: lambda calculus and equational logic

2010-07-15 Thread wren ng thornton
Patrick Browne wrote: Heinrich Apfelmus wrote: 3) Not sure what you mean by proof theoretic semantics. Apparently, the trace of any program execution like, say product [1..5] - 1 * product [2..5] - .. - 120 is a proof that the initial and the final expression denote the same value. The

Re: [Haskell-cafe] trees and pointers

2010-07-15 Thread wren ng thornton
Jake McArthur wrote: On 07/15/2010 05:33 PM, Victor Gorokhov wrote: From the docs, lookup is O(min(n,W)) Actually worse than O(log n). Perhaps I am misunderstanding you, but O(min(n,W)) is either better than or the same as O(log n), depending on how you look at things, but I don't see any

Re: [Haskell-cafe] A question about State Monad and Monad in general

2010-07-15 Thread wren ng thornton
C K Kashyap wrote: Thanks Daniel, Better refactorability. If you're using monadic style, changing from, say, State Thing to StateT Thing OtherMonad or from StateT Thing FirstMonad to StateT Thing SecondMonad typically requires only few changes. Explicit state-passing usually requires more

Re: [Haskell-cafe] Re: Functional dependencies and Peano numbers (and hoogle-bug?)

2010-07-15 Thread wren ng thornton
Oscar Finnsson wrote: Anyone made a module/package that solves this problem already? I cannot be the first that needs generic type safe conversion... . There's a restricted version in logfloat:Data.Numer.RealToFrac[1] which generalizes the Prelude's realToFrac to improve performance and

Re: [Haskell-cafe] Refactoring type-class madness

2010-07-15 Thread wren ng thornton
Andrew Webb wrote: Because, at the basic level all of the experiments share this type of data, it seems that I should be able to write analysis functions that work for any experiment. However, the experiments differ in the stimuli used, and associated with each stimulus set is a set of

Re: [Haskell-cafe] trees and pointers

2010-07-16 Thread wren ng thornton
Jan-Willem Maessen wrote: As you observe, it's really down to constant factors. The reason IntMap (or any digital trie) is so interesting is that it is simple enough that the constant factors are quite good---in particular we don't waste a lot of time figuring out if we're going to need to

Re: [Haskell-cafe] in-equality type constraint?

2010-07-17 Thread wren ng thornton
Christopher Lane Hinson wrote: On Fri, 16 Jul 2010, Paul L wrote: Does anybody know why the type families only supports equality test like a ~ b, but not its negation? I would suggest that type equality is actually used for type inference, whereas proof of type inequality would have no

Re: [Haskell-cafe] Re: Hot-Swap with Haskell

2010-07-17 Thread wren ng thornton
Brandon S Allbery KF8NH wrote: On 7/16/10 05:21 , Andy Stewart wrote: IMO, haskell interpreter is perfect solution for samll script job. But i'm afraid haskell interpreter is slow for *large code*, i don't know, i haven't try this way... Hugs? Or you can try implementing (or finding) a SASL

Re: [Haskell-cafe] RE: Design for 2010.2.x series Haskell Platform site (Don Stewart)

2010-07-17 Thread wren ng thornton
Niemeijer, R.A. wrote: Here's my take on the new design: Screenshot: http://imgur.com/9LHvk.jpg Live version: http://dl.dropbox.com/u/623671/haskell_platform_redesign/index.htm Is it just me, or does aligning [OSX,Win,Linux] `zip` [Comprehensive, Robust, CuttingEdge] send the wrong

[Haskell-cafe] Re: Design for 2010.2.x series Haskell Platform site (Don Stewart)

2010-07-19 Thread wren ng thornton
Niemeijer, R.A. wrote: Is it just me, or does aligning [OSX,Win,Linux] `zip` [Comprehensive, Robust, CuttingEdge] send the wrong message... Yeah, I noticed that too when designing it, but at the time it didn't bother me too much. I know folks who'd refute all three of those associations,

Re: [Haskell-cafe] Design for 2010.2.x series Haskell Platform site

2010-07-19 Thread wren ng thornton
Malcolm Wallace wrote: I still like the original design on http://imgur.com/NjiVh a lot better, It has a simple modern design to it in my opinion :) +1. It is simply beautiful. Much more striking and memorable than the blue diver. I really like the background image; it's nicely striking

Re: [Haskell-cafe] On documentation

2010-07-22 Thread wren ng thornton
David Waern wrote: 2010/7/21 Richard O'Keefe o...@cs.otago.ac.nz: One of the really nice ideas in the R statistics system is that documentation pages can contain executable examples, and when you wrap up a package for distribution, the system checks that the examples run as advertised. The

Re: [Haskell-cafe] cabal, Setup.lhs example

2010-07-22 Thread wren ng thornton
Magnus Therning wrote: On Thu, Jul 22, 2010 at 11:52, Ross Paterson r...@soi.city.ac.uk wrote: On Thu, Jul 22, 2010 at 11:31:21AM +0100, Magnus Therning wrote: On Thu, Jul 22, 2010 at 10:59, Ross Paterson r...@soi.city.ac.uk wrote: Magnus is building by directly running the Setup.hs himself,

  1   2   3   4   5   6   7   8   9   10   >