Re: [Haskell-cafe] Rank N type tutorial?

2006-10-27 Thread Ben Rudiak-Gould
Greg Buchholz wrote: I'm not quite sure why this is illegal... foo :: Integer - (forall a. Show a = a) foo 2 = [foo] foo x = x ...while this is just fine... bar :: Integer - (forall a. Show a = a-b) - b bar 2 k = k [bar] bar x k = k x The way to think about it is that foralls are extra

[Haskell-cafe] Re: Fractional/negative fixity?

2006-11-10 Thread Ben Rudiak-Gould
I'm surprised that no one has mentioned showsPrec and readsPrec. Anything more complicated than negative fixities would require their interfaces to be changed. -- Ben ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] File path programme

2005-01-24 Thread Ben Rudiak-Gould
Isaac Jones wrote: You might be interested in the new FilePath module that's in the works. There's been a lot of work to make these functions portable. http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/libraries/base/System/FilePath.hs I didn't realize this was in CVS. IMHO this library is

Re: [Haskell-cafe] Haskell programs in C

2005-01-25 Thread Ben Rudiak-Gould
Mark Carroll wrote: Wasn't there someone mentioning here a little while ago some project where they strip most of System.* from the libraries and get something that might be suitable for embedded applications? What was that called? Anyone remember? hOp: http://www.macs.hw.ac.uk/~sebc/hOp/ --

Re: [Haskell-cafe] File path programme

2005-01-25 Thread Ben Rudiak-Gould
Jules Bean wrote: [...] it is an extension of the notion that /foo/ and /foo refer to the same directory. (Except, apparently, in the presence of symbolic links... or so I have some vague memory) Yes, /foo/ is equivalent to /foo/., which is not always the same as /foo. If /foo is a symlink,

Re: [Haskell-cafe] File path programme

2005-01-26 Thread Ben Rudiak-Gould
robert dockins wrote: After the discussion about file paths over the last several days I went home and put together a quick trial implementation for unix file paths, with the idea of adding windows, SMB and maybe VMS (why not?) paths. This is great. Comments below. data PathRoot =

Re: [Haskell-cafe] The Nature of Char and String

2005-01-30 Thread Ben Rudiak-Gould
John Goerzen wrote: Char in Haskell represents a Unicode character. I don't know exactly what its size is, but it must be at least 16 bits and maybe more. String would then share those properties. However, usually I'm accustomed to dealing with data in 8-bit words. So I have some questions: Char

Re: [Haskell-cafe] Re: File path programme

2005-01-31 Thread Ben Rudiak-Gould
Peter Simons wrote: The module currently knows only _relative_ paths. I am still experimenting with absolute paths because I have recently learned that on Windows something like C:foo.txt is actually relative -- not absolute. Very weird. \foo.txt is also relative on Win32. And con.txt is absolute.

Re: [Haskell-cafe] Parity of the number of inversions of a permutation

2005-03-15 Thread Ben Rudiak-Gould
Henning Thielemann wrote: I' searching for a function which sorts the numbers and determines the parity of the number of inversions. I assume that there are elegant and fast algorithms for this problem (n * log n time steps), e.g. a merge sort algorithm. This is a rather nice little problem. I

Re: [Haskell-cafe] Growing Trees

2005-09-22 Thread Ben Rudiak-Gould
[Previously sent only to the OP -- oops] Tom Hawkins wrote: data Tree a = TreeRoot { stuff:: a , children :: [Tree] } | TreeNode { stuff:: a , parent :: Tree , children :: [Tree] } But because of these bidirectional

Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-14 Thread Ben Rudiak-Gould
Cale Gibbard wrote: As an example of this sort of thing, I know that there are only 4 values of type a - Bool (without the class context). They are the constant functions (\x - True), (\x - False), and two kinds of failure (\x - _|_), and _|_, where _|_ is pronounced bottom and represents

Re: [Haskell-cafe] newtype is superfluous

2005-10-15 Thread Ben Rudiak-Gould
Wolfgang Jeltsch wrote: This is not true. With newtype, A _|_ is _|_, with data, A _|_ is not _|_. It's probably more helpful to explain this in terms of a program that exhibits different behavior in the two cases: case error data of A x - newtype But as far as I know, the above

Re: [Haskell-cafe] Two questions: lazy evaluation and Church-Rosser

2005-11-19 Thread Ben Rudiak-Gould
Gregory Woodhouse wrote: I've been trying to do some background reading on lambda calculus, and have found discussions of strict evaluation strategies (call-by-value and call-by-name) but have yet to find an appropriate framework for modeling lazy evaluation Just wanted to point out that

