Re: [Haskell] Annoying naming clashes

2004-06-15 Thread John Meacham
at are hard to name and lead to naming conflicts. It is these structures that haskell programers learn are not needed as their skills improve. but yeah, I love intermediate structures as much as the next haskell programmer :) John -- John Meacham - ârepetae.netâjohnâ __

Re: [Haskell] Annoying naming clashes

2004-06-15 Thread John Meacham
On Tue, Jun 15, 2004 at 11:30:24AM +0200, Wolfgang Jeltsch wrote: > Am Dienstag, 15. Juni 2004 04:05 schrieb John Meacham: > > [...] > > > now classes are a bit trickier, the main thing is that classes in > > haskell are not like classes in other languages. A class in has

Re: [Haskell] Annoying naming clashes

2004-06-17 Thread John Meacham
hat have happened in the meantime. I think the moral is, don't hold your breath. and learn pattern guards, they are a really really useful and universal extension to the language. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell

Re: [Haskell] Annoying naming clashes

2004-06-17 Thread John Meacham
t they were in nhc and hugs. although, I must admit, I don't spend much time with these other compilers. in that case, consider this a feature request for all other haskell implementations to retroactivly make my statement true. John -- J

[Haskell] ANNOUNCING: The Haskell Bookstore

2004-06-18 Thread John Meacham
ng on your copyright, send me a note before breaking out the lawyers and I will be happy to work something out :) John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] modern language design, stone age tools

2004-06-23 Thread John Meacham
find them more or less the most unfriendly and useless things > > So how do you debug problems like "Prelude.head: empty list" > in large programs? enable template haskell and use $head where $head is defined to generate 'head' with the error annotated with the curre

Re: [Haskell] modern language design, stone age tools

2004-06-23 Thread John Meacham
ing Exception and the various routines like isIOError were modified to 'look through' these annotations. adding stack traces just where you think it might be useful becomes quite easy then. John -- John Meacham - ârepetae.netâjohnâ _

Re: [Haskell] modern language design, stone age tools

2004-06-23 Thread John Meacham
matching for deconstruction is just a good habit to get into. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

[Haskell] ANNOUNCE: new books in the bookstore!

2004-07-23 Thread John Meacham
://www.cs.chalmers.se/~boquist/phd/index.html Enjoy the books! More titles are in the queue. :) John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

[Haskell] confusing language in report and a bug in (ghc|hugs)

2004-07-28 Thread John Meacham
o { a,b::Int } au = Foo { a = undefined, b = 0 } main = case au of Foo { b = 1, a = 0 } -> print "foo" _ -> print "bar" ghc => error: Prelue.undefined hugs => "bar" -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] confusing language in report and a bug in (ghc|hugs)

2004-07-29 Thread John Meacham
d have been making my life easier. Perhaps I have just not been trained to recognize when it should be used. It is amazing what little things you pick up when you sit down and read the report as if it were a novel :) John -- John Meacham - ârepetae.netâjohnâ ___

Re: Ternary operators in Haskell, an observation (was: [Haskell] Do the libraries define S' ?)

2004-08-02 Thread John Meacham
mp;& g directly where f and g are functions which return bool. http://repetae.net/john/recent/out/Boolean.html it also gives you perl-like short circuting, so Just 'a' || Just 'b' -> Just 'a' and so forth... John -- John Meacham - ârepetae.netâjo

[Haskell] Re: overzealous defaulting?

2004-08-24 Thread John Meacham
-boot files, so they will get whatever is declared in those, but what is the correct thing that should happen in a fully recursive module supporting haskell compiler? John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list [E

Re: [Haskell] 2-D Plots, graphical representation of massive data

2004-08-26 Thread John Meacham
e a useful project. What would be cooler (IMHO) would be brining all of matlabs functionality into haskell via haskell libraries so one may use 'ghci' sort of as one uses matlab, but with the advantages haskell brings. John -- John Meacham

[Haskell] Global Variables and IO initializers: A proposal and semantics

2004-10-12 Thread John Meacham
be applied and if it determines an integral IORef is always passed strict values for instance, it can unbox the global int. for the purposes of GC, the global variables can be treated like CAFs. So, I believe this is a clean and efficient way to allow global state in haskell. sorry for t

Re: [Haskell] Global Variables and IO initializers: A proposal and semantics

2004-10-13 Thread John Meacham
On Wed, Oct 13, 2004 at 07:20:06AM +0100, Jules Bean wrote: > > On 12 Oct 2004, at 23:33, John Meacham wrote: > > > and via the FFI just a > > foreign import "&global_var" :: Ptr Int > > note that we do not need any foregin code, just an object wh

Re: [Haskell] threading mutable state through callbacks

2004-10-13 Thread John Meacham
On Wed, Oct 13, 2004 at 10:01:08AM +0100, Adrian Hey wrote: > On Wednesday 13 Oct 2004 3:36 am, Wolfgang Thaller wrote: > > b) Some predetermined order, with semantics like mdo: > > > > John Meacham wrote: > > > The basic idea is that your entire program behaves as i

Re: [Haskell] Global Variables and IO initializers: A proposal andsemantics

2004-10-15 Thread John Meacham
thing we lose is that the > translation may fail to type-check. This was a compromise we had to do, > and we chose the light-weight view that mdo is only syntactic-sugar. Ah yes, that is exactly what I meant. I misread recursion as polymorphism. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] hscpp

