[Haskell-cafe] type trickery

2007-12-20 Thread Adrian Neumann
Hello haskell-cafe! After making data Number = Zero | Succ Number an instance of Integral, I wondered how I could do the same with galois fields. So starting with Z mod p, I figured I'd need something like this data GF = GF Integer Integer so that each element of the finite field would

Re: [Haskell-cafe] type trickery

2007-12-20 Thread Luke Palmer
On Dec 20, 2007 9:34 AM, Adrian Neumann [EMAIL PROTECTED] wrote: Hello haskell-cafe! After making data Number = Zero | Succ Number an instance of Integral, I wondered how I could do the same with galois fields. So starting with Z mod p, I figured I'd need something like this data GF = GF

[Haskell-cafe] Re: MonadFix

2007-12-20 Thread apfelmus
Joost Behrends wrote: since about three weeks i am learning Haskell now. One of my first exercises is to decompose an Integer into its primefactors. How about separating the candidate prime numbers from the recursion factorize :: Integer - [Integer] factorize = f primes' where

[Haskell-cafe] Class deriving in GHC 6.8

2007-12-20 Thread Emil Axelsson
Hello all! How come in GHC 6.6 I could to write {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-} data Foo = Foo deriving Show data Bar c = Bar (c Foo) deriving Show but in GHC 6.8.2 I get the error No instance for (Show (c Foo)) arising from the

[Haskell-cafe] Haskell performance

2007-12-20 Thread Simon Peyton-Jones
Don, and others, This thread triggered something I've had at the back of my mind for some time. The traffic on Haskell Cafe suggests that there is a lot of interest in the performance of Haskell programs. However, at the moment we don't have any good *performance* regression tests for GHC. We

[Haskell-cafe] Dynamic typing of polymorphic functions

2007-12-20 Thread oleg
Alfonso Acosta wrote: mapSY :: (Typeable a, Typeable b) = (a - b) - Signal a - Signal b mapSY f (Signal primSig) = Signal (PrimSignal (MapSY (toDyn f) primSig)) The following process would be really useful but its compilation obviously fails: mapSnd :: Signal (a, a) - Signal a mapSnd =

Re: [Haskell-cafe] Class deriving in GHC 6.8

2007-12-20 Thread Emil Axelsson
After looking more closely at user's manual, I just found that the following works: {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-} data Foo = Foo deriving Show data Bar c = Bar (c Foo) deriving instance Show (c Foo) = Show (Bar c) / Emil On 2007-12-20

Re: [Haskell-cafe] Haskell performance

2007-12-20 Thread Lutz Donnerhacke
* Simon Peyton-Jones wrote: Does anyone feel like doing this? It'd be a great service. No need to know anything much about GHC. I'd like to do that. For a lecture I'm already generated performance tests for various sorting algorithms. It's designed about a function performance :: Size - IO

[Haskell-cafe] Re: type trickery

2007-12-20 Thread oleg
Adrian Neumann wrote: I figured I'd need something like this data GF = GF Integer Integer so that each element of the finite field would remember p. However I can't think of a way to use the typesystem to ensure that p is always the same. You might like: Vectro: Haskell library

[Haskell-cafe] [RFC] Preliminary benchmark graphs

2007-12-20 Thread Peter Lund
I added Don's three benchmarks and redid all my benchmarks with: ghc 6.6.1 ghc 6.8.2 ghc 6.8.2 + bytestring 0.9.0.2 ghc 6.9.20071119 ghc 6.9.20071119 + bytestring 0.9.0.2 ghc head-as-of-yesterday-around-noon ghc head-as-of-yesterday-around-noon + bytestring 0.9.0.2 I tried to get

Re: [Haskell-cafe] Haskell performance

2007-12-20 Thread Malcolm Wallace
Simon Peyton-Jones [EMAIL PROTECTED] wrote: What would be v helpful would be a regression suite aimed at performance, that benchmarked GHC (and perhaps other Haskell compilers) against a set of programs, regularly, and published the results on a web page, highlighting regressions. Something

[Haskell-cafe] Re: Haskell performance

2007-12-20 Thread Peter Lund
On Thu, 2007-12-20 at 10:37 +, Simon Peyton-Jones wrote: Don, and others, This thread triggered something I've had at the back of my mind for some time. The traffic on Haskell Cafe suggests that there is a lot of interest in the performance of Haskell programs. However, at the moment

Re: [Haskell-cafe] [HXT] Simple question

2007-12-20 Thread Uwe Schmidt
Hi Fernand, Everything works fine except for the fact that all the nodes « this /this » (that is, a space (an XML text node whose contents are a single space character) within a this element node) get transformed to a « this/ » element I can't really reproduce this: A simple ghci session