Re: [Haskell-cafe] Existentially-quantified constructors, Eq and Show

2005-12-11 Thread Ben Rudiak-Gould
John Meacham wrote: PS. many, including me, feel 'forall' is a misnomer there and should be the keyword 'exists' instead. so just read 'foralls' that come _before_ the type name as 'exists' in your head and it will make more sense. I disagree. When you write forall a. D (P a) (Q a) it

Re: [Haskell-cafe] Shootout favouring C

2006-01-16 Thread Ben Rudiak-Gould
Isaac Gouy wrote: Please keep to the true spirit of fictional crime writing and provide a motive for these evil characters who will stop at nothing to make Haskell seem some worse than C. Erm, fictional? It strikes me that this particular brand of evil is more the norm than the exception. I

Re: [Haskell-cafe] Guess what ... Tutorial uploaded! :)

2006-01-23 Thread Ben Rudiak-Gould
Dmitry Astapov wrote: http://www.haskell.org/hawiki/HitchhickersGuideToTheHaskell I like the approach too, but the section on IO actions, which I'm reading now, is not correct. It's not true that a - someAction has the effect of associating a with someAction, with the actual work deferred

[Haskell-cafe] Re: strict Haskell dialect

2006-02-04 Thread Ben Rudiak-Gould
Chris Kuklewicz wrote: Weak uses seq to achieve WHNF for it's argument newtype Weak a = WeakCon {runWeak :: a} mkWeak x = seq x (WeakCon x) unsafeMkWeak x = WeakCon x This doesn't actually do what you think it does. mkWeak and unsafeMkWeak are the same function. mkWeak 123 = seq 123

[Haskell-cafe] Re: Why is $ right associative instead of left associative?

2006-02-04 Thread Ben Rudiak-Gould
No one has mentioned yet that it's easy to change the associativity of $ within a module in Haskell 98: import Prelude hiding (($)) infixl 0 $ f$x = f x or, for the purists, import Prelude hiding (($)) import qualified Prelude (($)) infixl 0 $ ($) = (Prelude.$)

[Haskell-cafe] Re: Why is $ right associative instead ofleftassociative?

2006-02-05 Thread Ben Rudiak-Gould
Paul Hudak wrote: Minor point, perhaps, but I should mention that : is not special syntax -- it is a perfectly valid infix constructor. But Haskell 98 does treat it specially: you can't import Prelude hiding ((:)), or rebind it locally, or refer to it as Prelude.:. In fact I've always

[Haskell-cafe] Re: Why is $ right associative instead of leftassociative?

2006-02-05 Thread Ben Rudiak-Gould
Tomasz Zielonka wrote: On Sun, Feb 05, 2006 at 01:14:42PM -, Brian Hulley wrote: How about: f x y . g x $ z But then you have a problem when you when you want to add something at the beginning ;-) How about: id . f x y . g x $ z -- Ben

[Haskell-cafe] Re: extending bang proposal Re: strict Haskell dialect

2006-02-06 Thread Ben Rudiak-Gould
Bulat Ziganshin wrote: Hello Ketil, KM (Is the second ! actually meaningful?) yes! it means that the function is strict in its result - i.e. can't return undefined value when strict arguments are given. Unfortunately this interpretation runs pretty quickly into theoretical difficulties. A !

[Haskell-cafe] Re: extending bang proposal Re: strict Haskell dialect

2006-02-07 Thread Ben Rudiak-Gould
Brian Hulley wrote: One motivation seems to be that in the absence of whole program optimization, the strictness annotations on a function's type can allow the compiler to avoid creating thunks at the call site for cross-module calls whereas using seq in the function body itself means that the

[Haskell-cafe] Re: Matching constructors

2006-02-11 Thread Ben Rudiak-Gould
Mark T.B. Carroll wrote: Creighton Hogg [EMAIL PROTECTED] writes: data Patootie = Pa Int | Tootie Int and I want to pull out the indices of all elements of a list that have type constructor Tootie, how would I do that? x = [Pa 3, Tootie 5, Pa 7, Tootie 9, Pa 11] y = [ i |Tootie i - x ]

[Haskell-cafe] Re: -fno-monomorphism-restriction makes type-inference ambiguous?

2006-02-27 Thread Ben Rudiak-Gould
Eike Scholz wrote: mylength = synAttr listLength $ *Main :type synAttr $ synAttr :: (Data b) = ((?stack::[Dyn]) = b - a) - Attr a $ *Main :type listLength $ listLength :: (?stack::[Dyn]) = List - Float $ *Main :type (synAttr listLength) $ (synAttr listLength) :: Attr Float $ *Main :type