2004-09-27 Thread John Meacham
pear at the end of a line. so do things like infixl 9 \\ -- Hack for CPP and it should work. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

[Haskell] Real life examples

2004-11-23 Thread John Meacham
on global state will already HAVE to be in the IO monad, that should be indication enough to the programmer that this depends on the world, extended by the programmer in well thought out abstracted ways. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Real life examples

2004-11-24 Thread John Meacham
te proposal based on the 'mdo' semantics. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Real life examples

2004-11-24 Thread John Meacham
On Wed, Nov 24, 2004 at 02:40:52PM +, Ben Rudiak-Gould wrote: > John Meacham wrote: > > > randomIO [...] Data.Unique [...] Atom.hs [...] caching > > These are all great examples of cases where having per-process state > makes sense. > > But they can all be implem

Re: [Haskell] Real life examples

2004-11-24 Thread John Meacham
d be no different if sort were written with global state or even was a top level binding. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Real life examples

2004-11-24 Thread John Meacham
On Wed, Nov 24, 2004 at 10:40:41PM +, Ben Rudiak-Gould wrote: > John Meacham wrote: > > >On Wed, Nov 24, 2004 at 02:40:52PM +, Ben Rudiak-Gould wrote: > > > >>But they can all be implemented with George Russell's library plus safe > >>(pur

Re: [Haskell] Real life examples

2004-11-24 Thread John Meacham
On Wed, Nov 24, 2004 at 11:38:42PM +, Ben Rudiak-Gould wrote: > John Meacham wrote: > > >With my mdo proposal, and I think all proposals brought forth, the > >module system behaves identically to how it normally does for > >namespace control. [...] modules do not

Re: [Haskell] Real life examples

2004-11-24 Thread John Meacham
On Thu, Nov 25, 2004 at 12:49:13AM +0100, Benjamin Franksen wrote: > On Thursday 25 November 2004 00:38, Ben Rudiak-Gould wrote: > > John Meacham wrote: > > >With my mdo proposal, and I think all proposals brought forth, the > > >module system behaves identically

[Haskell] Re: Top-level <-

2004-11-25 Thread John Meacham
On Thu, Nov 25, 2004 at 10:07:20AM +0100, George Russell wrote: > John Meacham wrote: > > Now, my mdo proposal as written would have "hello" outputed exactly once > > at module start up time no matter what, whether x is demanded or not. it > > is equivalant t

Re: [Haskell] Real life examples

2004-11-25 Thread John Meacham
On Thu, Nov 25, 2004 at 09:54:41AM +0100, George Russell wrote: > John Meacham wrote (snipped): > > George Russell's library is precicly an invalid use of unsafePerformIO. > > Internally, it does the invalid unsafePerformIO (newIORef) trick which > > is exactly the prob

[Haskell] ANNOUNCE: DrIFT 2.1.0

2004-12-01 Thread John Meacham
ter yet use darcs to send a patch. The half-minute tutorial for sending me a patch if you don't know darcs is ;darcs get http://repetae.net/john/repos/DrIFT/ ;cd DrIFT edit code ;darcs record ;darcs send more info on darcs can be gotten from http://abrid

[Haskell] discrepancy between nhc and ghc

