Re: [Haskell-cafe] Re: Parsers are monadic?

2007-07-02 Thread Jonathan Cast
= \ ke ka -> a ((\ x -> either fe fa x ke ka) . Left) ((\ x -> either fe fa x ke ka) . Right) = \ ke ka -> a (\ x -> fe x ke ka) (\ x -> fa x ke ka) Not hard. > For a general proof, > we'd need an axiomatic characterization of dimonads and bind2.

Re: [Haskell-cafe] Before

2007-07-02 Thread Jonathan Cast
, and seq creates problems with some of these equations (or at least with proving that any of them hold for real programs!), but using the normal methods of Haskell equational reasoning (assume all values are total and finite, all functions preserve totality and finiteness, and the context prese

Re: [Haskell-cafe] Before

2007-07-03 Thread Jonathan Cast
On Tuesday 03 July 2007, you wrote: > On Mon, 2 Jul 2007, Jonathan Cast wrote: > > On Monday 02 July 2007, Andrew Coppin wrote: > > > What were monads like before they became a Haskell language construct? > > > > > > Is Haskell's idea of a "

Re: [Haskell-cafe] Before

2007-07-03 Thread Jonathan Cast
On Tuesday 03 July 2007, you wrote: > On Mon, 2 Jul 2007, Jonathan Cast wrote: > > On Monday 02 July 2007, Andrew Coppin wrote: > > > What were monads like before they became a Haskell language construct? > > > > > > Is Haskell's idea of a "

Re: [Haskell-cafe] A very nontrivial parser

2007-07-04 Thread Jonathan Cast
n, but this way all your parsers have polymorphic implementation types, but none has a type that trips the monomorphism restriction. There's some kind of argument here in the debate about the monomorphism restriction, but I'm not sure if it's for or against . . . [1] Jonathan Cast http:

Re: [Haskell-cafe] Binary serialization, was Re: Abstraction leak

2007-07-05 Thread Jonathan Cast
tter than (in terms of the POSIX bindings, worse than) Haskell. The one thing off the top of my head that Python had was Base64, but that's 20 lines of Haskell tops. Aside from that, nothing. Jonathan Cast http://sourceforge.net/projects/fid

Re: [Haskell-cafe] A very nontrivial parser

2007-07-05 Thread Jonathan Cast
On Thursday 05 July 2007, Andrew Coppin wrote: > Jonathan Cast wrote: > > On Wednesday 04 July 2007, Andrew Coppin wrote: > >> Anybody have a solution to this? > > > > newtype Parser state x y > > = Parser (forall src. Source src => (state, src x) ->

Re: [Haskell-cafe] A very nontrivial parser

2007-07-05 Thread Jonathan Cast
Andrew: By the way, could you share your definition of Stack with us? It isn't at all clear to me how stacked actually decides to terminate the underlying parser. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-

Re: [Haskell-cafe] A very nontrivial parser

2007-07-05 Thread Jonathan Cast
On Thursday 05 July 2007, Andrew Coppin wrote: > Jonathan Cast wrote: > > On Thursday 05 July 2007, Andrew Coppin wrote: > >> ...OK, anybody have a solution that works in Haskell 98? > > > > Rank-2 types are perhaps /the/ most common, widely accepted extension to >

Re: [Haskell-cafe] A very nontrivial parser [Source code]

2007-07-05 Thread Jonathan Cast
t . fst . run (many decodeRLEb1) . start () decodeRLEb1 :: (Integral x) => Process st x [x] decodeRLEb1 = do v <- get if v == 0 then do n <- get if n == 0 then return [0,0] else do x <- get

Re: [Haskell-cafe] A very nontrivial parser

2007-07-06 Thread Jonathan Cast
r). http://www.haskell.org/hierarchical-modules/ Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] A very nontrivial parser

2007-07-06 Thread Jonathan Cast
hould be, and Read and Show, which by the definition of deriving (and the expectations of 90% of the classes' users) lack isomorphic instances entirely. So, we can define the RWS monad as newtype RWS r w s alpha = RWS (ReaderT r (WriterT w (State s)) alpha) deriving Monad for example. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] A very nontrivial parser

2007-07-08 Thread Jonathan Cast
On Sunday 08 July 2007, Andrew Coppin wrote: > Jonathan Cast wrote: > > I wouldn't call rank-2 types extremely rare . . . > > Well now, my parser is annoyingly clunky to use, but it *works*. > However, I just found something where it seems to be *impossible* to > write

Re: [Haskell-cafe] A very nontrivial parser

2007-07-08 Thread Jonathan Cast
On Sunday 08 July 2007, Andrew Coppin wrote: > Jonathan Cast wrote: > > I think surely you're using existential data types rather than rank-2 > > types. > > You expect *me* to know? Surely not :) That's why I tried briefly explaining the ideas again. > > E

Re: [Haskell-cafe] Constraints on data-types, mis-feature?

2007-07-09 Thread Jonathan Cast
the status of this `feature' can be down-graded to wart: after all, if you say newtype Id a = Id a data GADT a where ... Alt :: (C a, C b, C c) => (a -> b -> c) -> GADT (Id a) -> GADT (Id b) -> GADT (Id c) ... pattern-matching on Alt introduces all three constrai

Re: [Haskell-cafe] Toy compression algorithms [was: A very edgy language]

2007-07-09 Thread Jonathan Cast
> ;-) Something like it's been done; compilers can take in a quadratic time list reverse and substitute a linear time version: http://homepages.inf.ed.ac.uk/wadler/papers/vanish/vanish.ps.gz (pg. 2-3). One of the better all-time papers by the major Haskell researchers, I'd sa

Re: [Haskell-cafe] Type system madness

2007-07-09 Thread Jonathan Cast
umer of the value. For the producer, it works the other way around. > > In Haskell 98, existential quantification is not supported at all, and > > universal quantification is not first class - values can have universal > > types if and only if they are bound by let. You can

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

2007-07-09 Thread Jonathan Cast
by exploiting the implementation of lazy evaluation. It > would seem that GHC's core data structures are coded closer to the > machine that anything I can write _in_ Haskell. So much for studying > how to explicitly write a good heap! > > So is there a name for this id

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

2007-07-09 Thread Jonathan Cast
www.haskell.org/haskellwiki/Prime_numbers > > On Jul 9, 2007, at 3:19 PM, Jonathan Cast wrote: > > I think we usually call it `exploiting laziness'. . . > > My motivation in asking for a name was to be able to find other > Haskell one-liners adequately replacing chapters of

Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Jonathan Cast
ives /might/ put you over GHC's inlining threshold, but that (ridiculous) scenario is the only thing that'll keep the argument from generalizing to your use case. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs _

[Haskell-cafe] Sequence Classes

2007-07-10 Thread Jonathan Cast
> t alpha transformerUp, transformerDn, transformerBi :: Sequence t beta => (Stream alpha -> Stream beta) -> t alpha -> t beta map :: Sequence t alpha => (alpha -> beta) -> t alpha -> t beta map f = transformerBi (mapS f) etc.? Jonathan Cast http://sourceforge.net/proj

Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Jonathan Cast
On Tuesday 10 July 2007, Nicolas Frisby wrote: > This might be a feasible appropriation of the term "destructor". Co-constructor? Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___

Re: [Haskell-cafe] Constraints on data-types, mis-feature?

2007-07-10 Thread Jonathan Cast
On Tuesday 10 July 2007, Jim Apple wrote: > On 7/9/07, Jonathan Cast <[EMAIL PROTECTED]> wrote: > > GADTs don't change anything (at least, not the last time I checked). > > GHC (in HEAD, at least) eliminates this wart for any datatype declared > with GADT syntax. &

Re: [Haskell-cafe] Type system madness

2007-07-10 Thread Jonathan Cast
plement uniqueness? Exactly. > > But that type of runST is illegal in Haskell-98, because it needs a > > universal quantifier *inside* the function-arrow! In the jargon, that > > type has rank 2; haskell 98 types may have rank at most 1. > > ...kinda wishing I hadn't asked... o_O Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Very freaky

2007-07-10 Thread Jonathan Cast
f this to the fragments of intuitionistic logic with logical connectives `and' (corresponds to products/record types) and `or' (corresponds to sums/union types) holds, as well, the prejudice that innovations in type systems should be driven by finding an isomorphism with some fragmen

Re: [Haskell-cafe] Constraints on data-types, mis-feature?

2007-07-11 Thread Jonathan Cast
On Tuesday 10 July 2007, Jim Apple wrote: > On 7/9/07, Jonathan Cast <[EMAIL PROTECTED]> wrote: > > GADTs don't change anything (at least, not the last time I checked). > > GHC (in HEAD, at least) eliminates this wart for any datatype declared > with GADT syntax. &

Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Jonathan Cast
On Wednesday 11 July 2007, Martin Percossi wrote: > Jonathan Cast wrote: > > toUpper :: exists x. x -> x works for only one choice of x. > > Are you sure that's not: > > "toUpper :: exists x. x -> x works for *at least one* choice of x" Not quite. When

Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Jonathan Cast
ul to understand both RealWorld as used by IO and the same mechanism as used by ST. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mai

Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Jonathan Cast
any functions. Shorter: longerThan n = not . null . drop n Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] function unique

2007-07-11 Thread Jonathan Cast
testunique' :: Eq a => [a] -- ^ $list List of elements to test -> [a] -- ^ $elementssofar List of elements seen thus far -> [a] -- ^ List of unique elements in 'list'. No patch forthcoming from this corner, though. Jonathan Cast http://sourc

Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Jonathan Cast
27;t do it that way and that *in GHC* newtype IO alpha = IO (State# RealWorld -> (# alpha, State# RealWorld #)) newtype ST s alpha = ST (State# (STState s) -> (# alpha, State# (STState s) #)) no? I don't see your objection to it. Especially if it causes light bulbs to

Re: [Haskell-cafe] function unique

2007-07-11 Thread Jonathan Cast
On Wednesday 11 July 2007, you wrote: > On Wed, Jul 11, 2007 at 03:59:45PM -0500, Jonathan Cast wrote: > > One could put up the Haddock doc-comment. Or, say, one could extend > > Haddock to support parameter names: > > > > testunique' :: Eq a > >

Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Jonathan Cast
something I misunderstood in the exchange ? Yeah. The reference to the "lazy natural type", which is: data Nat = Zero | Succ Nat deriving (Eq, Ord, Read, Show) instance Num Nat where fromInteger 0 = Zero fromInteger (n + 1) = Succ (fromInteger n) etc. then genericLe

Re: [Haskell-cafe] Type system madness

2007-07-12 Thread Jonathan Cast
There's your problem right there. Get either a terminal or a mail program that knows UTF-8. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Unicode support (Was: Type system madness)

2007-07-12 Thread Jonathan Cast
On Thursday 12 July 2007, Henning Thielemann wrote: > On Thu, 12 Jul 2007, Jonathan Cast wrote: > > On Thursday 12 July 2007, Henning Thielemann wrote: > > > On Tue, 10 Jul 2007, Albert Y. C. Lai wrote: > > > > Andrew Coppin wrote: > > > > > Wait..

Re: [Haskell-cafe] Lazy Lists and IO

2007-07-12 Thread Jonathan Cast
On Thursday 12 July 2007, Andrew Coppin wrote: > Jonathan Cast wrote: > > On Wednesday 11 July 2007, Chaddaï Fouché wrote: > >> Is there something I misunderstood in the exchange ? > > > > Yeah. The reference to the "lazy natural type", which is: > >

Re: [Haskell-cafe] Newbie question about tuples

2007-07-12 Thread Jonathan Cast
using "forall" aka existentially quantified types) > and vice versa? Use Data.Dynamic.Dynamic instead of explicit existentially quantified types, and it should come from gfoldl pretty readily. Jonathan Cast http://sourceforge.net/projects/fid-c

Re: [Haskell-cafe] function unique

2007-07-12 Thread Jonathan Cast
, sort of). GHC expends a good deal of effort looking for cases where pattern-matching is mutually-exclusive, and flattens it out to unique xn' = case xn' of [] -> [] x : xn -> x : unique (filter (/= x) xn) where each branch is equally efficient. Jonathan Cast http://sourceforg