[Haskell-cafe] Re: PrefixMap: code review request

2006-02-28 Thread Ben Rudiak-Gould
Brian Hulley wrote: Whoever thought up the original Haskell layout rule assumed that people would be happy using a single fixed width font, tabs set to 8 spaces, and didn't care about the brittleness of the code (in the face of identifier renamings) it allowed one to write. Are you

[Haskell-cafe] Re: rounding errors with real numbers.

2006-02-28 Thread Ben Rudiak-Gould
Henning Thielemann wrote: Maybe you should use a kind of convex combination, that is (x-oldLower)*a + (oldUpper-x)*b Maybe lower*(1-z) + upper*z where z = (x-oldLower) / (oldUpper-oldLower). I think this will always map oldLower and oldUpper to lower and upper exactly, but I'm not sure it's

[Haskell-cafe] Layout rule (was Re: PrefixMap: code review request)

2006-02-28 Thread Ben Rudiak-Gould
Brian Hulley wrote: Here is my proposed layout rule: 1) All layout keywords (where, of, let, do) must either be followed by a single element of the corresponding block type, and explicit block introduced by '{', or a layout block whose first line starts on the *next* line I wouldn't have

[Haskell-cafe] Re: Layout rule (was Re: PrefixMap: code review request)

2006-03-01 Thread Ben Rudiak-Gould
Duncan Coutts wrote: hIDE and Visual Haskell use the ghc lexer and get near-instantaneous syntax highlighting. Hmm... I just installed Visual Haskell 0.1, and when I type in the editor, CPU usage rises to about 70% and there's a noticeable delay before each character appears on the screen.

[Haskell-cafe] Re: Layout rule (was Re: PrefixMap: code review request)

2006-03-01 Thread Ben Rudiak-Gould
Benjamin Franksen wrote: TAB characters in program text should be forbidden by law. Well... they are quite useful for lining things up if you're using a proportional font, and I don't think proportionally-spaced code is a bad idea. I want them to be optional. But it would be nice if parsers

[Haskell-cafe] Re: Layout rule

2006-03-01 Thread Ben Rudiak-Gould
Ketil Malde wrote: Multi line comments are nice for commenting out blocks of code. They're also nice for comments within a line. E.g. haskell-src-exts contains the declaration data HsQualConDecl = HsQualConDecl SrcLoc {- forall -} [HsName] {- . -} HsContext {- = -}

[Haskell-cafe] Re: Layout rule (was Re: PrefixMap: code review request)

2006-03-02 Thread Ben Rudiak-Gould
I wrote: I just installed Visual Haskell 0.1, and when I type in the editor, CPU usage rises to about 70% and there's a noticeable delay before each character appears on the screen. This is no longer happening, so I guess I ran afoul of a bug. -- Ben

[Haskell-cafe] Re: different code in different platforms

2006-03-17 Thread Ben Rudiak-Gould
Neil Mitchell wrote: #ifdef __WIN32__ (Windows code) #else (Linux code) #endif In Yhc, we use a runtime test to check between Windows and Linux. I think the cleanest solution is to factor the OS-specific code into separate modules with OS-independent interfaces and names, and pull

[Haskell-cafe] Re: how would this be done? type classes? existential types?

2006-03-17 Thread Ben Rudiak-Gould
Matthias Fischmann wrote: now i want to create a list of a type similar to [r1, r2, r3] :: (Resource a) = [a] but with r1 being pizza, r2 being crude oil, and so on. The type you actually want here is [exists a. (Resource a) a], but no Haskell implementation supports that. data Rs =

[Haskell-cafe] Re: how would this be done? type classes? existentialtypes?

2006-03-17 Thread Ben Rudiak-Gould
Matthias Fischmann wrote: is there any difference between these two? if they are equivalent, why the two different ways to say it? data X where X :: (Resource a) = a - X data Y = forall a . (Resource a) = Y a There's no difference. There are two ways to say it for historical reasons.

[Haskell-cafe] Re: how would this be done? type classes? existential types?