2004-12-01 Thread John Meacham
behavior since it lets you export methods without exporting the class and lets you hide the implementation detail of whether a function is implemented as a method or normal declaration. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing

[Haskell] [ANNOUNCE] New version of unicode CWString library with extras

2005-01-18 Thread John Meacham
haskell library) I'd like to be able to print the error messages with the LocaleIO library as it is the only place where the wrong encoding still can leak out. -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list Haskell@haskell.org

[Haskell] Announce: Adaptive Simulated Annealing interface for haskell

2005-01-19 Thread John Meacham
rmation you usually need to explicitly specify in other languages. my code: http://repetae.net/john/recent/out/HsASA.html Lester's ASA page: http://www.ingber.com/ John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list

[Haskell] monad transformers

2005-01-29 Thread John Meacham
an arbitrary MonadIO. ** The monad transformer libraries appear to have moved somewhere in the most recent cvs fptools tree, anyone know where they moved too? *** Monad transformers rock. -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing lis

[Haskell] class assosiated types, via GADTs.

2005-02-14 Thread John Meacham
r perhaps it is what the paper actually says to do and I am just misreading it :) I thought I'd share because I have really wanted the class assosiated types in various situations and I wasn't sure if I'd have time (or knowledge) to explore this seriously too much further. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] class assosiated types, via GADTs.

2005-02-15 Thread John Meacham
implement without touching too much of ghcs internals. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] Re: class assosiated types, via GADTs.

2005-02-15 Thread John Meacham
On Wed, Feb 16, 2005 at 12:42:08AM +1100, Manuel M T Chakravarty wrote: > On Mon, 2005-02-14 at 19:17 -0800, John Meacham wrote: > > I believe there is a realationship between GADTs and class assosiated > > types which hints at a much simpler implementation of class assosiated

[Haskell] Re: class assosiated types, via GADTs.

2005-02-18 Thread John Meacham
wasn't really sure where the complexity of implementing them was coming from. > Nevertheless, it is interesting to see how it all fits together. definitly, I know I understand both CATs and GADTs to a much greater degree by thinking about this problem. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Re: Type of y f = f . f

2005-03-01 Thread John Meacham
; a -> b (b a) > d f = f . f rank-n polymorphism is fun :) now, I guess the tricky thing is creating a function which will work as d head and d (:[]) ... John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] sugar for extensible types (was: class associated types, via GADTs.)

2005-03-03 Thread John Meacham
ensibleExceptions (or something shorter?) then new code can use this better interface and eventually the old interface can be depreciated. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] "Classic" vs. "Cunning Newtype" Derivation

2005-03-07 Thread John Meacham
correct, or are there subtle differences? Read, Show, Typeable, and Data are the only differences AFAIK. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] instance Bounded Double

2005-03-13 Thread John Meacham
ld be made available somewhere in the libraries since portable programs would have no other way to figure this sort of thing out. John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] The FunctorM library

2005-03-23 Thread John Meacham
What do the Simons think? This was brought up before, a problem is that an 'import' can silently change behavior, because depending on whether an existing Functor instance is already in scope, a Monad instance will either create one or not. John -- John Meacham - ârepetae.ne

Re: [Haskell] No Pattern Guards

2005-03-28 Thread John Meacham
to write them up or was there further discussion elsewhere? Old mailing list archives seem to be hard to come by. http://www.cs.chalmers.se/~rjmh/Haskell/Messages/Decisions.cgi John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] pretty printing Haskell code with auto parens?

2005-04-12 Thread John Meacham
re is one included in 'hatchet' which I have succescfully reused in other projects. A bug is that it doesn't refix infix patterns, but that should be easy to fix. http://www.cs.mu.oz.au/~bjpop/hatchet.html You will probably have to write something to collect fixities from imp

[Haskell] ANNOUNCE: The jhc Haskell compiler.

2005-04-19 Thread John Meacham
ors (and some non-errors) cause the compiler to quit with an 'error' or pattern match failure. == References == * Boquist Thesis * Henk paper * Pure Type Systems type checking paper * CPR analysis. * Strictness analysis w/ HORN clauses * Typing Haskell in Haskell * Hatchet -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Re: ANNOUNCE: The jhc Haskell compiler.

2005-04-20 Thread John Meacham
es, most of it is derived from them anyway. There are only so many ways to define 'head' :) John -- John Meacham - ârepetae.netâjohnâ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Re: ANNOUNCE: The jhc Haskell compiler.

