Re: [Haskell-cafe] Re: Re[2]: [Haskell] Proposal: unification of styleof function/data/type/class definitions

2006-09-11 Thread Brian Hulley
Taral wrote: On 9/11/06, Bulat Ziganshin [EMAIL PROTECTED] wrote: Expr Bool = Eq (Expr t) (Expr t) | forall t . Eq t Still confusing, but less so. The problem is that it's really backwards. The symbol being defined is Eq. Eq (Expr t) (Expr t) | Eq t = Expr Bool but that doesn't fit

Re: [Haskell-cafe] Re: Re[2]: [Haskell] Proposal: unification of styleof function/data/type/class definitions

2006-09-11 Thread Brian Hulley
Taral wrote: On 9/11/06, Bulat Ziganshin [EMAIL PROTECTED] wrote: Expr Bool = Eq (Expr t) (Expr t) | forall t . Eq t Still confusing, but less so. The problem is that it's really backwards. The symbol being defined is Eq. Eq (Expr t) (Expr t) | Eq t = Expr Bool but that doesn't fit

Re: [Haskell-cafe] Re: [Haskell] Re: Proposal: unification of style offunction/data/type/class definitions

2006-09-10 Thread Brian Hulley
Bulat Ziganshin wrote: sequence :: [m a] - m [a] | Monad m I think translations of higher rank signatures using this syntax could be: foo :: (forall a. a- a) -b - c - (b,c) == foo :: (a - a | a) - b - c - (b, c) using the rule that we just write the variable by itself to indicate the

Re: [Haskell-cafe] Re: map (-2) [1..5]

2006-09-09 Thread Brian Hulley
Jón Fairbairn wrote: Brian Hulley [EMAIL PROTECTED] writes: I imagine that almost every editor at least does lexical fontification, and if so, then I don't think there could be much confusion in practice between these uses of '-'. I think that unnecessarily disadvantages people with poorer

Re: [Haskell-cafe] Re: sections of noncommutative operators

2006-09-09 Thread Brian Hulley
Michael Shulman wrote: On 09 Sep 2006 11:17:52 +0100, Jón Fairbairn [EMAIL PROTECTED] wrote: Right about the start of the design of Haskell, I proposed the rule parentheses should only be used for grouping. I think I would have liked that rule. Are parentheses currently used for anything

[Haskell-cafe] Weak pointers and referential transparency???

2006-09-09 Thread Brian Hulley
Hi, I have the following data structures: import System.Mem.Weak data Proxy = ... data Model = Model { _proxiesRef :: !(Ref.T [Weak Proxy]), ...} (Ref.T is just a lifted IORef) I was writing code like: createProxy :: MonadIO m = Model - m Proxy createProxy Model{_proxiesRef =

Re: [Haskell-cafe] map (-2) [1..5]

2006-09-08 Thread Brian Hulley
Cale Gibbard wrote: On 17/08/06, Brian Hulley [EMAIL PROTECTED] wrote: In contrast, a programming language should be based on general concepts uniformly applied. In Haskell we have operators, identifiers, prefix application using an identifier and infix application using a symbol, and a uniform

Re: [Haskell-cafe] Re: map (-2) [1..5]

2006-09-08 Thread Brian Hulley
Jón Fairbairn wrote: Brian Hulley [EMAIL PROTECTED] writes: Cale Gibbard wrote: Anyway, the point of all this is that 0,1,2... are not really literals at all. They're nullary operators which give particular elements of any given instance of Num. Perhaps at some level in the compiler after

Re: [Haskell-cafe] Monad laws

2006-09-07 Thread Brian Hulley
Deokhwan Kim wrote: What is the practical meaning of monad laws? (M, return, =) is not qualified as a category-theoretical monad, if the following laws are not satisfied: 1. (return x) = f == f x 2. m = return == m 3. (m = f) = g == m (\x - f x = g) But what practical problems can

Re: [Haskell-cafe] Monad laws

2006-09-07 Thread Brian Hulley
Lennart Augustsson wrote: On Sep 7, 2006, at 08:50 , Brian Hulley wrote: Deokhwan Kim wrote: What is the practical meaning of monad laws? Afaiu the monad laws are needed so the compiler can do various optimizations, especially in regard to the do notation. Consider: g c = do

Re: Re[2]: [Haskell-cafe] Reading integers

2006-09-07 Thread Brian Hulley
Bertram Felgenhauer wrote: I can't comment on why Bulat doesn't like negative numbers. Neither it seems, did the original Haskell committee - that's why we have to muddle along with a confusing unary minus operator instead of proper negative literals - see the thread beginning

Re: [Haskell-cafe] does the compiler optimize repeated calls?

2006-09-06 Thread Brian Hulley
John Hughes wrote: The trouble is that this isn't always an optimisation. Try these two programs: powerset [] = [[]] powerset (x:xs) = powerset xs++map (x:) (powerset xs) and powerset [] = [[]] powerset (x:xs) = pxs++map (x:) pxs where pxs = powerset xs Try computing length (powerset

[Haskell-cafe] Re: Problems trying to understand the BSD license

2006-09-04 Thread Brian Hulley
Simon Marlow wrote: Brian Hulley wrote: Copyright (c) 1988 XYZ ... Giving proper copyright attribution is not considered an endorsement, no. [other useful comments] Also what about the application's about dialog or help pages? There's no requirement in the BSD license that you have

Re: [Haskell-cafe] Advantages of using qualified names and a uniform naming convention

2006-09-04 Thread Brian Hulley
Henning Thielemann wrote: On Mon, 4 Sep 2006, Brian Hulley wrote: -- So related things appear alphabetically together... empty? :: Set a - Bool empty :: Set a I think the separation of alpha-numeric characters and other symbols simplifies things, and shall be preserved

Re: [Haskell-cafe] practice problems?

2006-09-03 Thread Brian Hulley
Tamas K Papp wrote: On Sun, Sep 03, 2006 at 12:47:45PM +0400, Bulat Ziganshin wrote: i also suggest you to start write some library. there is enough useful libs that are still bnot implemented because lack of time (and insterest in such simple code) on side of more experienced programmers. i

Re: [Haskell-cafe] practice problems?

2006-09-03 Thread Brian Hulley
Brian Hulley wrote: Interval llow lhigh + Interval rlow rhigh = Interval (min llow rlow) (max lhigh rhigh) Not a good start!!! ;-) Interval llow lhigh + Interval rlow rhigh = Interval (llow+rlow) (lhigh+rhigh) ___ Haskell-Cafe mailing list