2006-03-17 Thread Ben Rudiak-Gould
Matthias Fischmann wrote: On Thu, Mar 16, 2006 at 12:40:00PM +, Chris Kuklewicz wrote: (Why isn't it resourceName :: String ?) when i am trying this, ghc complains that the type of resourceName doesn't have any occurrance of 'a', and i feel that it must be harder for the type engine to

[Haskell-cafe] Re: how would this be done? type classes?existential types?

2006-03-23 Thread Ben Rudiak-Gould
Brian Hulley wrote: Is there a reason for using instead of [exists a. Resource a=a] ? Only that = looks like a function arrow, looks like a tuple. I stole this notation from an unpublished paper by SimonPJ et al on adding existential quantification to Haskell. I'm not especially

[Haskell-cafe] Re: Positive integers

2006-03-23 Thread Ben Rudiak-Gould
Daniel McAllansmith wrote: I can see the domain bounds check would be a problem in theory, but in practice doesn't the type enforce that? Keeping Word positive costs nothing because it just overflows. Wouldn't it be much the same? If you're planning wraparound semantics then you're better

[Haskell-cafe] Re: Existentially-quantified constructors: Hugs is fine, GHC is not?

2006-05-11 Thread Ben Rudiak-Gould
Otakar Smrz wrote: data ... = ... | forall b . FMap (b - a) (Mapper s b) ... where FMap qf qc = stripFMap f q the GHC compiler as well as GHCi (6.4.2 and earlier) issue an error My brain just exploded. I can't handle pattern bindings for existentially-quantified

[Haskell-cafe] Re: develop new Haskell shell?

2006-05-12 Thread Ben Rudiak-Gould
Brian Hulley wrote: Donn Cave wrote: (cd /etc/stuff; cat * result) Well the problem here is that the command leaves you in /etc/stuff so you have to remember this when you subsequently execute another command. No it doesn't. The parentheses around the command sequence cause it to run in

Re: [Haskell-cafe] matching constructors

2004-03-08 Thread Ben Rudiak-Gould
On Mon, 8 Mar 2004, Vadim Zaliva wrote: I am doing command line options parsing. I've defined Flag type with constructor for each possible option: data Flag = Verbose | Input String | Output String | Filter String deriving (Show,

Re: [Haskell-cafe] Writing binary files?

2004-09-15 Thread Ben Rudiak-Gould
I modestly re-propose the I/O model which I first proposed last year: http://www.haskell.org/pipermail/haskell/2003-July/012312.html http://www.haskell.org/pipermail/haskell/2003-July/012313.html http://www.haskell.org/pipermail/haskell/2003-July/012350.html

[Haskell-cafe] Maybe bytes *are* text (was Re: Writing binary files?)

2004-09-16 Thread Ben Rudiak-Gould
On Thu, 16 Sep 2004, Udo Stenzel wrote: Having a seperate byte based api is far better. If you don't know the encoding, all you have is bytes, no text. Okay, after reading large chunks of this discussion, I'm going to rock the boat a bit by suggesting that bytes *are* text, and *do* belong in

Re: [Haskell-cafe] OO idioms redux

2004-10-12 Thread Ben Rudiak-Gould
On Tue, 12 Oct 2004, John Goerzen wrote: One of the best features of OO programming is that of inheritance. It can be used to slightly alter the behavior of objects without requiring modification to existing code or breaking compatibility with existing APIs. I hesitate to express a contrary

Re: [Haskell-cafe] Re: [Haskell] lazy constructors

2004-10-13 Thread Ben Rudiak-Gould
Serge D. Mechveliani wrote: As the types are resolved before the computation, as the above program shows, how can addToSPair expect anything besides a string pair? Why tilda is not a default? Haskell pairs are lifted, meaning that they also include an extra value (bottom) which doesn't match

Re: [Haskell-cafe] OO idioms redux

2004-10-17 Thread Ben Rudiak-Gould
John Goerzen wrote: I'm not sure I understand what you mean by containment and delegation -- could you elaborate? This means that instead of inheriting all the member functions of the base class and selectively overriding them, you store an object of the base class as a member of the derived

Re: [Haskell-cafe] Re: OCaml list sees abysmalLanguage Shootoutresults

2004-10-08 Thread Ben Rudiak-Gould
On Fri, 8 Oct 2004, Marcin 'Qrczak' Kowalczyk wrote: If the representation of some lists was changed, it would complicate all code which works on lists. Or maybe only polymorphic code, but it's still much. I don't believe it would be practical. That's true in OCaml but not in the STG-machine,

Re: [Haskell-cafe] Stream processors

2004-10-21 Thread Ben Rudiak-Gould
Peter Simons wrote: type Buffer = (Ptr Word8, Int) data StreamProc ctx a = SP { start :: IO ctx , feed :: ctx - Buffer - IO ctx , commit :: ctx - IO a } Must contexts be used in a single-threaded manner? If so, I would expect this interface: start :: IO ctx

Re: [Haskell-cafe] Re: Stream processors

2004-10-21 Thread Ben Rudiak-Gould
Peter Simons wrote: Ben Rudiak-Gould writes: Must contexts be used in a single-threaded manner? If so, I would expect this interface: start :: IO ctx feed :: ctx - Buffer - IO () commit :: ctx - IO a 'feed' cannot have this signature because it needs to update

Re: [Haskell-cafe] hugs segmentation fault

2004-10-28 Thread Ben Rudiak-Gould
Jon Fairbairn wrote: In ghci you get: [1*** Exception: loop which is better. Not much better, though: in my experience this particular exception leaves ghci in a very peculiar state, and it's usually necessary to quit and restart it before it will work again. Is it coincidence that both Hugs

Re: [Haskell-cafe] hugs segmentation fault

2004-10-28 Thread Ben Rudiak-Gould
Jon Fairbairn wrote: On 2004-10-29 at 00:03BST Ben Rudiak-Gould wrote: Not much better, though: in my experience this particular exception leaves ghci in a very peculiar state, and it's usually necessary to quit and restart it before it will work again. I don't think I've seen such a problem

Re: [Haskell-cafe] Set of reals...?

2004-10-29 Thread Ben Rudiak-Gould
MR K P SCHUPKE wrote: | otherwise = contractSet (contract x0 y0:xs) ys I think you'll find the original is correct. The first two cases deal with non-overlapping ranges. The only remaining case is overlapping ranges, (partial and full overlap) both these cases are dealt with by contract, and

Re: [Haskell-cafe] Set of reals...?

2004-10-29 Thread Ben Rudiak-Gould
Keith Wansbrough wrote: Which brings me to a question: is there a better way to write -inf and +inf in Haskell than -1/0 and 1/0? Shouldn't (minBound :: Double) and (maxBound :: Double) work? They don't, but shouldn't they? -- Ben ___ Haskell-Cafe

Re: [Haskell-cafe] Newbie Question on type constructors

2004-11-01 Thread Ben Rudiak-Gould
Brian Beckman wrote: data Shape = Circle Float | Square Float I read this something along the lines of 'Shape' is a type constructor, for use in other type-defining expressions, and 'Circle' and 'Sqare' are its two data constructors, which should be used like functions of type 'Float -

Re: [Haskell-cafe] Newbie Question on type constructors

2004-11-01 Thread Ben Rudiak-Gould
Paul Hudak wrote: Oh, I disagree with this point of view. Circle is certainly a value, i.e. a full-fledged function, as Brian Beckman correctly surmised. Interesting. I don't claim that my viewpoint is the One True Path, but I don't think it's wrong, either. I know you're interested in the

Re: [Haskell-cafe] Newbie Question on type constructors

2004-11-01 Thread Ben Rudiak-Gould
Keith Wansbrough wrote: Indeed, they are functions. Another way of thinking about it is as an initial algebra (technical term). What this means is this: Shape is a set of values that contains - the result of Circle x for all values x :: Float - the result of Square x for all

Re: [Haskell-cafe] Newbie Question on type constructors

2004-11-01 Thread Ben Rudiak-Gould
Paul Hudak wrote: Ben Rudiak-Gould wrote: Have I succeeded in reconciling our views? Perhaps! In particular, perhaps it's just a pedagogical issue. I'm interested in it mainly from a pedagogical perspective, yes. Note that instead of: data Shape = Circle Float | Square Float

Re: [Haskell-cafe] Newbie Question on type constructors

2004-11-01 Thread Ben Rudiak-Gould
Benjamin Franksen wrote: Because, hmmm, isn't it rather *one* destructor with type destructShape :: Shape - (Double - t) - (Double - t) - t where the second and third arguments explain what to do with a Circle resp. a Square? So that case s of Circle r - f r Square l -

Re: [Haskell-cafe] Re: Double - CDouble, realToFrac doesn't work

2004-11-05 Thread Ben Rudiak-Gould
Henning Thielemann wrote: I wonder why Infinity has a sign in IEEE floating processing, as well as 0. To support this behaviour uniformly one would need a +0 or -0 offset for each number, which would lead straightforward to non-standard analysis ... See Branch Cuts for Complex Elementary

Re: [Haskell-cafe] Global Variables and IO initializers

2004-11-08 Thread Ben Rudiak-Gould
I think the broad issue is that there are many different levels of the system at which something can be global: a module, a thread, a process, a user, a computer, a network segment, the internet, the universe, etc.. If your model of a concept is more global than the concept itself, you lose

Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-11 Thread Ben Rudiak-Gould
Graham Klyne wrote: Wouldn't it be easier to simply define once as a common Haskell library function? Depends on the type and the expected semantics. As Adrian Hey already pointed out, (once :: IO a - IO a) with the obvious semantics is never going to be safe, because it's just not the case

Re: [Haskell-cafe] IO and State

2004-11-11 Thread Ben Rudiak-Gould
Iavor S. Diatchki wrote: In GHC the whole program stops when the main thread exits. So if the law I was talking about holds, this program should never terminate, as it will forever loop in 'reader'. However since there is a concurrent thread running that can modify the state, if 'reader' is

Re: [Haskell-cafe] Space efficiency problem

2004-11-12 Thread Ben Rudiak-Gould
Adrian Victor CRISCIU wrote: Thanks for the advice. However, though I don't know how ghc manages the heap, I am not sure it is possible to achieve constant heap usage, because a value of type State is a function, and = is creating a call stack in this case. I mean, I think that, even if the

Re: [Haskell-cafe] IO and State

2004-11-12 Thread Ben Rudiak-Gould
Iavor S. Diatchki wrote: Ben Rudiak-Gould wrote: I would say that the law holds in one direction and not the other. [...] How can things be equal the one way and not the other? Saying that two things are equal means (in this context) that either can be replaced by the other without changing

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Ben Rudiak-Gould
Keean Schupke wrote: At the risk of getting off topic... the reason 'C' has printf is because it is not polymorphic. Printf is a hack to allow different types to be printed out, such that they did not need printInt, printFloat etc. Many language have printf-like functions despite not satisfying

Re: [Haskell-cafe] Re: Global Variables and IO initializers

2004-11-24 Thread Ben Rudiak-Gould
Benjamin Franksen wrote: label1 = unique Uniq1 label2 = unique Uniq2 global1 = functionalNewMVar label1 True global2 = functionalNewMVar label1 (117::Int) No dice. Your example inadvertently shows why: you used label1 when creating both global1 and global2, and now I can write

Re: [Haskell-cafe] Re: Global Variables and IO initializers

2004-11-24 Thread Ben Rudiak-Gould
Benjamin Franksen wrote: My god, what a stupid mistake. I should just give it up... :-( Funny you should say that, because I made the same mistake two weeks ago and felt the same way: http://www.haskell.org/pipermail/haskell-cafe/2004-November/007556.html Live and learn... -- Ben

Re: [Haskell-cafe] Re: not possible with monad transformers ?

2004-11-30 Thread Ben Rudiak-Gould
Jules Bean wrote: However, your problem *does* have a natural underlying monad, if you care to use it. I may be confused, but I don't think it does. It seems like the OP wants a type like data Perhaps a = Success a | Failure [Error] and semantics like liftM2 (+) (Failure [error1])

[Haskell-cafe] Top-level state debate on the wiki

2004-12-01 Thread Ben Rudiak-Gould
I put up a wiki page summarizing the main proposals for top-level mutable state. The type-dictionary approach isn't there yet, but there's a space for it; I'll probably fill it in within the next 24 hours unless someone else feels like doing it first. Please add more detail, objections,

Re: [Haskell-cafe] Top-level state debate on the wiki

2004-12-02 Thread Ben Rudiak-Gould
Keean Schupke wrote: Ben Rudiak-Gould wrote: [...] Just a small comment on the Wiki page... it says Several real-life examples of pure haskell code which needs fast global variables to either be implemented efficiently or statically guarantee their invariants are given in http://www.haskell.org

Re: [Haskell-cafe] Mutable data design question

2004-12-03 Thread Ben Rudiak-Gould
GoldPython wrote: In the case of writing something like a text editor where the data involved is by its very nature mutable, what sort of design paradigm would you use in a functional language? I wouldn't say that textual data is by its nature mutable. That's just the imperative way of looking at

Re: [Haskell-cafe] Force evaluation

2004-12-06 Thread Ben Rudiak-Gould
Michael Walter wrote: PS: Ooops, posted this to haskell-ml first. Actually I think your question is more appropriate to haskell than to haskell-cafe. If it balloons into a huge discussion then it can move here. -- Ben ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Non-technical Haskell question

2004-12-06 Thread Ben Rudiak-Gould
[EMAIL PROTECTED] wrote: When I use javac every file that is created is necessary for the application to run. This can't be said of the ghc compiler. Having an excuse that this is way the C compiler does it or that this is the way its always been done is to poor of a reason to even argue against.

Re: [Haskell-cafe] Re: Non-technical Haskell question

2004-12-06 Thread Ben Rudiak-Gould
Philippa Cowderoy wrote: The strip utility helps somewhat, I just dropped a wxHaskell app from a 10 meg .exe to about 3.6 megs under windows. You can also compress the stripped executable with UPX. GHC-generated executables seem to compress very well (about 4:1 in my experience), and even a very

Re: [Haskell-cafe] Re: Non-technical Haskell question

2004-12-07 Thread Ben Rudiak-Gould
John Goerzen wrote: On Tue, Dec 07, 2004 at 12:43:27PM +0100, Lennart Augustsson wrote: Yay! :) Dynamically linked libraries are slower than statically linked ones in just about every implementation I know of. I don't care. My understanding was that this was mostly limited to x86 platforms.

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Ben Rudiak-Gould
GoldPython wrote: I know there's length to count the elements in a list and it works fine, but the function below stack overflows on a large list. countLines [] = 0 countLines (_:ls) = 1 + countLines ls I would have thought that this was tail recursive and would be flattened into iteration by

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Ben Rudiak-Gould
Jules Bean wrote: On 10 Dec 2004, at 15:34, Robert Dockins wrote: So it should get flattened, but it still doesn't run in constant space because the x parmeter isn't strict, so it will accumulate a bunch of closures like (((0)+1)+1)+1)+1)+1) To make it strict, do something like this:

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Ben Rudiak-Gould
Georg Martius wrote: It was allready posted before, that you need to enforce the evaluation of the + in order to get the function run in constant space. The thing is, that it is harder to achieve than I expected it to be. countLines' ls = foldl (\x y - let x' = x + 1 in x' `seq` y `seq` x' ) 0