2005-04-27 Thread John Meacham
On Wed, Apr 27, 2005 at 06:14:53PM +0200, Stephane Bortzmeyer wrote: > On Tue, Apr 19, 2005 at 04:54:42AM -0700, > John Meacham <[EMAIL PROTECTED]> wrote > a message of 375 lines which said: > > > There are still substantial issues which need to be overcome before

Re: [Haskell] Been there, it's great. Let's do it again, Re: HaskellForge

2005-05-31 Thread John Meacham
lForge: The web site'. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] translation of "kind"

2005-06-20 Thread John Meacham
ready mentioned. > And we often have to reuse existing words like "constructor" or "type" for > scientific purposes which forces us to declare what we mean with these words. I propose that all future haskell discussion take place in lojban. :) http://www.lojban.org/

Re: [Haskell] ANNOUNCE: GHC survey results

2005-06-28 Thread John Meacham
d to be a plugin based thing, but rather an executable that ghc can run and pass commands to it on stdin and read results on stdout. Being able to just work on any unmodified program the compiler supports is a huge feature. John -- John Meacham - ⑆repetae.net⑆john⑈

[Haskell] Re: ANNOUNCE: GHC survey results

2005-06-28 Thread John Meacham
ion or modification of function structure like with monads. - none of the implicit parameter oddness. Comments? and yes, I know the term 'variable' is a misnomer when dealing with haskell :) John -- John Meacham - ⑆repetae.net⑆john⑈ __

Re: [Haskell] proposal about declaring language version and language extensions used in specific module

2005-08-09 Thread John Meacham
I thought there was talk of a standardized {-# LANGUAGE ... #-} pragma somewhere.. but I can't seem to find it. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/lis

Re: [Haskell] pros and cons of static typing and side effects ?

2005-08-11 Thread John Meacham
ically have to constantly redervive everything the program does and all the unspoken invarients to understand it and how to change it. which is something that gets super-linearly harder as code size grows. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] concurrency analysis

2005-08-11 Thread John Meacham
doing SMP parallelism with haskell. It seems that some sort of abstract interpretation could provide a conservative answer to this similar to the way update analysis is done. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing li

Re: [Haskell] ANNOUNCE: ghc-src version 0.2.0

2005-08-23 Thread John Meacham
ch them to the right places? I thought it would be really cool if compilers could use the haddock documentation when printing out error messages and be able to query documentation as well as type info from inside the interpreter. John -- Jo

Re: [Haskell] ANNOUNCE: ghc-src version 0.2.0

2005-08-24 Thread John Meacham
On Wed, Aug 24, 2005 at 10:14:58AM +0100, Duncan Coutts wrote: > On Wed, 2005-08-24 at 10:56 +0200, Lemmih wrote: > > On 8/24/05, Krasimir Angelov <[EMAIL PROTECTED]> wrote: > > > 2005/8/24, John Meacham <[EMAIL PROTECTED]>: > > > > ooh. neat. any chanc

Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-08 Thread John Meacham
those, but that is no problem other than being non-haskell-98 compatable). Solving this 'class inflexibility' problem in general is something I have given some thought too. I will let everyone know if I figure something out... John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] monadic where

2005-09-18 Thread John Meacham
monad is an instance of MonadFix and although that would be nice to have, it is not really vital since 'mdo', although indispensable sometimes, is not generally needed except in a few special cases so I'd stick to the standard 'do' translation. John -- John Meacham

Re: [Haskell] monadic where

2005-09-20 Thread John Meacham
On Tue, Sep 20, 2005 at 10:29:14AM +0300, Yitzchak Gale wrote: > John Meacham wrote: > > f x y > >| b > c = ... > >| c <= 0 && a > b = ... > >where > > a = ... > > b <- ... > > c <- ... >

Re: [Haskell] Re: [Haskell-cafe] Haskell versus Lisp

2005-09-20 Thread John Meacham
hen can inspect and modify and then "interpret". John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] strictness of putChar: report incomplete?

2005-10-04 Thread John Meacham
urse. I believe the hugs behavior is correct and ghc and jhc are wrong, but there were differing opinions on #haskell. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] getArgs, maxBound, float division: pure functions?

2005-10-11 Thread John Meacham
ere of specific rounding modes too. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] PROPOSAL: class aliases