Re: [Haskell-cafe] function unique

2007-07-12 Thread Jonathan Cast
on: [] is treated like a variable, except it's a variable whose behavior is statically known, so the compiler can do more with it. In fact, all of your versions given are equivalent in GHC, but only because you're taking advantage of more and more of the heroic work GHC does to conv

Re: [Haskell-cafe] Very freaky

2007-07-12 Thread Jonathan Cast
s paradox) but Nat is > > small.) > > OK, see, RIGHT THERE! That's the kind of sentence that I read and three > of my cognative processes dump sort with an "unexpected out of neural > capacity exception". o_O I'd think you'd expect it by now :) Lessa answered this one competently enough, I think. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Newbie question about tuples

2007-07-13 Thread Jonathan Cast
might google for that. And GHC 6.8 will have true type-level functions (with guaranteed termination, of course) which will help. But I'm sure a good google will turn up a clearer explanation than I can provide; I've never needed or wanted to

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

2007-07-13 Thread Jonathan Cast
gt; at the next digit after the last one to be shown and use > that to decide what to start with. There's no reason why > show should be defined to truncate rather than defined to > round after the last digit, is there? > > > In short, the Real numb

Re: [Haskell-cafe] Maintaining the community

2007-07-13 Thread Jonathan Cast
there semi-verbatim, rather > than pondering whether to write an email to the author to seek > permission, or cojole them into doing it. > > Should we feel free to put mailing list material onto the wiki? We should. We may not, yet, but that should change. Jonathan Cast http://so