[Haskell-cafe] Problems trying to understand the BSD license

2006-09-03 Thread Brian Hulley
Hi - I'm not sure if this is the right place to ask this question but since a lot of Haskell code is under the BSD license I think the answer could be useful for other people as well. The question I have is if I want to redistribute a binary executable under my own proprietary license that

Re: [Haskell-cafe] practice problems?

2006-09-03 Thread Brian Hulley
Paul Johnson wrote: Brian Hulley [EMAIL PROTECTED] wrote: What about a library for interval arithmetic [1]? [Interval 5 5] / [Interval -1 1] = [FromNegInfinityTo -5, ToPosInfinityFrom 5] Take a look at my Ranged Sets library at http://sourceforge.net/projects/ranged-sets Hi Paul

[Haskell-cafe] Advantages of using qualified names and a uniform naming convention

2006-09-03 Thread Brian Hulley
Hi - There's lots of great Haskell libraries available, but little standardization regarding naming conventions or code organization. In this post I try to illustrate some dimensions of the question of how to form names for things and offer my opinion on specific examples knowing that this of

Re: [Haskell-cafe] Re: A free monad theorem?

2006-09-01 Thread Brian Hulley
Benjamin Franksen wrote: Tomasz Zielonka wrote: whatever you do, you won't be able to extract an 'a' typed value, non-bottom from this computation. Cont is defined as: newtype Cont r a = Cont {runCont :: (a - r) - r)} So getting the value out of the monad is not a

Re: [Haskell-cafe] state and exception or types again...

2006-08-29 Thread Brian Hulley
Andrea Rossato wrote: Il Mon, Aug 28, 2006 at 09:28:02PM +0100, Brian Hulley ebbe a scrivere: where the 4th element of the tuple is True iff we can continue or False iff an exception occurred. I'm starting to believe that the best method is just take the way StateT takes... without

Re: [Haskell-cafe] state and exception or types again...