2005-10-12 Thread John Meacham
d an earlier supertyping proposal you might know about, I feel this is a much better proposal even though it doesn't fully subsume my supertyping proposal, I feel it solves the problems it was meant to solve in a cleaner and easier to implement way. * You may wonder why for the num exam

Re: [Haskell] PROPOSAL: class aliases

2005-10-12 Thread John Meacham
On Thu, Oct 13, 2005 at 01:14:19AM +0100, Philippa Cowderoy wrote: > On Wed, 12 Oct 2005, John Meacham wrote: > > >ideally we would want to split it up like so (but with more mathematically > >precise names): > > > > Might it also be reasonable to provide le

Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
constraints. > class alias FooBar a = Show a => (Foo a, Bar a) where ... should do nicely. if nothing better comes along I will update my copy of the proposal with this new syntax... John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
of those rather than the internal ones. How much this will be an issue in practice we will have to see. we might have to experiment some to find the best method for producing error messages. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
eah, that has confused several people already. I wish I used the new syntax in my original post, it really makes more sense. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
than just rewriting the prelude. the Lattice example I gave is right out of my toolbox and my anoyances with it are part of what motivated me to write this. > Anyway, my main point it: would a smaller change not suffice? I do not think it suffices. We cou

Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
On Thu, Oct 13, 2005 at 01:41:14PM -0400, Paul Govereau wrote: > On Oct 12, John Meacham wrote: > > > > [...] > > > > > class Num a where > > > (+), (*):: a -> a -> a > > > (-) :: a -> a -> a > > > negate

Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
7;alias' so it is clearer what is going on. but if it were actually implemented we could decide whether we want it or not. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
other issues mentioned in my other reply. > > One final thing which would be nice is the ability to define > instances of superclass methods in a subclass declaration. But this > takes things in a different direction entirely.

[Haskell] PROPOSAL: class aliases (revised)

2005-10-13 Thread John Meacham
. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] ANNOUNCE: JRegex library

2005-10-17 Thread John Meacham
bar"),(1,"ooo"),(2,"ar")],array (0,2) [(0,"foobaaar"),(1,"oo"),(2,"aaar")]] here is its homepage: http://repetae.net/john/computer/haskell/JRegex/ I released a different version of this library in the past, but this version has been cleaned up, moved to a proper spot in the libraries, and is cabalized. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Excessive sharing and GHC

2005-10-18 Thread John Meacham
ld onto more than needed. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Excessive sharing and GHC

2005-10-18 Thread John Meacham
On Wed, Oct 19, 2005 at 12:01:07AM +0200, Daan Leijen wrote: > John Meacham wrote: > >On Tue, Oct 18, 2005 at 08:31:19AM +0100, Simon Peyton-Jones wrote: > >>GHC tries not to create space leaks, but does not guarantee not to. In > >>particular, the full laziness tran

Re: [Haskell] reader-like IO, parents of threads

2005-10-18 Thread John Meacham
read_getspecific' returns the value currently associated with > KEY in the calling thread. > > If there is no such key KEY, it returns `NULL'. in gcc you can create (faster) thread local storage with the __thread keyword. as in __thread int foo; m

Re: [Haskell] specification of sum

2005-11-01 Thread John Meacham
askell 06) I'd also like to see 'join' and 'ap' added to Monad while we are at it. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] pattern matching on record fields and position

2005-11-02 Thread John Meacham
le a data type with no appropriate field. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] The next langauage definition version will be ``Haskell 1.6''

2005-11-02 Thread John Meacham
from) Perhaps I just dislike dogshed discussions (even when taking place internally) John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] specification of sum

2005-11-02 Thread John Meacham
or an instance than + and *. however, I don't know if this ever actually occurs in practice. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] why don't we have const Ptrs?

2005-11-05 Thread John Meacham
category. you can cause the compiler itself to bottom out using them. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Improvements to GHC

2005-11-17 Thread John Meacham
ways to improve the current record system more conservativly. (like, why is update partial? it should not be partial. grr.) John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] existential type synonyms

2005-12-12 Thread John Meacham
Type a) -> (forall b . Type b) -> Bool which means something quite different. if we use 'exists' for existential types, this might be another useful use of said name. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell

Re: [Haskell] Making Haskell more open

2006-01-04 Thread John Meacham
It seems to me that trac is mainly about the various 'fptools' projects and hawiki is about haskell topics in general. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.o