Re: [Haskell-cafe] Type system madness

2007-07-13 Thread Jonathan Cast
t;> any post that mentions the word "Haskell". Except for Mr C++, who seems > >> to seek out such threads so he can tell me how superior C++ is to > >> Haskell...) > > > > Try not to care what other people think. > > LOL! If only that were in fact physica

Re: [Haskell-cafe] Maintaining the community

2007-07-14 Thread Jonathan Cast
he same way. I don't see how this involves "a few > terabytes"... Usenet is a giant network of NNTP servers (and UUCP servers before that...) that ISPs (and various Unix sites before that) maintained at one time (most seem to have given up on it now), with thousands o

Re: [Haskell-cafe] Another monad question...

2007-07-14 Thread Jonathan Cast
ctor is itself a monoid. So, if C is a category, the functor category C^C is a monoidal category with the identity functor in for the terminal object operator and composition in for the product, and a monoid in that category is a monad in C. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Haskell & monads for newbies

2007-07-15 Thread Jonathan Cast
tion: is separating I/O and > processing really the right thing to do (in terms of memory usage and > performance) in Haskell, and if so, why isn't it advertised more? (And > for extra credit, please explain why the article I quoted above didn't > make more of an impact in the Haskell community... :-)) Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Maintaining the community

2007-07-16 Thread Jonathan Cast
ots.* For most people, flying airliners is poorly-paid and quite exciting (at least up until the inevitable crash). Haskell may be a PhD language, but (that is, it isn't, but even if it were) it's quite easy to work in for PhDs. Which isn't at all the same thing as being ea

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

2007-07-18 Thread Jonathan Cast
: loop m xn (Consume f, []) -> [] (Consume f, x : xn) -> loop (f x) xn Discards the last few elements of the list if there aren't enough, but you can say genMap (Consume $ \ x -> Consume $ \ y -> Yield $ f x y) xn if you want, and you can even get true C-style varargs out of

Re: [Haskell-cafe] Producing MinimumValue

2007-07-19 Thread Jonathan Cast
;& allEqual xs > allEqual _ = ??? Try defining just allEqual [x1, x2, x3] and then generalize that. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___ Haskell-Cafe mailing list Haskell-Cafe@ha

Re: [Haskell-cafe] Equational Reasoning goes wrong

2007-07-22 Thread Jonathan Cast
ntation is as total as possible (which is equivalent to (2)), the derivation/re-factoring/whatever we're doing succeeds. Otherwise we've got either a bad specification or a bad implementation, anyway, so we'll need to investigate the issue in greater detail. Jonathan Cas

Re: [Haskell-cafe] filterFirst

2007-07-23 Thread Jonathan Cast
wo. Haskell can't figure out which arguments you want to stay the same on every recursive call, and which ones you want to vary, so you have to supply every argument every time. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___

Re: [Haskell-cafe] Another analogy

2007-07-23 Thread Jonathan Cast
even STEERS by pushing air. It sounds so > absurd, it couldn't possibly work... > > ...oh, but it DOES work. Very well, actually. In fact, a hovercraft can > do some things that the others can't. It works on water. It can go > sideways. It can REALLY turn on the spot."

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

2007-07-23 Thread Jonathan Cast
ntirely new entry in the semantic space --- and => /is/ already a keyword in GHC, which makes it worse. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Another analogy

2007-07-23 Thread Jonathan Cast
skell has to be small? It seems a great big language to me. > one of those Florida glades ones, like in Lassie, with one guy > sitting on it, weaving between the aligators. > > Java is a hot air balloon. Kindof obvious really ;-) > > C# is the F1 ferrari. Jonathan Cast http://