2006-08-28 Thread Brian Hulley
Andrea Rossato wrote: Now I'm trying to create a statefull evaluator, with output and exception, but I'm facing a problem I seem not to be able to conceptually solve. data Eval_SOI a = Raise { unPackMSOIandRun :: State - (a, State, Output) } | SOIE { unPackMSOIandRun :: State -

Re: [Haskell-cafe] difference between type and newtype

2006-08-26 Thread Brian Hulley
Andrea Rossato wrote: Il Sat, Aug 26, 2006 at 01:27:38AM +0200, Daniel Fischer ebbe a scrivere: Because T a is a function type, namely Int - (a,Int), so ... iHowever, neither T1 a nor T2 a is a function type, a value of type T1 a is a function _wrapped by the data (or value) constructor T1_

Re: [Haskell-cafe] difference between type and newtype

2006-08-26 Thread Brian Hulley
Andrea Rossato wrote: this is what I'm trying to do, sort of: turn the code at the button into the do-notation.[1] module StateOutputMonad where -- do notation only works with instances of Monad import Control.Monad data Term = Con Int | Add Term Term deriving (Show)

Re: [Haskell-cafe] difference between type and newtype

2006-08-25 Thread Brian Hulley
Andrea Rossato wrote: Hello! I cannot understand this piece of code: type Z = Int type T a = Z - (a, Z) newtype T1 a = T1 (Z - (a,Z)) mkT :: a - T a mkT a = \x - (a, x) Hi Andrea, The definition of mkT above is identical to just writing: mkT :: a - (Z - (a,Z)) which in turn is

Re: [Haskell-cafe] stack overflow when using ST monad

2006-08-24 Thread Brian Hulley
Gregory Wright wrote: -- A structure with internal state: -- data Tag s = Tag { tagID :: Int, state :: STRef s TagState, count :: STRef s Integer } data FrozenTag = FrozenTag { ft_tagID :: Int, ft_state :: TagState, ft_count :: Integer } deriving

[Haskell-cafe] Proposal to allow {} instead of () in contexts

2006-08-23 Thread Brian Hulley
Hi - Disregarding my last proposal which involved the use of {} in types, I am wondering if anyone would agree with me that it would be a good idea to use {} instead of () when writing out the context ie: foo :: (Num a, Bar a) = a - a would become: foo :: {Num a, Bar a} = a - a and

Re: [Haskell-cafe] Proposal to allow {} instead of () in contexts

2006-08-23 Thread Brian Hulley
On August 23, 2006 5:16 PM, Brian Smith wrote On 8/23/06, Brian Hulley [EMAIL PROTECTED] wrote: Hi - Disregarding my last proposal which involved the use of {} in types, I am wondering if anyone would agree with me that it would be a good idea to use {} instead of () when writing out

Fw: [Haskell-cafe] A restricted subset of CPP included in a revisionof Haskell 98

2006-08-22 Thread Brian Hulley
Hi - here is an exchange that was off-list by accident: Original Message From: Brian Smith To: Brian Hulley Sent: Tuesday, August 22, 2006 5:50 AM (Brian, I see that my last reply only went to you and so I forwarded it to the list. Since you replied to me directly, I am responding

Re: Re[2]: class [] proposal Re: [Haskell-cafe] One thought: Num to 0as ? to list?

2006-08-22 Thread Brian Hulley
Bulat Ziganshin wrote: f :: Num a = a - Int write as f :: Num - Int so, while this proposal is rather minor, i think that it is Good thing I wouldn't like it because I'd like to eventually make the class namespace separate from the tycon namespace so that I could write: class Object a

Re: Re[2]: class [] proposal Re: [Haskell-cafe] One thought: Num to0as ? to list?

2006-08-22 Thread Brian Hulley
Brian Hulley wrote: Bulat Ziganshin wrote: f :: Num a = a - Int write as f :: Num - Int Actually separating the class namespace from the tycon namespace would allow you to get a very similar effect to the use of abstract interfaces in C++ ie: class Object a where name

Re: Re[2]: class [] proposal Re: [Haskell-cafe] One thought: Numto0as ? to list?

2006-08-22 Thread Brian Hulley
Brian Hulley wrote: -- generated automatically? data Object = forall a. Object a Ooops! ;-) data Object = forall a. Object a = Object a ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: Re[2]: class [] proposal Re: [Haskell-cafe] One thought: Num to0as ? to list?

2006-08-22 Thread Brian Hulley
Brian Hulley wrote: Bulat Ziganshin wrote: f :: Num a = a - Int write as f :: Num - Int so, while this proposal is rather minor, i think that it is Good thing I wouldn't like it because I'd like to eventually make the class namespace separate from the tycon namespace... Apologies

Re: class [] proposal Re: [Haskell-cafe] One thought: Num to 0as ? to list?

2006-08-22 Thread Brian Hulley
Brandon Moore wrote: Perhaps there is something similar that could be done with type classes. In particular, I very much like Daan's rule of only inlining a constraint if the type it binds is only used once, which would mean Num - Num - Num would be equivalent to (Num a, Num b, Num c) = a - b

Re: Re[2]: class [] proposal Re: [Haskell-cafe] One thought: Num to 0as ? to list?

2006-08-22 Thread Brian Hulley
Bulat Ziganshin wrote: from one my module: copyStream :: (BlockStream h1, BlockStream h2, Integral size) = h1 - h2 - size - IO () in my library and found the way to simplify most of their signatures: copyStream :: BlockStream* - BlockStream** - Integral - IO () i think that

Re: Re[2]: class [] proposal Re: [Haskell-cafe] One thought: Num to 0as ? to list?

2006-08-22 Thread Brian Hulley
Bulat Ziganshin wrote: Hello Brian, Tuesday, August 22, 2006, 9:35:21 PM, you wrote: I feel if it ain't broken don't fix it, and not only is the existing syntax not broken, it's already (imho) absolutely perfect in it's clarity and consistency it's because you not programmed a lot with type

Re: [Haskell-cafe] A backwards-compatible record proposal

2006-08-20 Thread Brian Hulley
Bulat Ziganshin wrote: Hello Brian, Saturday, August 19, 2006, 12:21:34 PM, you wrote: ie putting a '.' before each field name. The intended meaning is that dotted field names do *not* generate top level functions. Instead they allow the compiler to generate instance decls as follows, where

Re: [Haskell-cafe] A restricted subset of CPP included in a revisionof Haskell 98

2006-08-20 Thread Brian Hulley
Henning Thielemann wrote: On Thu, 17 Aug 2006, Brian Smith wrote: I find it strange that right now almost every Haskell program directly or indirectly (through FPTOOLS) depends on CPP, yet there is no effort to replace CPP with something better or standardize its usage in Haskell. I think

[Haskell-cafe] A backwards-compatible record proposal

2006-08-19 Thread Brian Hulley
Hi - As I've been writing a Haskell program over the past few months the main problem I encounter is that record field names are not local to the record type, and any systematic way of making them local (eg by prepending _Tycon_) results in names that are just too clunky, and I feel that

Re: [Haskell-cafe] A backwards-compatible record proposal

2006-08-19 Thread Brian Hulley
Brian Hulley wrote: In the module containing the data decl for the record, the compiler inserts the following: instance (.x) (Vector3 a) a where (.x) v = ... -- compiler generated code to access the field instance (.x) (Vector3 a) a where (.x) Vector3{.x = x} = x

[Haskell-cafe] Re: A backwards-compatible record proposal

2006-08-19 Thread Brian Hulley
Gene A wrote: On 8/19/06, Brian Hulley [EMAIL PROTECTED] wrote: {... magSquared v = v.x*v.x + v.y*v.y + v.z*v.z ...} Hi, Won't the use of the dot lend confusion to the eye of the beholder.. that as in the code fragment about that v.y or v.z is implying function composition I'll admit

Re: [Haskell-cafe] A backwards-compatible record proposal

2006-08-19 Thread Brian Hulley
Bernard James POPE wrote: On Sat, Aug 19, 2006 at 09:21:34AM +0100, Brian Hulley wrote: Therefore I think the desugaring would need to take place in the compiler so the compiler could avoid exporting the compiler-generated instances when the fields are not present in the module export list

Re: [Haskell-cafe] A backwards-compatible record proposal

2006-08-19 Thread Brian Hulley
Ooops! ;-) Brian Hulley wrote: module M (Rec, use) where import DotClasses.Dot_f-- every class has its own module (*) data Rec' a = Rec a newtype Rec a = Rec (Rec' a) instance Dot__f (Rec' a) a where instance Dot_f (Rec' a) a where __dot_f (Rec' x) = x

Re: [Haskell-cafe] A backwards-compatible record proposal

2006-08-19 Thread Brian Hulley
Brian Hulley wrote: However I think it could be solved by a more complex desugaring: The proposed desugarings allow us to either make all dotted fields in a record visible, or none of them visible, but I don't think there exists a desugaring that would allow some to be visible while others

Re: [Haskell-cafe] C++ class = neutered (haskell class + haskellexistential)

2006-08-18 Thread Brian Hulley
Bulat Ziganshin wrote: http://haskell.org/haskellwiki/OOP_vs_type_classes although i mentioned not only pluses but also drawbacks of type classes: lack of record extension mechanisms (such at that implemented in O'Haskell) and therefore inability to reuse operation implementation in an derived

Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Brian Hulley
Tamas K Papp wrote: The code in the subject generates an error. I understand why this is (- is treated as part of the number), but I don't know how to solve it, ie how to tell Haskell that - is a function/binary operator? Actually looking at the Haskell98 report, -2 seems to be treated as

Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Brian Hulley
Jared Updike wrote: -4^2is not the same whether parsed as (-4)^2 or -(4^2) (the correct version) Basically, before someone argues this with me, -4^2 should parse the same as - 4^2 which should be the same thing as 0 - 4^2 I'd argue that -4^2 should parse as (-4)^2 in the same way

Re: [Haskell-cafe] A restricted subset of CPP included in a revisionof Haskell 98

2006-08-17 Thread Brian Hulley
On Thursday, August 17, 2006 7:54 PM, Brian Smith wrote: I want to have conditionals limited in their placement to make things easier for refactoring tools. But, I don't have any ideas about how to deal with conditional exports without allowing preprocessor conditionals in the export list.

Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Brian Hulley
Jared Updike wrote: I'd also argue that in maths the necessary brackets are implied by the superscripting syntax ASCII text parsing issues aside, in math, 2 -4 =? (No you cannot ask if there is space between the 4 and the - symbol, or if I meant (-4)^2 or -(4^2), or if I

Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Brian Hulley
David House wrote: On 17/08/06, Brian Hulley [EMAIL PROTECTED] wrote: Literal highlighting in the editor would make it clear that x-2 === x (-2). I think a basic issue is that at the moment it is strange that non-negative numbers can be specified as literals but negative numbers can't

Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Brian Hulley
Jared Updike wrote: In other words, superscripts bind tighter than prefix ops but prefix ops bind tighter than infix. I see. My point is that there already exists a convention[1] that the way to type in 2 -4 is -4^2 which means -(4^2) not (-4)^2 because - as a prefix op has the same

Re: [Haskell-cafe] Re: Why Not Haskell?

2006-08-07 Thread Brian Hulley
Jón Fairbairn wrote: Stefan Monnier [EMAIL PROTECTED] writes: I can't entirely dismiss GNU/FSF/GPL but it poses a fundamental conflict with the only way I can see of earning a living so it's like a continuous background problem which drains some of my energy and enthusiasm hence the length of

Re: [Haskell-cafe] Re: Why Not Haskell?

2006-08-07 Thread Brian Hulley
Brian Hulley wrote: Jón Fairbairn wrote: Stefan Monnier [EMAIL PROTECTED] writes: I can't entirely dismiss GNU/FSF/GPL... Maybe you should thank the FSF for making you doubt: I know of several good ideas that started out as attempts at commercial projects but weren't taken up. [...snip

Re: [Haskell-cafe] How can we detect and fix memory leak due tolazyness?

2006-08-07 Thread Brian Hulley
Ahn, Ki Yung wrote: Recently, I'm facing the dark side of laziness -- the memory leak because of laziness. The following is the code that leaks memory. sctAnal gs = null cgs || all (not . null) dcs where gs' = fixSize compose $ Set.fromList [TT (x,y,cs) [] | To _ x y cs-Set.toList gs]

Re: [Haskell-cafe] Why Not Haskell?

2006-08-06 Thread Brian Hulley
Piotr Kalinowski wrote: On 06/08/06, Brian Hulley [EMAIL PROTECTED] wrote: Therefore I think this distinction between concepts is just sophistry. The distinction is there and relies on the community and people being honest to avoid situations as you described. If you don't want it however

Re: [Haskell-cafe] Monad Imparative Usage Example

2006-08-05 Thread Brian Hulley
Kaveh Shahbazian wrote: Thanks All This is about my tries to understand monads and handling state - as you perfectly know - is one of them. I have understood a little about monads but that knowledge does not satidfy me. Again Thankyou There are many tutorials available from the wiki at

Re: [Haskell-cafe] Monad Imparative Usage Example

2006-08-05 Thread Brian Hulley
Brian Hulley wrote: q = (\x - p) For example with the State monad, (q) must be some expression which evaluates to something of the form S fq where fq is a function with type s - (a,s), and similarly, (\x - p) must have type a -S ( s - (a,s)). If we choose names for these values which describe

Re: [Haskell-cafe] Monad Imparative Usage Example

2006-08-05 Thread Brian Hulley
Ooops - more bugs in my explanation... Brian Hulley wrote: -- from State.hs newtype State s a = S (s - (a,s)) I used the source given in ghc-6.4.2\libraries\monads\Monad\State.hs but the version of state monad that comes with the hierarchical libs is in ghc-6.4.2\libraries\mtl\Control

Re: [Haskell-cafe] Why Not Haskell?

2006-08-05 Thread Brian Hulley
Henning Thielemann wrote: On Fri, 4 Aug 2006, Brian Hulley wrote: 4) Haskell is open source and licensing restrictions forbid commercial applications. I haven't seen any such restrictions, but is this a problem for the standard modules? You can discover the licensing situation by downloading

Re: [Haskell-cafe] a bunch of newbie questions

2006-08-04 Thread Brian Hulley
Mark T.B. Carroll wrote: Janis Voigtlaender [EMAIL PROTECTED] writes: (snip) Yes, as long as enough type information is provided for the typechecker to decide what is the correct instance to use. (snip) I've always been a little surprised when this doesn't happen more widely for things other

Re: [Haskell-cafe] a bunch of newbie questions

2006-08-04 Thread Brian Hulley
Martin Percossi wrote: Bulat Ziganshin wrote: this is called ad-hoc polymorphism which is not supported by Haskell. instead Haskell supports parametric polymorphism via type classes. I think you are wrong here Bulat. In fact, I think a) Haskell supports parametric polymorphism, e.g. id :: t

Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread Brian Hulley
Hans van Thiel wrote: Hello All, I'm wondering why I can't find any commercial Haskell applications on the Internet. Is there any reason for this? I'm actually working on a Haskell program which I hope to release as a commercial application. The biggest problem I'm encountering is the lack