Re: [Haskell-cafe] The difference between ($) and application

2004-12-14 Thread Ben Rudiak-Gould
Derek Elkins wrote: Andrew Pimlott wrote: I think this post should go under the heading ($) considered harmful. I've been bitten by this, and I never use ($) anymore in place of parentheses because it's too tempting to think of it as syntax. I find this position ridiculous. [...] If you ever make

Re: [Haskell-cafe] Seeking comments on this IO proposal

2004-12-16 Thread Ben Rudiak-Gould
John Goerzen wrote: My proposal is here: http://www.complete.org/~jgoerzen/t/MissingH.IO.HVIO.html I'm aware that others have been working on IO proposals; specifically, Simon Marlow's here: http://www.haskell.org/~simonmar/io/System.IO.html The proposal on Simon M's page was originally my

Re: [Haskell-cafe] Parse text difficulty

2004-12-10 Thread Ben Rudiak-Gould
Henning Thielemann wrote: I try to stay away from list comprehension because I can't memorize in which order the conditions are processed [...] I remember it as being slowest-changing-to-the-left, just like the positional notation for integers. E.g. [[x,y] | x - ['1'..'4'], y - ['0'..'9']]

Re: [Haskell-cafe] FFI woes!

2004-12-16 Thread Ben Rudiak-Gould
Sebastian Sylvan wrote: If there was a way to simply defer GC (like you attatch a function to an object which can simply deny the GC the right to remove it depending on its state) then I wouldn't have to do anything significant in the finalizer. Why not spawn a thread which starts the playback,

