Re: Template Haskell question

2003-06-27 Thread Ian Lynagh
On Fri, Jun 27, 2003 at 03:57:19PM -0700, Ashley Yakeley wrote: > > aninstance :: TypQ -> Q [Dec]; > aninstance t = [d| > > instance HasZero $t where -- error here > { > zero = 0; > }; > > |]; You can only splice in expressions and decla

Arrow Classes

2003-06-27 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Wolfgang Jeltsch <[EMAIL PROTECTED]> wrote: > This brings me to another point. One year ago we had a discussion on The > Haskell Mailing List concerning arrows. (The subject of the mails was just > "arrows".) The point was that it seemed strange to me that first

Template Haskell question

2003-06-27 Thread Ashley Yakeley
Can anyone tell me what's wrong with this? -- ghc -fglasgow-exts -c TH.hs module TH where { import Language.Haskell.THSyntax; class HasZero a where { zero :: a; }; aninstance :: TypQ -> Q [Dec]; aninstance t = [d| instance HasZero $t w

Re: Simple monads

2003-06-27 Thread Graham Klyne
At a casual glance, your Labeller looks to me like a state transformer monad. I've found that the State transformer monad in the hierarchical libraries can be useful for this kind of thing; the following example is part of a larger program, so it can't be run in isolation, but I hope it shows so

Re: haskell array access

2003-06-27 Thread David Roundy
On Fri, Jun 27, 2003 at 12:10:55PM -0500, Shawn P. Garbett wrote: > - -- > New Haskell version with Unboxed Array > Note:it was a simple change of import and type > - - > import Data.Array.Unboxed > > a :: UArray Int Int >

RE: haskell array access

2003-06-27 Thread Hal Daume
> At best case for Haskell, 15.5 times slower. The thing about > bounds checking, > in Haskell it's always there. In C, you might have it, you > might not there is > no certainty by the language, only by design and > implementation. So with C, > one is free to live dangerously. If you're usi

Re: Simple monads

2003-06-27 Thread Wolfgang Jeltsch
On Thursday, 2003-06-26, 23:57, CEST, Derek Elkins wrote: > [...] > > not deeply understanding the use of Haskell extensions in the State > > source, > > I'm assuming Control.Monad.State's source in which case -no- extensions are > used for -State- (well, at least I don't see any quickly glancing)

Re: haskell array access

2003-06-27 Thread Shawn P. Garbett
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 On Thursday 26 June 2003 05:46 pm, Lex Stein wrote: > Great, thanks. Those suggestions narrow the gap from GHC -O being 330x > slower than GCC -O3 to it being 20x slower. Here are the new results: > > gcc -O3 0.54s > ocamlopt 1.11s > ghc -O

Re: Simple monads

2003-06-27 Thread Wolfgang Jeltsch
On Friday, 2003-06-27, 12:55, CEST, Christian Maeder wrote: > [...] > The portable parts of Control.Monad.State (that are sufficient for most > cases) should be in an extra module (maybe called Control.Monad.StateTypes). > In addition further non-overloaded names for put, get, gets and modify woul

RE: Help with ghci and Yet Another Haskell Tutorial

2003-06-27 Thread Hal Daume
toUpper is in the Char (or Data.Char) library. You can do: Prelude> :m Data.Char Data.Char> map toUpper "hello world" or specify it completely. Prelude> map Data.Char.toUpper "hello world" I'll fix this reference in YAHT. I believe that Hugs automatically exports toUpper, which is why it was

Help with ghci and Yet Another Haskell Tutorial

2003-06-27 Thread Mark Espinoza
Greetings, I am going through the Tutorial using ghc on a redhat 8.0 system. Everything works fine untill I get to the map function: Prelude>  map toUpper "hello world" :1: Variable not in scope: `toUpper' Prelude> Can anyone tel me what is or might be going on? Thanks. Sincerely, Mark Get

ELearnChina Conference 2003 - Only 4 Weeks To Go!

2003-06-27 Thread Edwin Jones
Hey its me again! Ok, there are still a few places left at the best Elearning Event of the year. Please contact me directly for final discounted prices [yes, even lower now] Yours, Edwin Jones www.chinaconferences.net Sales China Conferences Tel +44 131 440 9881 Fax +44 131 440 9882 [EMAIL PROT

Re: Simple monads

2003-06-27 Thread Christian Maeder
The previous "newtype Labeller a = Labeller (Int -> (Int, a))" (the result tuple is reversed within Control.Monad.State) would simply become (untested): newtype Labeller a = State Int a newLabel = do { n <- get; put (n + 1); return (Label n) } runLabeller l = execState l minBound it must be "e

Re: Simple monads

2003-06-27 Thread Christian Maeder
not deeply understanding the use of Haskell extensions in the State source, I'm assuming Control.Monad.State's source in which case -no- extensions are used for -State- (well, at least I don't see any quickly glancing). Extensions are used for the -MonadState class-. The portable parts of Con

Re: haskell array access

2003-06-27 Thread Derek Elkins
On Fri, 27 Jun 2003 09:36:36 +0100 "Simon Peyton-Jones" <[EMAIL PROTECTED]> wrote: > Several comments > > 1. In Haskell "mod" is a lot more expensive than "rem", because it > involves careful jiggery pokery with the sign of the result. That's > why your boxed version was slower (nothing to do

RE: haskell array access

2003-06-27 Thread Simon Peyton-Jones
Several comments 1. In Haskell "mod" is a lot more expensive than "rem", because it involves careful jiggery pokery with the sign of the result. That's why your boxed version was slower (nothing to do with boxing). 2. GHC does indeed optimise away the array access if you aren't careful, and d