Re: Re[2]: [Haskell-cafe] a bunch of newbie questions

2006-08-04 Thread Brian Hulley
Bulat Ziganshin wrote: Hello Brian, Friday, August 4, 2006, 8:50:25 PM, you wrote: class Bar a b where bar :: a - b (*) But there's one exception: you can't use typeclasses to resolve overloadings between values and functions because non-function values don't have a

Re: [Haskell-cafe] Why shouldn't variable names be capitalized?

2006-08-04 Thread Brian Hulley
Martin Percossi wrote: Hi, I'm wondering what the rationale was for not allowing capitalized variable names (and uncapitalized type names and constructors). I can only think of two arguments, and IMHO both of them are bad: 1. Enforces a naming convention. Fine - but my view is that this doesn't

[Haskell-cafe] Code review: initial factoring for sequences and other structures

2006-08-03 Thread Brian Hulley
Hi - I've started work on an initial factoring of sequence ops into classes, and already I've run into some major design issues which stand like a mountain in the way of progress. The classes are below: -- all code below standard BSD3 licence :-) module Duma.Data.Class.Foldable (

Re: [Haskell-cafe] Code review: initial factoring for sequences andother structures

2006-08-03 Thread Brian Hulley
Brian Hulley wrote: Hi - I've started work on an initial factoring of sequence ops into [snip] class Foldable c a | c - a where foldR :: (a - b - b) - b - c - b [snip] There is a general problem that when the element type needs to be specified along with the type of the overall

Re: [Haskell-cafe] ANN: TextRegexLazy-0.56, (=~) and (=~~) are here

2006-08-02 Thread Brian Hulley
Chris Kuklewicz wrote: Announcing: TextRegexLazy version 0.56 Where: Tarball from http://sourceforge.net/projects/lazy-regex darcs get --partial [--tag=0.56] http://evenmere.org/~chrisk/trl/stable/ License : BSD, except for Great! - Thanks for all your hard work in making this available

Re: Re[2]: [Haskell-cafe] The difficulty of designing a sequence class

2006-08-01 Thread Brian Hulley
Bulat Ziganshin wrote: Hello Brian, Tuesday, August 1, 2006, 4:43:23 AM, you wrote: As you've pointed out, there are 2 separate issues that are in danger of being confused: 1) Forcing all sequence instances to support all operations 2) Bundling all the ops into a single huge class

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-08-01 Thread Brian Hulley
John Meacham wrote: On Tue, Aug 01, 2006 at 02:56:21AM +0100, Brian Hulley wrote: Now the problem is that person C may come along and notice that there is a useful abstraction to be made by inheriting both from ClassA and ClassB. But both of these define foo and there is no mechanism

Re: [Haskell-cafe] Future Edison directions

2006-08-01 Thread Brian Hulley
Robert Dockins wrote: [snip other points] 7) Finally, I somehow feel like there should be a nice categorical formulation of these datastructure abstractions which would help to drive a refactoring of the API typeclasses in a principled way, rather than on an ad-hoc