Re: [Haskell] (small) records proposal for Haskell '06

2006-01-04 Thread John Meacham
what type would f x = x { foo = "hello" } have if there were multiple types with 'foo' as a field name? John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Re: (small) records proposal for Haskell '06

2006-01-04 Thread John Meacham
at type does f have? f :: Foo -> Foo or f :: Bar -> Bar ? John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Boxing (Day) Question

2006-01-04 Thread John Meacham
lymorphic functions that are {-# INLINE #-}'d for which all polymorphic functions called by it are also inlined to be applied to unboxed arguments. a $ b = a b id x = x f . g = \x -> f (g x) being particularly useful instances of this John --

Re: [Haskell] A collection of related proposals regarding monads

2006-01-05 Thread John Meacham
independent of anything else, giving up error messages on pattern match failures in do notation is not acceptable. so, if the split were to happen, having two methods in MonadZero, one which takes a string argument, would be needed. John -- John Meacham - ⑆repetae.net⑆john

Re: [Haskell] Re: haskell.org Public Domain

2006-01-10 Thread John Meacham
lso get around any issues with 'public domain' not being a well defined term in some places and more clearly expresses the intent. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] IO == ST RealWorld

2006-01-29 Thread John Meacham
: > data World__ > > data IOResult a = FailIO World__ IOError | JustIO World__ a > newtype IO a = IO (World__ -> IOResult a) I belive other implementations have used continuations for IO as well. John -- John Meacham - ⑆repetae.net⑆john⑈ ___

Re: [Haskell] System.FilePath survey

2006-02-03 Thread John Meacham
27;s, so is > entirely portable between Unix/Windows - important if you want to be > able to create a binary that runs anywhere. also if you want to manipulate windows paths from unix and vice versa. any standard library should support that sort of thing. John -- John

Re: [Haskell] Re: System.FilePath survey

2006-02-06 Thread John Meacham
we could experiment with more advanced representations without breaking anyones code. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] Question for the haskell implementors: Arrays, unsafePerformIO, runST

2006-02-15 Thread John Meacham
> newAT__ :: Int -> AT a -> Array__ a > newAT__ n (AT a1) = a1 (prim_newAT__ (prim_newWorld__ a1) n) so the initial call to newAT__ now depends on the array transformer and can't be floated out as a CAF. I have reduced several magic primitives to just one, the world cre

Re: [Haskell] Long live Edison

2006-02-20 Thread John Meacham
ls more appropriate to me, there isn't really an 'mplus' you are going to use so making it the mzero just doesn't feel right. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Long live Edison

2006-02-20 Thread John Meacham
dditive operator, there is no need for another concept of zero and it seems to me that is the real issue. mzero can simply be defined as 'fail "mzero"'. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Long live Edison

2006-02-20 Thread John Meacham
On Mon, Feb 20, 2006 at 05:10:02PM -0800, Iavor Diatchki wrote: > On 2/20/06, John Meacham <[EMAIL PROTECTED]> wrote: > > I think the problem is that 'mzero' exists, the correct solution seems > > to be to get rid of the 'mzero' method of MonadPlus. Sinc

Re: [Haskell] Re: Question for the haskell implementors: Arrays, unsafePerformIO, runST

2006-02-20 Thread John Meacham
gmas have been proposed for in the past. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Re: Question for the haskell implementors: Arrays, unsafePerformIO, runST

2006-02-21 Thread John Meacham
On Tue, Feb 21, 2006 at 10:15:59AM +, Malcolm Wallace wrote: > John Meacham <[EMAIL PROTECTED]> wrote: > > > I generalized this primitive to > > > > drop__ :: a -> b -> b > > Also known in the Prelude as "const"... well, 'flip co

Re: [Haskell] Re: IO == ST RealWorld

2006-02-21 Thread John Meacham
e c-- style continuations to grin which should obviate the need for setjmp and longjmp which currently cannot be optimized through all that well. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] Re: Question for the haskell implementors: Arrays, unsafePerformIO, runST

2006-02-21 Thread John Meacham
nd of a name in jhc are equivalent in intent to # at the end in ghc, it just means "this might be special in some way" but if we were to have a common name, it should be something more descriptive. perhaps `dependingOn` ? > dependingOn :: a -> b -> a > dependingOn = flip

<    1   2   3   >