Re: [Haskell-cafe] Re: Trouble with record syntax and classes

2007-02-26 Thread Steve Schafer
On Mon, 26 Feb 2007 23:41:14 -0600 (CST), you wrote: >Here's my second attempt at the code: >... You've left out a bunch of constructors, and there are various other errors here and there. I think this will do what you want: > data ISine = > Sine Integer Integer Integer [Char] | > MetaSine

Re: [Haskell-cafe] Re: AT solution: rebinding >>= for restricted monads

2007-02-26 Thread Manuel M T Chakravarty
Pepe Iborra: > David Roundy darcs.net> writes: > > My latest attemp (which won't compile with the HEAD ghc that I just > > compiled, > > probably because I haven't figured out the synatax for guards with indexed > > types is: > > > > class WitnessMonad m where > > type W m :: * -> * -> * > >

[Haskell-cafe] Re: Trouble with record syntax and classes

2007-02-26 Thread Thomas Nelson
Thank you all for your advice so far. I went back and tried to simplify my code, but I'm still stuck. The basic idea I want is something like an arbitrary tree structure, where MetaSines are the branches containing Sines, and Sines are the leaves containing strings. I want to recurse through

Re: [Haskell-cafe] Re: OO Design in Haskell Example (Draft)

2007-02-26 Thread Tim Docker
Steve Downey wrote: > interesting. it leads to something that feels much more like an object based, as opposed to a class based, system. > as far as haskell is concerned, everything has the same type, even though different instances have very different behavior. > > the question is, which play

[Haskell-cafe] Build failed - hidden package ?

2007-02-26 Thread Dunric
Hi. I've got stuck with the following compilation error I probably can't fully understand: -- Building library... ... Using package config file: /usr/local/lib/ghc-6.6/package.conf wired-in package base mapped to base-2.0 wired-i

Re: [Haskell-cafe] Splitting Hairs Over Terminology

2007-02-26 Thread Kirsten Chevalier
On 2/26/07, P. R. Stanley <[EMAIL PROTECTED]> wrote: Back to the comma, surely, syntax sugar fulfills the role of an operator, a function, or a sequence of low-level procedures, either in part or comprehensively. In C, for example, iteration could be implemented using the if construct with the dr

Re: [Haskell-cafe] Splitting Hairs Over Terminology

2007-02-26 Thread Brandon S. Allbery KF8NH
On Feb 26, 2007, at 22:17 , P. R. Stanley wrote: Prelude> 13:[1, 2] [13, 1, 2] which I don't believe has an address in the memory, correct? If I understand what you're getting at: internally it just allocates a new cons cell, stuffs 13 in the left side and a pointer to the existing list [

Re: [Haskell-cafe] Splitting Hairs Over Terminology

2007-02-26 Thread Kirsten Chevalier
On 2/26/07, Dan Weston <[EMAIL PROTECTED]> wrote: P. R. Stanley wrote: > In C, for example, iteration could be implemented using the if construct > with the dreaded goto command. So, strictly speaking, the while loop > could be classed as syntax sugar. Yet, the while loop is a > well-recognized

Re: [Haskell-cafe] Splitting Hairs Over Terminology

2007-02-26 Thread Dan Weston
P. R. Stanley wrote: You know, as soon as I posted the message I remembered the destructive assignment thingummy. the following is what I was talking about: Prelude> 13:[1, 2] [13, 1, 2] which I don't believe has an address in the memory, correct? No. It does have a well-defined address in me

Re: [Haskell-cafe] Safe lists with GADT's

2007-02-26 Thread Robin Green
On Mon, 26 Feb 2007 17:28:59 -0800 (PST) [EMAIL PROTECTED] wrote: > The problem with GADTs and other run-time based evidence is just > that: _run-time_ based evidence and pattern-matching. In a non-strict > system, checking that the evidence is really present is the problem on > and of itself. Th

[Haskell-cafe] Re: OO Design in Haskell Example (Draft)

2007-02-26 Thread Steve Downey
I just started reading "Haskell's overlooked object system". The survey of existing object encodings looks like a good place to start, although for several, where Either is used as a union type there are some rather obvious scaling problems. If I've underst

Re: [Haskell-cafe] Splitting Hairs Over Terminology

2007-02-26 Thread P. R. Stanley
I'm assuming that the ":" function takes two arguments and returns a newly constructed list which is assigned to the variable holding/ pointing to the old list. First part correct, second quite wrong --- Haskell doesn't have destructive assignment in the general case. There are special cases

Re: [Haskell-cafe] Splitting Hairs Over Terminology

2007-02-26 Thread Brandon S. Allbery KF8NH
On Feb 26, 2007, at 21:27 , P. R. Stanley wrote: Hi folks in C and C++ world the humble comma is an operator. Is this also the case in Haskell or, is it classed as a function? Neither; it's syntactic sugar. The formal tuple constructor is (, [,...]) a [b ...] (e.g. (,,) a b c), with (a, b

Re: [Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread ajb
G'day all. Oh, one more thing. Quoting Aaron McDaid <[EMAIL PROTECTED]>: > Somebody more knowledgeable can describe the etymology of the terms, [...] You can think of a type as a set of values. For example, Bool is the set { False, True }. A "class", then, is a set of types. The distinction

[Haskell-cafe] Splitting Hairs Over Terminology

2007-02-26 Thread P. R. Stanley
Hi folks in C and C++ world the humble comma is an operator. Is this also the case in Haskell or, is it classed as a function? In the wikibook they talk about consing new elements onto a list. Does this cons stand for anything meaningful in the English language? For example, is it short for con

Re: [Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread ajb
G'day all. Quoting Aaron McDaid <[EMAIL PROTECTED]>: > 'class' in Haskell doesn't mean the same as 'class' in C++ or Java. I > found it easier at first to thing of them as: >A Haskell 'class' is more like a Java interface. >Haskell types are more like what you might think of as 'class'es.

[Haskell-cafe] OO Design in Haskell Example (Draft)

2007-02-26 Thread oleg
Steve Downey wrote: > In the last OO design in Haskell thread (and probably in every one > preceeding it), it was suggested that having some examples might be a good > idea. > > Since most people with existing designs will have some familiarity with > Design Patterns, and those are typical buildin

[Haskell-cafe] Re: overlapping instances, selecting if type a does not belong to class?

2007-02-26 Thread Marc Weber
Wow. > That said, it is quite possible in Haskell to achieve genuine > class-based dispatch, with backtracking if necessary: > http://pobox.com/~oleg/ftp/Haskell/poly2.txt Thanks for digging this up. I'll have to reread it tomorrow. I wasn't able to find the definition of AllOf(But): quote

[Haskell-cafe] Safe lists with GADT's

2007-02-26 Thread oleg
Stefan O'Rear wrote: > Personally I like the GADT approach best since it is very flexible and > convienient. I have never used a purpose-build computer proof system, > but (modulo _|_) it took me less than 10 minutes to answer > LoganCapaldo (on #haskell)'s challenge to proof that + was commutati

RE: [Haskell-cafe] State of OOP in Haskell

2007-02-26 Thread Ralf Lammel
Lennart wrote: > OOHaskell is ingenious, but it's a terrible way to use Haskell. > It's very unidiomatic Haskell, and it makes you do things in the > same old OO way. It's probably obvious but let me say that ... OOHaskell is more of a proof of concept and a sandbox for OO language design. It is

[Haskell-cafe] overlapping instances, selecting if type a does not belong to class?

2007-02-26 Thread oleg
Marc Weber wrote: > class (HList c) => HListAppendArbitrary a b c | a b -> c where > hAppendArbitrary :: a -> b -> c > > -- instance HList + HList (1) > instance (HList a, HList b, HAppend a b c, HList c) > => HListAppendArbitrary a b c where > hAppendArbitrary a b = hAppend a b > >

[Haskell-cafe] overlapping instances, selecting if type a does not belong to class?

2007-02-26 Thread Marc Weber
I want to write a class introducing a function which should append a b resulting in a HList containing a and b (order doesn't matter) So I came up with: = code === class (HList c) => HListAppendArbitrary a b c | a b -> c where hAppend

Re: [Haskell-cafe] Hi can u explain me how drop works in Haskell

2007-02-26 Thread Steve Downey
ok maybe i should have read ahead. but still, i can see how to apply hunit, but not quickcheck. but quickcheck seems more powerful. On 2/26/07, Steve Downey <[EMAIL PROTECTED]> wrote: in addition, a good example of how to apply quickcheck would be really awesome. without using the standard drop

Re: [Haskell-cafe] Hi can u explain me how drop works in Haskell

2007-02-26 Thread Steve Downey
in addition, a good example of how to apply quickcheck would be really awesome. without using the standard drop On 2/26/07, Thomas Hartman <[EMAIL PROTECTED]> wrote: Here's my, probably very obvious, contribution. What I'd like feedback on is 1) code seem ok? (hope so!) 2) What do you think

[Haskell-cafe] Re: OO Design in Haskell Example (Draft)

2007-02-26 Thread Steve Downey
interesting. it leads to something that feels much more like an object based, as opposed to a class based, system. as far as haskell is concerned, everything has the same type, even though different instances have very different behavior. instance variables are captured by the closures that define

Re: [Haskell-cafe] Delaling with State StateT and IO in the same function

2007-02-26 Thread Alfonso Acosta
On 2/27/07, Kirsten Chevalier <[EMAIL PROTECTED]> wrote: So what if you changed your netlist function so that the type sig would be: netlist :: DT.Traversable f => (State s (S HDPrimSignal) -> State s v ) -> -- new (State s (Type,v) -> S v -> State s ()) -> -- define

Re: [Haskell-cafe] Delaling with State StateT and IO in the same function

2007-02-26 Thread Kirsten Chevalier
On 2/26/07, Alfonso Acosta <[EMAIL PROTECTED]> wrote: On 2/27/07, Kirsten Chevalier <[EMAIL PROTECTED]> wrote: > I may be missing something, but why are you using both State and > StateT? Maybe I don't understand your code, but it seems like you > could be using StateT everywhere you're currentl

Re: [Haskell-cafe] FFI basics

2007-02-26 Thread Stefan O'Rear
On Mon, Feb 26, 2007 at 01:02:57PM -0800, Evan Laforge wrote: > Question #1 is compiling FFI using modules. I'd like to use ghc > --make for the speed and convenience, but obviously it doesn't know > how to compile the C. So my hybrid approach has been to write a > makefile for the C, and then ma

Re: [Haskell-cafe] Delaling with State StateT and IO in the same function

2007-02-26 Thread Alfonso Acosta
On 2/27/07, Kirsten Chevalier <[EMAIL PROTECTED]> wrote: I may be missing something, but why are you using both State and StateT? Maybe I don't understand your code, but it seems like you could be using StateT everywhere you're currently using State. Well, as far as I know using "StateT s IO a

Re: [Haskell-cafe] Delaling with State StateT and IO in the same function

2007-02-26 Thread Kirsten Chevalier
On 2/26/07, Alfonso Acosta <[EMAIL PROTECTED]> wrote: The returned type is a StateT and the only way in which I succesfully managed to internally work with both State and StateT is converting from the former to the later one using this function (not elegant at all) I may be missing something,

Re: [Haskell-cafe] Safe lists with GADT's

2007-02-26 Thread Stefan O'Rear
On Mon, Feb 26, 2007 at 04:35:06PM +0100, Pepe Iborra wrote: > I am really curious about this style of programming, and find myself > playing with it from time to time. > The example so far is very nice, but the funniest part is missing. > That is, defining appendL. > > > appendL :: List a t1

[Haskell-cafe] Delaling with State StateT and IO in the same function

2007-02-26 Thread Alfonso Acosta
Hello, I know StateT is exactly aimed at dealing with a state and an inner monad but I have an example in which I have to mix State and IO and in which I didn't get to an elegant solution using StateT. I have a higher order function which gets some State processing functions as input, makes som

Re: [Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread Marc Weber
On Mon, Feb 26, 2007 at 01:22:57PM -0600, Thomas Nelson wrote: > I'm brand new to haskell and I'm having trouble using classes. The basic > idea is I want two classes, Sine and MetaSine, that are both instances of > ISine. This way I can use the act method and recurse through the metasines > an

Re: [Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread Tillmann Rendel
Hello Thomas, Thomas Nelson schrieb: I'm brand new to haskell and I'm having trouble using classes. The basic idea is I want two classes, Sine and MetaSine, that are both instances of ISine. This way I can use the act method and recurse through the metasines and sines. That looks too much like

Re: [Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread Aaron McDaid
On 2/26/07, Thomas Nelson <[EMAIL PROTECTED]> wrote: I'm brand new to haskell and I'm having trouble using classes. The basic idea is I want two classes, Sine and MetaSine, that are both instances of ISine. 'class' in Haskell doesn't mean the same as 'class' in C++ or Java. I found it easier a

Re: [Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread Albert Y. C. Lai
All record fields are in the same namespace, and furthermore this is also the same namespace of functions and class methods. In other words you cannot have two record types containing the same field name, and you cannot have a record field and a function using the same name, and you cannot have

Re: [Haskell-cafe] FFI basics

2007-02-26 Thread Evan Laforge
... and now I have more questions. Maybe it would be better if I just asked them on the mailing list, and then incorporated the answers into the wiki myself. Question #1 is compiling FFI using modules. I'd like to use ghc --make for the speed and convenience, but obviously it doesn't know how t

[Haskell-cafe] Re: [Haskell] [Fwd: Re: Computer Language Shootout]

2007-02-26 Thread Kirsten Chevalier
[redirecting to haskell-cafe, since this is getting to be a long discussion] On 2/26/07, Andrzej Jaworski <[EMAIL PROTECTED]> wrote: The examples I pointed to seem to share strong and relatively consistent logic of a program. In case of large GA (e.g. Royal Road Problem) and IFP (e.g. ADATE) SML

[Haskell-cafe] Links in Haskell code in HaskellWiki

2007-02-26 Thread Henk-Jan van Tuyl
L.S., Links in the Haskell code in the wiki pages point to wrong labels; for example, if 'print' is used, it is linked to: http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:print the colon should be "%3A": http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.

[Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread Thomas Nelson
I'm brand new to haskell and I'm having trouble using classes. The basic idea is I want two classes, Sine and MetaSine, that are both instances of ISine. This way I can use the act method and recurse through the metasines and sines. Here's my code: module Main where class ISine a where

[Haskell-cafe] reed-solomon or other ECC codes

2007-02-26 Thread Bulat Ziganshin
Hello haskell-cafe, is there a haskell library for any ECC codes? -- Best regards, Bulat mailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] problems installing ghc 6.6 with extralibs (bad interface file)

2007-02-26 Thread Thomas Hartman
I installed ghc 6.6 from source ok. But then when I tried installing it with the "extralibs" to get all the functionality that had been unbundled in 6.6, I hit a glitch. Anyone ever seen anything like this? In case it matters, this is ssh-ed in to a virtualized user mode linux session.

Re: [Haskell-cafe] Did quickchekc get dropped from ghc from 6.4 to 6.6?

2007-02-26 Thread Brandon S. Allbery KF8NH
On Feb 26, 2007, at 10:30 , Thomas Hartman wrote: I seem to recall this came with ghc 6.4. After upgrading to ghc 6.6, however, I don't seem to have it anymore. As noted by others, in 6.6 it was unbundled. If you're using binary Linux packages, this unbundling is generally reflected in the

Re: [Haskell-cafe] Safe lists with GADT's

2007-02-26 Thread David Roundy
On Mon, Feb 26, 2007 at 04:35:06PM +0100, Pepe Iborra wrote: > First, via existentials: > > appendL1 :: List a t1 -> List a t2 -> exists t3. List a t3 It seems like this problem is begging for the new indexed types (for which I never remember the right syntax). type AddListTs :: * -> * -> * AddLi

Re: [Haskell-cafe] Did quickchekc get dropped from ghc from 6.4 to 6.6?

2007-02-26 Thread Björn Bringert
Thomas Hartman wrote: According to http://www.cs.chalmers.se/~rjmh/QuickCheck/ Quickcheck is distributed with ghc. I seem to recall this came with ghc 6.4. After upgrading to ghc 6.6, however, I don't seem to have it anymore. Do I need to install it from cabal? If so, I assume this would star

Re: [Haskell-cafe] Did quickchekc get dropped from ghc from 6.4 to 6.6?

2007-02-26 Thread Cale Gibbard
On 26/02/07, Thomas Hartman <[EMAIL PROTECTED]> wrote: According to http://www.cs.chalmers.se/~rjmh/QuickCheck/ Quickcheck is distributed with ghc. I seem to recall this came with ghc 6.4. After upgrading to ghc 6.6, however, I don't seem to have it anymore. Hmm, which release do you have?

Re: [Haskell-cafe] R wrapper in haskell

2007-02-26 Thread Henning Thielemann
On Sun, 25 Feb 2007, Peng Zhang wrote: > Hi folks, > > My primary language is R, which is an imperative functional language. I > start to learn haskell and try to use it instead when a project is > time-consuming and it takes months in R. I like the language very much > so far, but I do miss some

[Haskell-cafe] Re: AT solution: rebinding >>= for restricted monads

2007-02-26 Thread Pepe Iborra
David Roundy darcs.net> writes: > My latest attemp (which won't compile with the HEAD ghc that I just compiled, > probably because I haven't figured out the synatax for guards with indexed > types is: > > class WitnessMonad m where > type W m :: * -> * -> * > (>>=) :: (WitnessMonad m', Wi

Re: [Haskell-cafe] Safe lists with GADT's

2007-02-26 Thread Pepe Iborra
I am really curious about this style of programming, and find myself playing with it from time to time. The example so far is very nice, but the funniest part is missing. That is, defining appendL. > appendL :: List a t1 -> List a t2 -> List a t3 This says that the append of a list of length

[Haskell-cafe] Did quickchekc get dropped from ghc from 6.4 to 6.6?

2007-02-26 Thread Thomas Hartman
According to http://www.cs.chalmers.se/~rjmh/QuickCheck/ Quickcheck is distributed with ghc. I seem to recall this came with ghc 6.4. After upgrading to ghc 6.6, however, I don't seem to have it anymore. Do I need to install it from cabal? If so, I assume this would start by wgetting http://h

Re: [Haskell-cafe] Safe lists with GADT's

2007-02-26 Thread David Roundy
On Sun, Feb 25, 2007 at 10:40:13PM +, Neil Mitchell wrote: > >data ConsT a > >data NilT > > > >data List a t where > >Cons :: a -> List a b -> List a (ConsT b) > >Nil :: List a NilT ... > Defining safeMap was trivial, but one thing I couldn't figure out was > how to write something lik

Re: [Haskell-cafe] haskell-art mailing list

2007-02-26 Thread Ian Lynagh
On Sat, Feb 24, 2007 at 12:47:19PM +0100, Henk-Jan van Tuyl wrote: > > Is this something for the list at > http://haskell.org/mailman/listinfo That's generated by mailman, and as far as I know can't be easily altered. > (Maybe this page could be moved to haskellwiki?) Perhaps adding a list of

Re: [Haskell-cafe] How you can help improve Haskell implementations!

2007-02-26 Thread Donald Bruce Stewart
ndmitchell: > Hi > > >And also I guess the compilers will do more optimisations, etc. > >So this suggests an obvious extra feature for nobench which would be the > >ability to view a graph of each compiler's performance over a period of > >time, obviously this probably wouldn't be useful for at le

Re: [Haskell-cafe] How you can help improve Haskell implementations!

2007-02-26 Thread Neil Mitchell
Hi And also I guess the compilers will do more optimisations, etc. So this suggests an obvious extra feature for nobench which would be the ability to view a graph of each compiler's performance over a period of time, obviously this probably wouldn't be useful for at least a few months. We hop

Re: [Haskell-cafe] How you can help improve Haskell implementations!

2007-02-26 Thread Allan Clark
Donald Bruce Stewart wrote: Just a quick note to say that the Haskell implementation shootout is progressing, now supporting jhc, fixing a range of bugs, and providing more benchmark programs. Nice average numbers are also reported for the relative performance of each compiler or interpreter. On

[Haskell-cafe] How you can help improve Haskell implementations!

2007-02-26 Thread Donald Bruce Stewart
Just a quick note to say that the Haskell implementation shootout is progressing, now supporting jhc, fixing a range of bugs, and providing more benchmark programs. Nice average numbers are also reported for the relative performance of each compiler or interpreter. On x86: http://www.cse.unsw.

[Haskell-cafe] Re: OO Design in Haskell Example (Draft)

2007-02-26 Thread apfelmus
Tim Docker wrote: > Steve Downey wrote: > > So, I've been working on a Composite example. I've used > > existential types to have a generic proxy to the base > > type, rather than a simple algebraic type, since adding > > new leaves to the algebraic type means modifying the whole > > type, a

[Haskell-cafe] Re: Safe lists with GADT's

2007-02-26 Thread apfelmus
Stefan O'Rear wrote: >> How do I get my original function back which just turns a standard >> list to one of the funky lists, or is that just impossible with >> GADT's? Do I now have to "wrap" all the fuctions I use, i.e. pass >> safeMap in CPS? > > AFAIK you can't. Fortunately the CPS transform c

Re[2]: [Haskell-cafe] OO Design in Haskell Example (Draft)

2007-02-26 Thread Bulat Ziganshin
Hello Tim, Monday, February 26, 2007, 2:26:44 AM, you wrote: > Rather than using existential types, a simple record of > functions can be often be useful. ie: > data Component = Component { > draw :: String > add :: Component -> Component > } Steve, you can look at the pages http://has

Re: [Haskell-cafe] Hi can u explain me how drop works in Haskell

2007-02-26 Thread Thomas Hartman
I'd heard of quick check, but haven't got my head around it. This seems like a good place to start. I understand you have to build an invariant and then you can automate against it, eg "reverse of reverse is your original string" prop_RevRev xs = reverse (reverse xs) == xs where types = xs::[Int

Re: [Haskell-cafe] A "real" Haskell Cookbook

2007-02-26 Thread Martin DeMello
On 2/26/07, Chris Eidhof <[EMAIL PROTECTED]> wrote: Hey everyone, we added some examples to this page. There are some topics that don't have any examples, notably: # 11 Network Programming # 12 XML * 12.1 Parsing XML # 13 Databases * 13.1 MySQL * 13.2 PostgreSQL * 13.3 SQLite

Re: [Haskell-cafe] Hi can u explain me how drop works in Haskell

2007-02-26 Thread Antonio Cangiano
On 2/26/07, Thomas Hartman <[EMAIL PROTECTED]> wrote: Here's my, probably very obvious, contribution. What I'd like feedback on is 1) code seem ok? (hope so!) Hi Thomas, tail [] raises an error, therefore your code will fail when n > length xs ( e.g. mydrop 3 [1,2] will raise an exception,