Re: [Haskell-cafe] Future Edison directions

2006-08-01 Thread Brian Hulley
Robert Dockins wrote: [snip] 7) Finally, I somehow feel like there should be a nice categorical formulation of these datastructure abstractions which would help to drive a refactoring of the API typeclasses in a principled way, rather than on an ad-hoc I-sort-of-think-these-go-together sort of

Re: [Haskell-cafe] Future Edison directions

2006-08-01 Thread Brian Hulley
Jared Updike wrote: This page: http://jaortega.wordpress.com/2006/03/17/programmers-go-bananas/ lists some references at the bottom. Perhaps they would be useful. Thanks! That page looks really interesting and useful, Brian. ___ Haskell-Cafe

Re: [Haskell-cafe] Future Edison directions

2006-08-01 Thread Brian Hulley
Brian Hulley wrote: splitWith :: (v - Bool) - c - (c,c) splitWith p t | isEmpty t = (empty, empty) | p (measure t) = let (l,x,r) = splitWithInternal p mempty t in (l, pushL x r) | otherwise

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley
Robert Dockins wrote: On Jul 30, 2006, at 5:28 PM, Brian Hulley wrote: Robert Dockins wrote: So, what you want is a sequence of sequences that can be transparently converted to a flattened sequence and vice versa? Yes as long as the conversion between them takes no time at all