Re: [Haskell-cafe] FFI woes!

2004-12-16 Thread Ben Rudiak-Gould
Sebastian Sylvan wrote: Ben Rudiak-Gould wrote: Why not spawn a thread which starts the playback, waits for it to finish, and then exits, and wrap the whole thread in a call to withForeignPtr? Then your finalizer won't be called prematurely. Well I could do this, but for one it would

Re: [Haskell-cafe] Why no IO transformer monad?

2004-12-20 Thread Ben Rudiak-Gould
Ross Paterson wrote: But IO is not ST RealWorld (even if GHC pretends it is): other users of the world are not waiting for the new world produced by your Haskell program. They're *part* of the world. IO = State RealWorld makes sense if you think of RealWorld as encapsulating the entire state of

Re: [Haskell-cafe] Re: Hugs vs GHC (again) was: Re: Some randomnewbiequestions

2005-01-10 Thread Ben Rudiak-Gould
Andre Pang wrote: Is there a Wiki page or URL with the steram proposal? It's here: http://www.haskell.org/~simonmar/io/System.IO.html -- Ben ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: Hugs vs GHC (again) was: Re: Some randomnewbiequestions

2005-01-11 Thread Ben Rudiak-Gould
Marcin 'Qrczak' Kowalczyk wrote: fileRead :: File - FileOffset - Integer - Buffer - IO () This is unimplementable safely if the descriptor is read concurrently by different processes. The current position is shared. ... which is terrible library design, which we should avoid if at all possible,