Re: [Haskell-cafe] [HXT] Simple question

2007-12-20 Thread Miguel Mitrofanov
I can't really reproduce this: A simple ghci session gives the following: --- [EMAIL PROTECTED]:~/haskell/hxt/curr/examples/arrows/HelloWorld ghci HelloWorld.hs GHCi, version 6.8.1: http://www.haskell.org/ghc/ :? for help Loading package base ... linking

Re: [Haskell-cafe] [HXT] Simple question

2007-12-20 Thread Uwe Schmidt
Hi Miguel, Hmmm, with 'readString ... this /this' everything works fine, but with 'readString ... itemsthis /this/items' it doesn't. Seems to be a bug in HXT. I don't see the bug: -- *Main runX $ ( readString [(a_validate,v_0)] itemsthis /this/items

Re: [Haskell-cafe] Haskell performance

2007-12-20 Thread Lutz Donnerhacke
* Malcolm Wallace wrote: Something along these lines already exists - the nobench suite. Ok, your turn. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Knowledge

2007-12-20 Thread Tillmann Rendel
jlw501 wrote: I'm new to functional programming and Haskell and I love its expressive ability! I've been trying to formalize the following function for time. Given people and a piece of information, can all people know the same thing? Anyway, this is just a bit of fun... but can anyone help me

Re: [Haskell-cafe] [HXT] Simple question

2007-12-20 Thread Fernand
Prelude Text.XML.HXT.Arrow runX $ ( readString [(a_validate,v_0)] xy /y/x setTraceLevel 4 traceDoc doc after reading s etTraceLevel 0 writeDocumentToString [(a_indent, v_1)]) -- (1) doc after reading x y/ /x content of: xy /y/x = ---XTag / | source=\xy

[Haskell-cafe] Re: #haskell works

2007-12-20 Thread Simon Marlow
Tim Chevalier wrote: On 12/14/07, Dan Piponi [EMAIL PROTECTED] wrote: There have been some great improvements in array handling recently. I decided to have a look at the assembly language generated by some simple array manipulation code and understand why C is at least twice as fast as ghc

[Haskell-cafe] Re: Haskell performance

2007-12-20 Thread Simon Marlow
Malcolm Wallace wrote: Simon Peyton-Jones [EMAIL PROTECTED] wrote: What would be v helpful would be a regression suite aimed at performance, that benchmarked GHC (and perhaps other Haskell compilers) against a set of programs, regularly, and published the results on a web page, highlighting

[Haskell-cafe] Re: Haskell performance

2007-12-20 Thread Simon Marlow
Simon Marlow wrote: Nobench does already collect code size, but does not yet display it in the results table. I specifically want to collect compile time as well. Not sure what the best way to measure allocation and peak memory use are? With GHC you need to use +RTS -s and then slurp in the

[Haskell-cafe] Storable types

2007-12-20 Thread Clerton Filho
Hi, I'm newbie in Haskell, and I have some doubts... In this programming language, do we have storable values? Case affirmative, what are the storable types in Haskell, and how can I implement then... thanks! -- Clerton Ribeiro de Araujo Filho Graduando em Ciência da Computação Integrante do

Re: [Haskell-cafe] Storable types

2007-12-20 Thread Alex Sandro Queiroz e Silva
Hallo fellow Brazilian, Clerton Filho escreveu: Hi, I'm newbie in Haskell, and I have some doubts... In this programming language, do we have storable values? Case affirmative, what are the storable types in Haskell, and how can I implement then... What exactly is a storable type?

Re: [Haskell-cafe] Storable types

2007-12-20 Thread Henning Thielemann
On Thu, 20 Dec 2007, Alex Sandro Queiroz e Silva wrote: Hallo fellow Brazilian, Clerton Filho escreveu: Hi, I'm newbie in Haskell, and I have some doubts... In this programming language, do we have storable values? Case affirmative, what are the storable types in Haskell, and how

Re: [Haskell-cafe] Storable types

2007-12-20 Thread Jules Bean
Clerton Filho wrote: Hi, I'm newbie in Haskell, and I have some doubts... In this programming language, do we have storable values? Case affirmative, what are the storable types in Haskell, and how can I implement then... Not entirely sure what you mean. There is a haskell typeclass called

[Haskell-cafe] Re: #haskell works

2007-12-20 Thread Tim Chevalier
On 12/20/07, Simon Marlow [EMAIL PROTECTED] wrote: That's not entirely true - there is a fairly decent linear-scan register allocator in GHC http://darcs.haskell.org/ghc/compiler/nativeGen/RegAllocLinear.hs the main bottleneck is not the quality of the register allocation (at least, not

Re: [Haskell-cafe] [HXT] Simple question

2007-12-20 Thread Uwe Schmidt
Hi Miguel, Try xy /y/x and a_indent writing option. yes, with the indent option set, whitespace becomes insignificant and will change during formating, and so the contents of the inner element reduces to empty Turn of the indentation and you get the result you want. Cheers, Uwe -- Web:

[Haskell-cafe] Class/Instance : what am I doing wrong in this example ?

2007-12-20 Thread david48
I'm really inexperienced at this : --- {-# OPTIONS_GHC -fglasgow-exts -funbox-strict-fields -fallow-undecidable-instances -O2 #-} class Gadget g where fInit :: g - a - g data FString = FString !Int !String deriving Show instance Gadget FString where fInit (FString n _) s = FString

Re: [Haskell-cafe] Creating a type for a subset of the integers

2007-12-20 Thread Brad Larsen
On Wed, 19 Dec 2007 02:00:53 -0500, Jules Bean [EMAIL PROTECTED] wrote: Brad Larsen wrote: Hi there list, How would one go about creating a new type for a subset of the integers, for (contrived) example just the even integers? I was thinking of making a new type newtype EvenInt =

Re: [Haskell-cafe] Class/Instance : what am I doing wrong in this example ?

2007-12-20 Thread Claude Heiland-Allen
david48 wrote: | I'm really inexperienced at this : class Gadget g where fInit :: g - a - g data FString = FString !Int !String deriving Show instance Gadget FString where fInit (FString n _) s = FString n (take n s) The types of: fInit :: g - a - g and: take :: Int - [a] - [a]

Re: [Haskell-cafe] Creating a type for a subset of the integers

2007-12-20 Thread Jules Bean
Brad Larsen wrote: On Wed, 19 Dec 2007 02:00:53 -0500, Jules Bean [EMAIL PROTECTED] wrote: Brad Larsen wrote: Hi there list, How would one go about creating a new type for a subset of the integers, for (contrived) example just the even integers? I was thinking of making a new type

Re: [Haskell-cafe] Class/Instance : what am I doing wrong in this example ?

2007-12-20 Thread david48
On Dec 20, 2007 5:03 PM, Claude Heiland-Allen [EMAIL PROTECTED] wrote: You're trying to apply 'take n' to a value of type 'a' ('take n' requires [a]), moreover putting the value of 'take n s' into the FString further constrains its type to be [Char] == String. First of all, thanks a lot for

Re: [Haskell-cafe] Class/Instance : what am I doing wrong in this example ?

2007-12-20 Thread Tillmann Rendel
david48 wrote: class Gadget g where fInit :: g - a - g data FString = FString !Int !String deriving Show instance Gadget FString where at this point fInit has this type: FString - a - FString fInit (FString n _) s = FString n (take n s) but your implementation has this type

Re: [Haskell-cafe] Class/Instance : what am I doing wrong in this example ?

2007-12-20 Thread Jules Bean
Tillmann Rendel wrote: david48 wrote: class Gadget g where fInit :: g - a - g Tillman's two suggestions (below) are probably your answer. Just to say what everyone else has said in a bunch of different ways: your class says that for ANY Gadget, fInit will work with ANY OTHER type a.

Re: [Haskell-cafe] Class/Instance : what am I doing wrong in this example ?

2007-12-20 Thread david48
On Dec 20, 2007 5:26 PM, Tillmann Rendel [EMAIL PROTECTED] wrote: at this point fInit has this type: FString - a - FString fInit (FString n _) s = FString n (take n s) but your implementation has this type FString - String - FString These types are incompatible, your fInit

Re: [Haskell-cafe] Class/Instance : what am I doing wrong in this example ?

2007-12-20 Thread david48
On Dec 20, 2007 5:44 PM, david48 [EMAIL PROTECTED] wrote: fString :: Int - FString fString n = FString n Oo do I feel dumb for writing this ! Problem solved :) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Class/Instance : what am I doing wrong in this example ?