Fw: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley
David Menendez wrote: Brian Hulley writes: 1) Did Edison choose MonadPlus just because this fitted in with the lack of multi-parameter typeclasses in H98? Instances of Monoid (and your ISeq) have kind *. Instances of MonadPlus (and Edison's Sequence) have kind * - *. Functions like map, zip

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley
David Menendez wrote: [EMAIL PROTECTED] writes: I didn't get around to fixing Sequence because there wasn't a need for it yet, but yes, it should be done. That's a tough call to make. Changing the kind of Sequence to * from * - * means losing the Functor, Monad, and MonadPlus superclasses and

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley
[EMAIL PROTECTED] wrote: G'day all. Quoting Brian Hulley [EMAIL PROTECTED]: The problem is that some people will be using Data.Edison.Seq at the moment and will naturally not want it to change. However I'd suggest that all the common operations be factored out into separate classes eg

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley
Brian Hulley wrote: David Menendez wrote: Brian Hulley writes: 4) Would it be worth reconsidering the rules for top level names so that class methods could always be local to their class (ditto for value constructors and field names being local to their type constructor). Qualified module

[Haskell-cafe] The difficulty of designing a sequence class

2006-07-30 Thread Brian Hulley
Hi - Part 1 of 2 - Monoid versus MonadPlus === I've just run into a troublesome question when trying to design a sequence class: class ISeq c a | c - a where empty :: c single :: a - c append :: c - c - c However I've noticed that people

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-30 Thread Brian Hulley
Robert Dockins wrote: On Sunday 30 July 2006 07:47, Brian Hulley wrote: Another option, is the Edison library which uses: class (Functor s, MonadPlus s) = Sequence s where so here MonadPlus is used instead of Monoid to provide empty and append. So I've got three main questions: 1) Did

Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Brian Hulley
Jon Fairbairn wrote: On 2006-07-27 at 13:01+0200 Tomasz Zielonka wrote: Also, after a few years of Haskell programming, I am still not sure how to indent if-then-else. what I was alluding to in my footnote... I think there's really only one way when it needs to occupy more than one line:

Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Brian Hulley
David House wrote: On 27/07/06, Brian Hulley [EMAIL PROTECTED] wrote: I think there's really only one way when it needs to occupy more than one line: if c then t else f Confusingly, if c then t else f Also works, although no-one really knows why. Only