[Haskell-cafe] Re: I/O interface

2005-01-11 Thread Ben Rudiak-Gould
Marcin 'Qrczak' Kowalczyk wrote: Ben Rudiak-Gould [EMAIL PROTECTED] writes: fileRead can be implemented in terms of OS primitives, Only if they already support reading from a fixed offset (like pread). I'm not sure if we can rely on something like this being always available, or whether it should

Re: [Haskell-cafe] Re: I/O interface

2005-01-12 Thread Ben Rudiak-Gould
Marcin 'Qrczak' Kowalczyk wrote: Ben Rudiak-Gould [EMAIL PROTECTED] writes: The file interface in this library is only used for files, which are always seekable (by definition). What do you mean by files? What you get from open() is not always seekable [...] This was all discussed a year ago

Re: [Haskell-cafe] Re: I/O interface

2005-01-12 Thread Ben Rudiak-Gould
Simon Marlow wrote: I assumed that dup()'ing file descriptors would be enough to produce separate file pointers, but no. Question (for qrczak or the group at large): is there *any* way to get, without an exploitable race condition, two filehandles to the same file which don't share a file

Re: [Haskell-cafe] Re: Hugs vs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-12 Thread Ben Rudiak-Gould
Marcin 'Qrczak' Kowalczyk wrote: File positions are not evil. They allow to treat files and devices in a uniform way. Indeed, file positions are exactly as evil as indices into shared memory arrays, which is to say not evil at all. But suppose each shared memory array came with a shared current