2007-12-20 Thread david48
On Dec 20, 2007 5:36 PM, Jules Bean [EMAIL PROTECTED] wrote: 2. Maybe you want lots of possible different as for each g. Then you make a a parameter of the class too. 3. Maybe you want just one particular a for each g. I.e. g determines a. Then you can proceed as for (2), but add the

Re: [Haskell-cafe] [RFC] Preliminary benchmark graphs

2007-12-20 Thread Don Stewart
firefly: I added Don's three benchmarks and redid all my benchmarks with: ghc 6.6.1 ghc 6.8.2 ghc 6.8.2 + bytestring 0.9.0.2 ghc 6.9.20071119 ghc 6.9.20071119 + bytestring 0.9.0.2 ghc head-as-of-yesterday-around-noon ghc head-as-of-yesterday-around-noon + bytestring 0.9.0.2

[Haskell-cafe] Re: Haskell performance

2007-12-20 Thread Don Stewart
simonpj: Don, and others, This thread triggered something I've had at the back of my mind for some time. The traffic on Haskell Cafe suggests that there is a lot of interest in the performance of Haskell programs. However, at the moment we don't have any good *performance* regression

Re: [Haskell-cafe] Haskell performance

2007-12-20 Thread Don Stewart
Malcolm.Wallace: Simon Peyton-Jones [EMAIL PROTECTED] wrote: What would be v helpful would be a regression suite aimed at performance, that benchmarked GHC (and perhaps other Haskell compilers) against a set of programs, regularly, and published the results on a web page, highlighting