Re: [Haskell-cafe] if-then-else as rebindable syntax (was Re: Why doesHaskell have the if-then-else syntax?)

2006-07-27 Thread Brian Hulley
Niklas Broberg wrote: Also, is cond the best name for the suggested function? If we don't expect anyone to really use it without the sugar, we could name it whatever weird thing so as to break as few existing programs as possible. It would make explicit import a bit more akward though. But I

Re: [Haskell-cafe] Re: Why Haskell?

2006-07-24 Thread Brian Hulley
Simon Marlow wrote: Neil Mitchell wrote: Would it not be possible to add a GHC rule like the following: forall a b . sequence a b = sequence_ a b I'm not sure if thats correct, a valid rule definition, or semantics preserving, but if it was it would be nice :) Now there's a good idea!

Re: [Haskell-cafe] Why Haskell?

2006-07-23 Thread Brian Hulley
Matthew Bromberg wrote: 3) The problem here is existing code. I don't want to add every function that I use into a class just to maintain simple polymorphism over closely related numeric types. This would take longer than just calling the coercion routines. It's funny how trivial stuff likes

Re: Re[2]: [Haskell-cafe] Re: ANN: System.FilePath 0.9

2006-07-23 Thread Brian Hulley
Bulat Ziganshin wrote: Hello Brian, Sunday, July 23, 2006, 1:20:36 AM, you wrote: instance IString ByteString.Char8 ... instance IString String ... i think that we should ask Donald Stewart who is patronized SoC project involving development of such type class. If he will say that such type

Re: [Haskell-cafe] Re: ANN: System.FilePath 0.9

2006-07-22 Thread Brian Hulley
Neil Mitchell wrote: And if someone wants to define a new and better FilePath type, I would prefer something more abstract, such as a list of Path components, with functions to serialize it as a String and to parse it from a String. A list of path components is just not enough, I'm afraid.

Re: [Haskell-cafe] Comma in the front