Re: [Haskell-cafe] Linear shuffle

2005-01-15 Thread Ben Rudiak-Gould
Marcin 'Qrczak' Kowalczyk wrote: Henning Thielemann [EMAIL PROTECTED] writes: I did some shuffling based on mergesort [...] I think it doesn't guarantee equal probabilities of all permutations. It doesn't (proof: it has a bounded runtime, which can't be true of a perfect shuffling algorithm

Re: [Haskell-cafe] Linear shuffle

2005-01-15 Thread Ben Rudiak-Gould
Scott Turner wrote: Analogous to quicksort's bad behavior in the worst case, an invocation of 'partition' is not guaranteed to make any progress with the shuffling, because one of the output lists might receive all of the input items. It's worse than quicksort, because there's no guarantee that

Re: [Haskell-cafe] Re: Hugs vs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-17 Thread Ben Rudiak-Gould
John Meacham wrote: Actually, If I were writing new haskell libraries, I would use mmap whenever I could for accessing files. not only does it make the file pointer problem go away, but it can be drastically more efficient. I'm not sure this is a good idea, because GHC really needs non-blocking

Re: [Haskell-cafe] I/O interface

2005-01-17 Thread Ben Rudiak-Gould
Marcin 'Qrczak' Kowalczyk wrote: Convenience. I'm worried that it uses separate types for various kinds of streams: files, pipes, arrays (private memory), and sockets. Haskell is statically typed and lacks subsumption. This means that even though streams are unified by using a class, code which

Re: [Haskell-cafe] performance question

2005-01-17 Thread Ben Rudiak-Gould
Stijn De Saeger wrote: data Bound = I Double | E Double deriving (Eq, Show, Ord) data Interval = Il Bound Bound | Nil Bound Bound deriving (Eq,Ord) isIn :: Double - Interval - Bool isIn r (Nil x y) = not (isIn r (Il x y)) isIn r (Il (I x) (I y)) = r = x r = y isIn r (Il (I x) (E y)) = r = x

Re: [Haskell-cafe] Re: Top Level etc.

2005-01-20 Thread Ben Rudiak-Gould
Jim Apple wrote: Does anyone have examples of these? This one scares the foo out of me: * It's not even safe in general to add a signature giving the same type that the compiler would infer anyway Here's an example: len :: [a] - Int len xs = let ?accum = 0 in len' xs len'

Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-20 Thread Ben Rudiak-Gould
Glynn Clements wrote: Keean Schupke wrote: Why is disk a special case? With slow streams, where there may be an indefinite delay before the data is available, you can use non-blocking I/O, asynchronous I/O, select(), poll() etc to determine if the data is available. [...] With files or block

[Haskell-cafe] Re: Existentials and type var escaping

2007-06-11 Thread Ben Rudiak-Gould
Roberto Zunino wrote: foo, as defined above does not work (lazy patterns not allowed), and in foo y = E (case y of E x - x) a variable escapes. I also tried with CPS with no success. Is foo definable at all? I'm starting to think that it is not, and that there must be a very good reason for