Re: [Haskell-cafe] "Identifier" generators with QuickCheck

2007-07-24 Thread Jonathan Cast
om character. I want both, the > characters, and the length to be random. do n <- choose (1, 63) replicateM $ elements validFirstChars Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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

2007-07-25 Thread Jonathan Cast
7; -> loop (x', cons streamTsil x ys, xn')} The best part is that you can have multiple data types to a view and multiple views of a data type, and the fact that pattern-matching proceeds one level at a time; the worst part is the rather syntactic way e.g. (:) as a view-constructo

Re: [Haskell-cafe] advantages of using fix to define rcursive functions

2007-07-26 Thread Jonathan Cast
adable code becomes when some of those single-use functions are inlined. You can't inline a recursive function, but you can inline an application of fix. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs pgpmuHDVlwwsm.pgp Description: PGP si

Re: [Haskell-cafe] Order of evaluation

2007-07-26 Thread Jonathan Cast
ugars to (||) = \ a b -> case a of True -> True False -> b Which does exactly what you want. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs pgpHiL6AGRotf.pgp Description: PGP signature __

Re: [Haskell-cafe] Indentation woes

2007-07-26 Thread Jonathan Cast
l benefit. > if one were so > inclined. If language complexity is the chief concern, why not > dispense with layout altogether (and a few more things beside)? > Perhaps fuzzy notions of aesthetics and intuitiveness should weigh > into the equation as well unless you don't mind prog