2006-07-14 Thread Brian Hulley
Tim Docker wrote: These layouts feel a bit artificial to me. I am quite partial to python's list syntax - a trailing comma is optional. meaning you can write [ a, b, c, ] I'm surprised this approach isn't more widespread - Are there reasons why haskell syntax could

Re: [Haskell-cafe] Re: Why is there no splitBy in the list module?

2006-07-12 Thread Brian Hulley
Christian Maeder wrote: Donald Bruce Stewart schrieb: Question over whether it should be: splitBy (=='a') aabbaca == [,,bb,c,] or splitBy (=='a') aabbaca == [bb,c] I argue the second form is what people usually want. Yes, the second form is needed for words, but the first form is

Re: [Haskell-cafe] help with creating a DAG?

2006-07-08 Thread Brian Hulley
David Roundy wrote: Hi all, I'm wanting to create a data structure to hold a directed acyclic graph (which will have patches represented by edges), and haven't yet been able to figure out a nice representation. I'd like one that can be reasoned with recursively, or as closely to recursively as

Re: [Haskell-cafe] Re: Packages and modules

2006-07-06 Thread Brian Hulley
Brian Hulley wrote: Simon Peyton-Jones wrote: compulsory. Perhaps you could improve the wording to make it more unambiguous? Indeed, if we've converged, would you like to fold into our draft whatever you think is useful from yours? [snip] Therefore it seems best to just leave them

[Haskell-cafe] Re: Packages and modules

2006-07-05 Thread Brian Hulley
Simon Peyton-Jones wrote: In response to Brian and Ian's helpful comments, I've added a bunch more stuff to our proposal about packages. If I have missed anything, let me know. http://hackage.haskell.org/trac/ghc/wiki/GhcPackages If you or anyone else thinks the choices made there are poor

[Haskell-cafe] Re: Packages and modules

2006-07-05 Thread Brian Hulley
Simon Peyton-Jones wrote: So instead of just taking this simple solution, the wiki proposal is instead destroying the beauty of the per-package namespace idea by incorporating into it the existing shared namespaces with their attendant problems, instead of just letting the existing messy system

Re: [Haskell-cafe] Re: Where is Data.Atom?

2006-07-04 Thread Brian Hulley
Iain Alexander wrote: Another suggestion: Put your strings in an ordered binary tree (other data structures might also work here). Make your Atom an encoding of the structure of the tree (resp. other structure). This is logically a sequence of bits, 0 for left (less than), 1 for right

[Haskell-cafe] Re: Packages and modules

2006-07-04 Thread Brian Hulley
Simon Peyton-Jones wrote: Concerning other mail on this subject, which has been v useful, I've revised the Wiki page (substantially) to take it into account. http://hackage.haskell.org/trac/ghc/wiki/GhcPackages Further input (either by email or by adding material to the Wiki) would be welcome.

Re: [Haskell-cafe] Re: Packages and modules

2006-07-04 Thread Brian Hulley
Brian Hulley wrote: Simon Peyton-Jones wrote: http://hackage.haskell.org/trac/ghc/wiki/GhcPackages I think the following is a non-question: An open question: if A.B.C is in the package being compiled, and in an exposed package, and you say import A.B.C, do you get an error

Re: [Haskell-cafe] Are FunPtr's stable? (was: how to write an haskellbinding)

2006-06-28 Thread Brian Hulley
Simon Peyton-Jones wrote: Can I urge any of you who learn stuff that I wish I'd know at the beginning to add that information to GHC's FFI Wiki page? http://haskell.org/haskellwiki/GHC/Using_the_FFI Anyone can add to this material, and it's extremely helpful to jot down what you've learned while

Re: [Haskell-cafe] Packages and modules

2006-06-28 Thread Brian Hulley
Marc Weber wrote: I'm not sure on which mail of this thread I should append MHO. What happens if two programmers happen to choose the same package name? (Prepend the location on the filesystem? ;-) If something like a package name is introduced I would prefer not separating package and module

Re: [Haskell-cafe] how to write an haskell binding

2006-06-27 Thread Brian Hulley
[EMAIL PROTECTED] wrote: Quoting Brian Hulley [EMAIL PROTECTED]: It is defnitely *a* haskell. There is actually no word in English with a silent 'h', though this statement is unfortunately controversial and news to whoever wrote the spell checker used in many printed publications

[Haskell-cafe] Are FunPtr's stable? (was: how to write an haskell binding)

2006-06-27 Thread Brian Hulley
Bulat Ziganshin wrote: Hello Brian, Tuesday, June 27, 2006, 2:43:15 AM, you wrote: achieve a goal. One other thing to bear in mind is that foreign calls are extremely slow, so for example it is much faster to use the Foreign.Marshal.Array and Foreign.C.String functions to allocate and

<    1   2   3   4   >