Re: [Haskell-cafe] Re: Haskell performance

2007-12-20 Thread Don Stewart
simonmarhaskell: Malcolm Wallace wrote: Simon Peyton-Jones [EMAIL PROTECTED] wrote: What would be v helpful would be a regression suite aimed at performance, that benchmarked GHC (and perhaps other Haskell compilers) against a set of programs, regularly, and published the results on a web

Re: [Haskell-cafe] Re: Haskell performance

2007-12-20 Thread Jon Harrop
On Thursday 20 December 2007 19:02, Don Stewart wrote: Ok, so I should revive nobench then, I suspect. http://www.cse.unsw.edu.au/~dons/nobench/x86_64/results.html that kind of thing? Many of those benchmarks look good. However, I suggest avoiding trivially reducible problems like

Re: [Haskell-cafe] Re: Haskell performance

2007-12-20 Thread Don Stewart
jon: On Thursday 20 December 2007 19:02, Don Stewart wrote: Ok, so I should revive nobench then, I suspect. http://www.cse.unsw.edu.au/~dons/nobench/x86_64/results.html that kind of thing? Many of those benchmarks look good. However, I suggest avoiding trivially reducible

Re: [Haskell-cafe] Re: Haskell performance

2007-12-20 Thread Thomas DuBuisson
However, I suggest avoiding trivially reducible problems like computing constants (e, pi, primes, fib) and redundant operations (binary trees). Make sure programs accept a non-trivial input (even if it is just an int over a wide range). Avoid unnecessary repeats (e.g. atom.hs). This will

[Haskell-cafe] instance Monad Either?

2007-12-20 Thread Eric
According to this http://www.randomhacks.net/articles/2007/03/10/haskell-8-ways-to-report-errors Either is an instance of class Monad, but when I try to use the do notation I get a compiler error. What's going on? E. ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] instance Monad Either?

2007-12-20 Thread Tom Phoenix
On 12/20/07, Eric [EMAIL PROTECTED] wrote: According to this http://www.randomhacks.net/articles/2007/03/10/haskell-8-ways-to-report-errors Either is an instance of class Monad, but when I try to use the do notation I get a compiler error. What's going on? Near the bottom of that page is a

Re: [Haskell-cafe] instance Monad Either?

2007-12-20 Thread Eric
Tom Phoenix wrote: On 12/20/07, Eric [EMAIL PROTECTED] wrote: According to this http://www.randomhacks.net/articles/2007/03/10/haskell-8-ways-to-report-errors Either is an instance of class Monad, but when I try to use the do notation I get a compiler error. What's going on? Near the

[Haskell-cafe] Is there some place where I can find the hs-curses doc ?

2007-12-20 Thread david48
It seems I can't find it. David. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Is there some place where I can find the hs-curses doc ?

2007-12-20 Thread Don Stewart
dav.vire+haskell: It seems I can't find it. hscurses, Stefan Wehr's package of the curses binding is pre-hackage and pre-cabal, so you can only get the source: http://www.informatik.uni-freiburg.de/~wehr/haskell/ there's another curses binding in hmp3,

Re: [Haskell-cafe] instance Monad Either?

2007-12-20 Thread Tillmann Rendel
Eric wrote: According to this http://www.randomhacks.net/articles/2007/03/10/haskell-8-ways-to-report-errors Either is an instance of class Monad, but when I try to use the do notation I get a compiler error. What's going on? Try to import Control.Monad.Error to get a Monad instance for

Re: [Haskell-cafe] Is there some place where I can find the hs-curses doc ?