Re: [Haskell-cafe] Avoiding boilerplate retrieving GetOpt cmd line args

2007-07-27 Thread Jonathan Cast
String | DocStart String | DocEnd String deriving (Typeable, Data) getString :: Flag -> String -> Flag -> String getString c df f | toConstr c /= toConstr f = df getString c df (Filter s) = s getString c df (DateFormat s) = s getString c df (DocStart s) = s getString c df (Do

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

2007-07-27 Thread Jonathan Cast
gt; constructors of the same name could appear both in classes > and in data declarations. So if one had something like > > class Stream s where >Cons:: a -> s a -> s a >Nil:: s a >Snoc:: s a -> a -> s a >... > >{- an instanc

Re: [Haskell-cafe] combinators for a simple grammar

2007-08-06 Thread Jonathan Cast
he code that evaluates the expressions? Exactly thus. Say: data SearchCondition = Constant Bool | SearchCondition :||: SearchCondition | SearchCondition :&&: SearchCondition infixr 3 (:&&:) infixr 2 (:||:) And you're set. Jonathan Cast http://sourceforge.net/projects/fid-cor

Re: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-04 Thread Jonathan Cast
On Tue, 2007-09-04 at 16:06 +0200, Peter Verswyvelen wrote: > Henning Thielemann wrote: > > If you are happy with writing "do {1;2;3;4}" you are certainly also happy > > with "cv [1,2,3,4]", where cv means 'convert' and is a method of a class > > for converting between lists and another sequence ty

Re: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-04 Thread Jonathan Cast
On Tue, 2007-09-04 at 23:03 +0200, Peter Verswyvelen wrote: > Jonathan Cast wrote: > > I don't think this has been mentioned explicitly yet, but the > > discrepancy is purely for pedagogical purposes. > > > > In Gofer, list comprehensions (and list syntax, II

Re: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Jonathan Cast
On Wed, 2007-09-05 at 19:50 +0200, Twan van Laarhoven wrote: > Bulat Ziganshin wrote: > > Hello Simon, > > > > Wednesday, September 5, 2007, 11:19:28 AM, you wrote: > > > > > >>when you come across a case where GHC produces an > >>unhelpful message, send it in, along with the pro

Re: [Haskell-cafe] Mutable but boxed arrays?

2007-09-05 Thread Jonathan Cast
On Wed, 2007-09-05 at 20:37 +0200, Henning Thielemann wrote: > Can someone explain me, why there are arrays with mutable but boxed > elements? I thought that boxing is only needed for lazy evaluation. > However if I access an element of an array that is the result of a > sequence of in-place upd

Re: [Haskell-cafe] Re: Can somebody give any advice for beginners?

2007-09-11 Thread Jonathan Cast
On Tue, 2007-09-11 at 16:55 +, Gracjan Polak wrote: > clisper 163.com> writes: > > > > > > > haskell is greate > > but i don't know how to start. > > > > Don't! > > Learning Haskell will change your world! For worse! Really! Don't do that, > you still have time to go back! Or be damned

Re: [Haskell-cafe] Shouldnt this be lazy too?

2007-09-24 Thread Jonathan Cast
On Mon, 2007-09-24 at 17:35 +0100, Andrew Coppin wrote: > Vimal wrote: > > Hi all, > > > > I was surprised to find out that the following piece of code: > > > > > >> length [1..] > 10 > >> > > > > isnt lazily evaluated! I wouldnt expect this to be a bug, but > > in this case, shouldnt the c

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Jonathan Cast
On Tue, 2007-09-25 at 11:40 +0100, Andrew Coppin wrote: > Aaron Denney wrote: > > On 2007-09-25, Andrew Coppin <[EMAIL PROTECTED]> wrote: > > > >> OK, *now* I'm puzzled... Why does map . map type-check? > >> > > > > (map . map) = (.) map map > > > > (.) :: (a -> b) -> (b -> c) -> a -> c > >

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Jonathan Cast
On Tue, 2007-09-25 at 12:24 +0100, Andrew Coppin wrote: > Chaddaï Fouché wrote: > > 2007/9/25, Andrew Coppin <[EMAIL PROTECTED]>: > > > >> This is why I found it so surprising - and annoying - that you can't use > >> a 2-argument function in a point-free expression. > >> > >> For example, "zipWi

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Jonathan Cast
On Tue, 2007-09-25 at 19:18 +0100, Brian Hulley wrote: > Brian Hulley wrote: > > I'm wondering if anyone can shed light on the reason why > > > >x # y > > > > gets desugared to > > > > (#) x y > > > > and not > > > > (#) y x > > > > > Can anyone think of an example where the current desuga

Re: [Haskell-cafe] Haskell Cheat Sheet?

2007-09-26 Thread Jonathan Cast
On Tue, 2007-09-25 at 17:19 -0700, Dan Weston wrote: > One suggestion: > > Section 3.6 defines a function "fix": > > fix :: Eq x => (x -> x) -> x -> x > > fix f x = if x == x' then x else fix f x' > where x' = f x > > This confusingly differs in both type and meaning from the traditio

Re: [Haskell-cafe] PROPOSAL: New efficient Unicode string library.

2007-09-26 Thread Jonathan Cast
On Wed, 2007-09-26 at 09:05 +0200, Johan Tibell wrote: > > I'll look over the proposal more carefully when I get time, but the > > most important issue is to not let the storage type leak into the > > interface. > > Agreed, > > > From an implementation point of view, UTF-16 is the most efficient

Re: [Haskell-cafe] PROPOSAL: New efficient Unicode string library.

2007-09-26 Thread Jonathan Cast
On Wed, 2007-09-26 at 18:46 +0100, Duncan Coutts wrote: > In message <[EMAIL PROTECTED]> Jonathan Cast <[EMAIL PROTECTED]> writes: > > On Wed, 2007-09-26 at 09:05 +0200, Johan Tibell wrote: > > > > If UTF-16 is what's used by everyone else (how about Java?

Re: [Haskell-cafe] Haskell Cheat Sheet?

2007-09-26 Thread Jonathan Cast
On Wed, 2007-09-26 at 11:43 -0700, Dan Weston wrote: > It seems no one liked idea #2. I still think fix is the wrong name for > this, maybe limit would be better. It calculates least fixed points. `fix' is as good a name as any. `limit' is terrible; the argument to fix, a -> a, is neither a seq

Re: [Haskell-cafe] unsafePerformIO: are we safe?

2007-09-26 Thread Jonathan Cast
On Wed, 2007-09-26 at 14:28 -0700, Dan Piponi wrote: > On 9/26/07, Lennart Augustsson <[EMAIL PROTECTED]> wrote: > > Things can go arbitrarily wrong if you misuse unsafePerformIO, you can even > > subvert the type system. > > So...if I was in a subversive kind of mood (speaking hypothetically), >

Re: [Haskell-cafe] Haskell Cheat Sheet?

2007-09-26 Thread Jonathan Cast
On Wed, 2007-09-26 at 17:09 -0500, Derek Elkins wrote: > On Wed, 2007-09-26 at 14:12 -0700, Jonathan Cast wrote: > > On Wed, 2007-09-26 at 11:43 -0700, Dan Weston wrote: > > > It seems no one liked idea #2. I still think fix is the wrong name for > > > this,

Re: [Haskell-cafe] Re: isWHNF :: a -> IO Bool ?

2007-09-27 Thread Jonathan Cast
On Thu, 2007-09-27 at 16:57 +0100, Tristan Allwood wrote: > On Thu, Sep 27, 2007 at 05:31:51PM +0200, apfelmus wrote: > > Tristan Allwood wrote: > >> Does anyone know if there is a function that tells you if a haskell > >> value has been forced or not? e.g. isWHNF :: a -> IO Bool let x = > >> (map

Re: [Haskell-cafe] Newb question about map and a list of lists

2007-09-28 Thread Jonathan Cast
On Fri, 2007-09-28 at 11:19 -0700, Chuk Goodin wrote: > I have a list of lists of pairs of numeric Strings (like this: > [["2","3"],["1","2"],["13","14"]] etc.) I'd like to change it into a > list of a list of numbers, but I'm not sure how to go about it. If it > was just one list, I could use map,

Re: [Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-10-02 Thread Jonathan Cast
On Tue, 2007-10-02 at 08:02 -0700, Deborah Goldsmith wrote: > On Oct 2, 2007, at 5:11 AM, ChrisK wrote: > > Deborah Goldsmith wrote: > > > >> UTF-16 is the native encoding used for Cocoa, Java, ICU, and > >> Carbon, and > >> is what appears in the APIs for all of them. UTF-16 is also what's > >>

Re: [Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-10-02 Thread Jonathan Cast
On Tue, 2007-10-02 at 22:05 +0400, Miguel Mitrofanov wrote: > > I would like to, again, strongly argue against sacrificing > > compatibility > > with Linux/BSD/etc. for the sake of compatibility with OS X or > > Windows. > > Ehm? I've used to think MacOS is a sort of BSD... Cocoa, then. jcc

Re: [Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-10-02 Thread Jonathan Cast
On Wed, 2007-10-03 at 00:01 +0200, Twan van Laarhoven wrote: > Lots of people wrote: > > I want a UTF-8 bikeshed! > > No, I want a UTF-16 bikeshed! > > What the heck does it matter what encoding the library uses internally? +1 jcc ___ Haskell-Cafe

Re: [Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-10-03 Thread Jonathan Cast
On Wed, 2007-10-03 at 14:15 +0200, Stephane Bortzmeyer wrote: > On Wed, Oct 03, 2007 at 12:01:50AM +0200, > Twan van Laarhoven <[EMAIL PROTECTED]> wrote > a message of 24 lines which said: > > > Lots of people wrote: > > > I want a UTF-8 bikeshed! > > > No, I want a UTF-16 bikeshed! > > Person

Re: [Haskell-cafe] Why not assign a type to unsafePerformIO?

2007-10-03 Thread Jonathan Cast
On Wed, 2007-10-03 at 14:47 -0700, Justin Bailey wrote: > One of the "holes" in real-world Haskell is you never know if a > library/function is calling unsafePerformIO and you have to trust the > library author. I recognize the necessity of the function, but should > it announce itself? unsafePerfo

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

2007-10-05 Thread Jonathan Cast
On Fri, 2007-10-05 at 20:19 +, Aaron Denney wrote: > On 2007-10-05, Peter Verswyvelen <[EMAIL PROTECTED]> wrote: > > But where is the great IDE Haskell deserves??? :-) Seriously, 99% of the > > programmers I know don't want to look at it because when they see Emacs > > or VIM, they say "what

[Haskell-cafe] pi

2007-10-09 Thread Jonathan Cast
I just noticed that pi doesn't have a default definition in the standard prelude, according to the Haddock docs. Why is this? jcc ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] pi

2007-10-09 Thread Jonathan Cast
On Tue, 2007-10-09 at 13:07 -0700, Don Stewart wrote: > jonathanccast: > > I just noticed that pi doesn't have a default definition in the standard > > prelude, according to the Haddock docs. Why is this? > > $ ghci > Prelude> :t pi > pi :: (Floating a) => a > > Prelude> pi >

Re: [Haskell-cafe] pi

2007-10-10 Thread Jonathan Cast
On Wed, 2007-10-10 at 10:40 +0200, [EMAIL PROTECTED] wrote: > Yitzchak Gale writes: > > > Dan Piponi wrote: > >> The reusability of Num varies inversely with how many > >> assumptions you make about it. > > > > A default implementation of pi would only increase usability, > > not decrease it. >

Re: [Haskell-cafe] Re: pi

2007-10-10 Thread Jonathan Cast
On Wed, 2007-10-10 at 12:29 +0200, [EMAIL PROTECTED] wrote: > ChrisK writes: > > > Putting 'pi' in the same class as the trigonometric functions is good > > design. > > If you wish so... But: > Look, this is just a numeric constant. > Would you like to have e, the Euler's constant, etc., as wel

Re: [Haskell-cafe] pi

2007-10-10 Thread Jonathan Cast
On Thu, 2007-10-11 at 02:11 +0200, [EMAIL PROTECTED] wrote: > Jonathan Cast adds 'something' to a discussion about pi. > > I commented the statement of Yitzchak Gale, who answered some point > of Dan Piponi: > > >> > A default implementation of pi woul

Re: [Haskell-cafe] pi

2007-10-11 Thread Jonathan Cast
On Thu, 2007-10-11 at 11:22 +0200, [EMAIL PROTECTED] wrote: > My last word (promise!) on the subject, especially addressed to Jonathan > Cast, who writes: > > > To wit, I'm still failing to understand what your position is. > > I quote the Master: > > Le

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

2007-10-11 Thread Jonathan Cast
On Wed, 2007-10-10 at 21:45 -0400, Brandon S. Allbery KF8NH wrote: > On Oct 10, 2007, at 20:14 , Michael Vanier wrote: > > > I haven't been following this discussion closely, but here's an > > idea: use reverse psychology. > > > > "Haskell -- You're probably not smart enough to understand it." >

Re: [Haskell-cafe] Re: pi

2007-10-11 Thread Jonathan Cast
On Thu, 2007-10-11 at 07:57 +, Aaron Denney wrote: > On 2007-10-11, Jonathan Cast <[EMAIL PROTECTED]> wrote: > > Yes. I am very eager to criticize your wording. To wit, I'm still > > failing to understand what your position is. Is it fair to say that > > yo

Re: [Haskell-cafe] Type Synonyms

2007-10-11 Thread Jonathan Cast
On Fri, 2007-10-12 at 11:00 +1300, ok wrote: > On 11 Oct 2007, at 4:06 pm, Tom Davies basically asked for > something equivalent to Ada's > type T is new Old_T; > which introduces a *distinct* type T that has all the operations and > literals of Old_T. In functional terms, suppose there is a

Re: [Haskell-cafe] Re: Type-level arithmetic

2007-10-23 Thread Jonathan Cast
On Fri, 2007-10-12 at 13:52 -0400, Steve Schafer wrote: > On Fri, 12 Oct 2007 18:24:38 +0100, you wrote: > > >I was actually thinking more along the lines of a programming language > >where you can just write > > > > head :: (n > 1) => List n x -> x > > > > tail :: List n x -> List (n-1) x > >

Re: [Haskell-cafe] Tutorial: Curry-Howard Correspondence

2007-10-23 Thread Jonathan Cast
On Fri, 2007-10-19 at 00:02 +0200, [EMAIL PROTECTED] wrote: > Dan Weston writes: > > > ... now I am totally flummoxed: > > > > thm1 :: (a -> a) -> a > > thm1 f = let x = f x in x > > > > > thm1 (const 1) > > 1 > > > > I *thought* that the theorem ((a => a) => a) is not derivable (after all,

Re: [Haskell-cafe] Polymorphic (typeclass) values in a list?

2007-10-23 Thread Jonathan Cast
On Fri, 2007-10-19 at 23:57 +0800, TJ wrote: > Henning Thielemann: > > > class Renderable a where > > > render :: a -> RasterImage > > > > > > scene :: Renderable a => [a] > > > > This signature is valid, but it means that all list elements must be of > > the same Renderable type. > > Yes, that'

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

2007-10-23 Thread Jonathan Cast
On Fri, 2007-10-12 at 19:33 -0400, Brandon S. Allbery KF8NH wrote: > On Oct 12, 2007, at 18:35 , Albert Y. C. Lai wrote: > > > You are not expected to be convinced this, but it seems > > continuations completely characterize system programming. :) > > Didn't someone already prove all monads can

Re: [Haskell-cafe] Do you trust Wikipedia?

2007-10-23 Thread Jonathan Cast
On Fri, 2007-10-19 at 02:45 +0200, [EMAIL PROTECTED] wrote: > PR Stanley writes: > > > One of the reasons I'm interested in Wikipedia and Wikibook is because > > you're more likely to find Latex source code used for typesetting the > > maths. > > Latex is the one and only 100% tool right now. >

  1   2   3   4   5   6   >