2007-12-20 Thread david48
On Dec 20, 2007 11:24 PM, Don Stewart [EMAIL PROTECTED] wrote: there's another curses binding in hmp3, http://www.cse.unsw.edu.au/~dons/code/hmp3/Curses.hsc that i keep meaning to package up, but never do. Thanks ! There's quite a lot of stuff I don't understand in Curses.hsc ( the use

[Haskell-cafe] Re: MonadFix

2007-12-20 Thread Joost Behrends
Albert Y. C. Lai trebla at vex.net writes: Theoretically the recursions in oddFactors k n | otherwise = oddFactors (k+2) n and (*) divisions y |divisor y = bound y = divisions (divstep y) do not cost stack space. They are tail recursions too! In general similar tail

[Haskell-cafe] Re: MonadFix

2007-12-20 Thread Joost Behrends
apfelmus apfelmus at quantentunnel.de writes: How about separating the candidate prime numbers from the recursion factorize :: Integer - [Integer] factorize = f primes' where primes' = 2:[3,5..] f (p:ps) n | r == 0= p : f (p:ps) q | p*p n

Re: [Haskell-cafe] Re: MonadFix

2007-12-20 Thread Ryan Ingram
On 12/20/07, Joost Behrends [EMAIL PROTECTED] wrote: makes a DESTRUCTIVE UPDATE of the DivIters (by put) and this kind of recursion seems not to remember itself (as i have understood, that is achieved by tail recursion). I just didn't like making DivIters to States. It's kind of lying code.

[Haskell-cafe] upgrading regex in GHC 6.8.2

2007-12-20 Thread Michael Mounteney
Hello, I have an application that uses/used Text.Regex and have just updated GHC from 6.6.1 to 6.8.2 and it seems that Text.Regex is gone, so I'm trying to install the replacement from Hackage. First of all, the procedure is quite tedious as one has to install the hierarchy of dependencies

Re: [Haskell-cafe] Optimizing cellular automata the beauty of unlifted types

2007-12-20 Thread Sterling Clover
I'm curious how much of the unboxing helped performance and how much didn't. In my experience playing with this stuff, GHC's strictness analyzer has consistently been really excellent, given the right hints. Unboxed tuples are generally a win, but GHC was often smarter at unboxing ints

Re: [Haskell-cafe] upgrading regex in GHC 6.8.2

2007-12-20 Thread Duncan Coutts
On Fri, 2007-12-21 at 13:58 +1030, Michael Mounteney wrote: Hello, I have an application that uses/used Text.Regex and have just updated GHC from 6.6.1 to 6.8.2 and it seems that Text.Regex is gone, so I'm trying to install the replacement from Hackage. First of all, the procedure is

[Haskell-cafe] Smart Constructor Puzzle

2007-12-20 Thread Ronald Guida
I'm playing around with smart constructors, and I have encountered a weird puzzle. My goal is to do vector arithmetic. I'm using smart constructors so that I can store a vector as a list and use the type system to staticly enforce the length of a vector. So my first step is to define Peano

Re: [Haskell-cafe] Smart Constructor Puzzle

2007-12-20 Thread Luke Palmer
On Dec 21, 2007 4:39 AM, Ronald Guida [EMAIL PROTECTED] wrote: Finally, I tried to define vecLength, but I am getting an error. vecLength :: (Peano s) = Vec s t - Int vecLength _ = pToInt (pGetValue :: s) The s in (pGetValue :: s) is different from the s in (Peano s). Use the scoped type

Re: [Haskell-cafe] Smart Constructor Puzzle

2007-12-20 Thread Twan van Laarhoven
Ronald Guida wrote: I'm playing around with smart constructors, and I have encountered a weird puzzle. My goal is to do vector arithmetic. I'm using smart constructors so that I can store a vector as a list and use the type system to staticly enforce the length of a vector. So my first step

Re: [Haskell-cafe] Smart Constructor Puzzle

2007-12-20 Thread Stefan O'Rear
On Thu, Dec 20, 2007 at 11:39:42PM -0500, Ronald Guida wrote: data PZero = PZero deriving (Show) data PSucc a = PSucc a deriving (Show) type P1 = PSucc PZero type P2 = PSucc P1 type P3 = PSucc P2 -- etc ... Now here's the puzzle. I want to create a function vecLength that

Re: [Haskell-cafe] upgrading regex in GHC 6.8.2

2007-12-20 Thread Alex Jacobson
Searchpath already does recursive module chasing accross the internet. If your module is available at a url in an unpacked module hierarchy or in a tgz file or if it is exposed in a darcs/svn/cvs etc repo, searchpath can retrieve it and put it on your local import path. The main limitations