Re: [Haskell-cafe] IDE?

2007-06-18 Thread Jules Bean
peterv wrote: I just tried the Haskell Mode using xemacs, adjust my init.el file, loaded my haskell file, and got great syntax highlighting! So far so good. But people, emacs is so weird for a Windows user... Well you're certainly quite right to observe that emacs keys are rather differ

Re: [Haskell-cafe] Head and tail matching question

2007-06-11 Thread Jules Bean
Olivier Boudry wrote: Hi all, I'm trying to write a untab function that would split a string on tabs and return a list. Code is here. import Data.List (break, unfoldr) import Data.Char (String) untab :: String -> [String] untab s = unfoldr untab' s untab' :: String -> Maybe (String, String) u

Re: [Haskell-cafe] Just for a laugh...

2007-06-01 Thread Jules Bean
Donald Bruce Stewart wrote: > let s = encode (1.1 :: Float) > :t s s :: Data.ByteString.Lazy.ByteString > s LPS ["\NUL\NUL\140\204\205\255\255\255\255\255\255\255\233"] > decode s :: Float 1.1 But doesn't Data.Binary serialise to a guaranteed representation, i.e. m

Re: [Haskell-cafe] Re: Has anyone looked into adding subtyping to Haskell?

2007-05-31 Thread Jules Bean
apfelmus wrote: Al Falloon wrote: OCaml has been getting a lot of mileage from its polymorphic variants (which allow structural subtyping on sum types) especially on problems relating to AST transformations and the infamous "expression problem". Has there been any work on extending Haskell's ty

Re: [Haskell-cafe] Language extensions

2007-05-31 Thread Jules Bean
Roberto Zunino wrote: Ah, silly me! I checked that inequality was preserved, but forgot that (==) diverges on infinite list! Indeed, strictly speaking, Eq [] does not satisfy the Eq invariant x==x. All haskell types contain divergence. So all Eq types have exactly this same problem. We 'li

Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Jules Bean
Andrew Coppin wrote: My point is for most programs, trying to figure out exactly what you want the program to do is going to be much harder than implementing a program that does it. Also, for most programs the spec is far more complicated (and hence prone to error) than the actual program, so

Re: [Haskell-cafe] New book: Real-World Haskell!

2007-05-29 Thread Jules Bean
Doug Kirk wrote: No offense to the darcs creators, but 1) Only current Haskellers use it; everyone else either uses Subversion or is migrating to it; If that is true, then they have missed the point. DVC is a real win for most workflows. The applicable alternatives to darcs are : bzr, git,

Re: [Haskell-cafe] Re: Network.HTTP+ByteStrings Interface--Or: How to shepherd handles and go with the flow at the same time?

2007-05-26 Thread Jules Bean
Pete Kazmier wrote: Jules Bean <[EMAIL PROTECTED]> writes: E,F. Progressive GET pSynGET :: URL -> ((Bool,ByteString) -> IO ()) -> IO () pAsynGET :: URL -> ((Bool,ByteString) -> IO ()) -> IO (MVar ()) Incidentally there are more complex options than (Bo

Re: [Haskell-cafe] Network.HTTP+ByteStrings Interface--Or: How to shepherd handles and go with the flow at the same time?

2007-05-24 Thread Jules Bean
I've been having something of a discussion on #haskell about this but I had to go off-line and, in any case, it's a complicated issue, and I may be able to be more clear in an email. The key point under discussion was what kind of interface the HTTP library should expose: synchronous, asynchronou

Re: [Haskell-cafe] Re: Editor

2007-05-22 Thread Jules Bean
Michael T. Richter wrote: On Tue, 2007-22-05 at 10:19 +0200, apfelmus wrote: I can't know whether that's the case, but the fact that virtually all commands are invoked with the keyboard clashes with HID research reported at http://www.asktog.com/TOI/toi06KeyboardVMouse1.html It adresses the

Re: [Haskell-cafe] Re: Editor

2007-05-22 Thread Jules Bean
apfelmus wrote: I can't know whether that's the case, but the fact that virtually all commands are invoked with the keyboard clashes with HID research reported at http://www.asktog.com/TOI/toi06KeyboardVMouse1.html It adresses the question whether selecting commands in menus with the mouse o

Re: [Haskell-cafe] List algorithm

2007-05-21 Thread Jules Bean
Matthew Brecknell wrote: This seems to work, but presumably only because it's a boxed array, and the construction makes no circular references. Yes, AIUI the boxed arrays are strict in indices but lazy in values. Therefore they can be used for this kind of memoization trick as long as you're

Re: [Haskell-cafe] Editor OT: streamofconciousness

2007-05-21 Thread Jules Bean
John Meacham wrote: It is somewhat depressing that immutable pre-packaged macros[1] and the simple brute-force inclusion of separate tools[2] into the editor are hailed as innovation, when new innovations, whether they are simple refinements of old ideas[3], excercises in orthoginality[4], or tr

Re: [Haskell-cafe] how can I select all the 3-element-combination out of a list efficiently

2007-05-21 Thread Jules Bean
[EMAIL PROTECTED] wrote: Then you want "triples1" from the code below. The idea for triples1, triples2, and triples3 is that each pickOne returns a list of pairs. The first element of each pair is the chosen element and the second element of each pair is the list of choices for the next element

Re: [Haskell-cafe] Editor

2007-05-21 Thread Jules Bean
Michael T. Richter wrote: I have a dream. It's not a little dream. It's a big dream. I have a dream that someday I can find a UNIX/Linux text editor for Haskell hacking (and possibly two or three hundred other programming languages, although that's optional) that can give me all of the follo

Re: [Haskell-cafe] global variables

2007-05-20 Thread Jules Bean
Adrian Hey wrote: Jules Bean wrote: I've pretty much convinced it's wrong. There should be one and only one "main" from which all subsequent IO activity derives. But creating internal state in the form of mutable data structures is not an IO activity. It just so happens th

Re: [Haskell-cafe] how can I select all the 3-element-combination out of a list efficiently

2007-05-20 Thread Jules Bean
geniusfat wrote: hi dear haskell lover ;) what I want to do is simply this: select3 :: [a] -> [(a, a, a)] and how can it be done efficiently? thanks in advance! Oh, hang on. I just read your subject line. Do you really mean all the 3-elem combinations? that's much easier: Prelude> let l =

Re: [Haskell-cafe] how can I select all the 3-element-combination out of a list efficiently

2007-05-20 Thread Jules Bean
geniusfat wrote: hi dear haskell lover ;) what I want to do is simply this: select3 :: [a] -> [(a, a, a)] and how can it be done efficiently? thanks in advance! If, given [1,2,3,4,5,6,7,8,9,10,11,12] you want [(1,2,3),(4,5,6),(7,8,9)] then: map (take 3) . iterate (drop 3) is very nearl

Re: [Haskell-cafe] global variables

2007-05-18 Thread Jules Bean
[I agree with your points, but...] Adrian Hey wrote: I've pretty much convinced it's wrong. There should be one and only one "main" from which all subsequent IO activity derives. But creating internal state in the form of mutable data structures is not an IO activity. It just so happens that at

Re: [Haskell-cafe] writer monad help

2007-05-18 Thread Jules Bean
iskaldur wrote: I'm trying to learn to use the Writer Monad, but I'm having trouble with the following very simple program: import Control.Monad.Writer foo :: Writer String Int foo = tell "hello" Basically, I was trying to figure out the 'tell' function, so I want foo to return ((), "hello").

[Haskell-cafe] Debunking tail recursion

2007-05-18 Thread Jules Bean
A conversation on #haskell just showed that it's quite hard to explain (at least it is for me) to people attached to tail recursion why that is a red herring in Haskell. I had a poke around the wiki and couldn't see a page which explains it clearly. In fact http://www.haskell.org/haskellwiki/

Re: [Haskell-cafe] global variables

2007-05-17 Thread Jules Bean
Adrian Hey wrote: We've been talking about this problem for years, but nothing is ever done about it (a solution to this problem isn't even on the agenda for Haskell' AFIAK). The problem needs talking about, it's important. My objection was the implication that top-level mutable state was the

Re: [Haskell-cafe] global variables

2007-05-17 Thread Jules Bean
Please take this message in the fashion that is intended. My criticism is light hearted, as I believe yours is. Adrian Hey wrote: [hack snipped] BTW, this is the commonly the subject of flame wars on the Haskell mailing lists because there appear to be many who passionately believe and assert

Re: [Haskell-cafe] global variables

2007-05-17 Thread Jules Bean
Eric wrote: H|i, Does anyone know of a simple and straightforward way to use global variables in Haskell? (Perhaps annoyingly) the answer to this question, like so many other questions on this list, is a question. "What are you trying to do?". The reason for this is that haskell's abstract

Re: [Haskell-cafe] haskell quiry

2007-05-17 Thread Jules Bean
ashutosh dimri wrote: func [] = [] func (x:xs) |(ord x > 57) = ((ord x)-87):func xs |otherwise = ((ord x)-48):func xs Your problem is with the type of 'func'. *Main> :t func func :: [Char] -> [Int] 'Int' is a 32-bit type, on most systems. The thing that has forced your type to I

Re: [Haskell-cafe] Tail Recursion within the IO Monad

2007-05-16 Thread Jules Bean
Rob Hoelz wrote: item <- linked_list_getdata listPtr next <- linked_list_next listPtr cStr <- peek item hStr <- peekCString cStr t <- linkedListToStringList next return (hStr : t) item <- linked_list_getdata listPtr next <-

Re: [Haskell-cafe] reversing big list with constant heap space used

2007-05-16 Thread Jules Bean
David House wrote: On 16/05/07, Sergey Perminov <[EMAIL PROTECTED]> wrote: How to solve task of reversing big list with constant heap space used? I think that as lists are singly-linked in Haskell, reversing a list will always be O(n) space. You can do it in O(n^2) time and constant space,

Re: [Haskell-cafe] Re: The danger of Monad ((->) r)

2007-05-16 Thread Jules Bean
Tomasz Zielonka wrote: On Wed, May 16, 2007 at 09:28:31AM +0100, Jules Bean wrote: Tomasz Zielonka wrote: You mean using the (Monoid b) => Monoid (a -> b) instance ? I can see that IO () makes a perfect Monoid, but there doesn't seem to be a standard instance for that.

Re: [Haskell-cafe] Re: The danger of Monad ((->) r)

2007-05-16 Thread Jules Bean
Tomasz Zielonka wrote: On Tue, May 15, 2007 at 06:55:11AM -0700, Conal Elliott wrote: You could also use mappend instead of concatStmts and keep the Database -> IO () representation.- Conal You mean using the (Monoid b) => Monoid (a -> b) instance ? I can see that IO () makes a per

Re: [Haskell-cafe] openBinaryFile

2007-05-15 Thread Jules Bean
Eric wrote: Hello all, Does anyone have some sample code for reading and writing to binary files? openBinaryFile is a bit of a red herring. All it does is disable the line-ending interpretation which may or may not happen on some OSes when you open a file in text mode. For simple binary

Re: [Haskell-cafe] The danger of not specifying types (was The danger of Monad ((->) r))

2007-05-15 Thread Jules Bean
Tomasz Zielonka wrote: My mistake was that I forgot about db and wrote: concatStmts s1 s2 = s1 >> s2 And it was accepted because I had the Monad instance for ((->) r) in scope (from Control.Monad.Trans I guess)! The danger in overloading is that you are relying on the compiler to infe

Re: [Haskell-cafe] Code layout in Emacs' haskell-mode

2007-05-15 Thread Jules Bean
Christopher L Conway wrote: I've installed 2.3 and it exhibits the same indentation behavior: any entity appearing on a new line immediately after "module X where" wants to be indented 4 spaces, including function definitions and variable bindings. Yes, it does do that. And it's correct syntax

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Jules Bean
Christopher L Conway wrote: The inference assigns y the type (t1 -> t1) even though it is assigned the value 3? Yes, because type classes are open, and maybe you will demonstrate some way to make t1->t1 an instance of Num. Note the Num (t1 -> t1) constraint in the type...

Re: [Haskell-cafe] Lazy HTML parsing with HXT, HaXML/polyparse, what else?

2007-05-11 Thread Jules Bean
Henning Thielemann wrote: I want to parse and process HTML lazily. I use HXT because the HTML parser is very liberal. However it uses Parsec and is thus strict. HaXML has a so called lazy parser, but it is not what I consider lazy: *Text.XML.HaXml.Html.ParseLazy> Text.XML.HaXml.Pretty.document $

Re: [Haskell-cafe] Limits of deduction

2007-05-11 Thread Jules Bean
Andrew Coppin wrote: There are many possible variations - length examines the whole list, but not the elements *in* the list. null does less than that. And so on. I'm sure there are many possible combinations. What I'm wondering is if it's possible to algorithmically decide which class of fun

Re: [Haskell-cafe] Monad pronounced like gonad?

2007-05-11 Thread Jules Bean
[If I sound definitive below, it's because I am stating facts; but they are facts about the community of mathematicians and computer scientists I have interacted with in person. I'm sure other physically-connected communities have adopted different conventions] Dan Piponi wrote: A more pressi

Re: [Haskell-cafe] Debugging

2007-05-10 Thread Jules Bean
Joel Reymont wrote: On May 10, 2007, at 10:19 AM, Jules Bean wrote: The 'next step' is to move from testing by hand in ghci to writing quickcheck properties / smallcheck / unit tests for the functions. I still don't understand the difference between QC and SC. Would someone

Re: [Haskell-cafe] Debugging

2007-05-10 Thread Jules Bean
Ryan Dickie wrote: I've only written trivial applications and functions in haskell. But the title of this thread got me thinking. In an imperative language you have clear steps, states, variables to watch, etc. What techniques/strategies might one use for a functional language? Well, bre

Re: Re [Haskell-cafe] Vanishing polymorphism

2007-05-09 Thread Jules Bean
David House wrote: On 08/05/07, Matthew Sackman <[EMAIL PROTECTED]> wrote: > :t let f r s = let g (fn::forall n . (Num n) => n -> n) = return (fn r, fn s) in (return negate) >>= g in f Ah, I may have been off the mark earlier. I think the problem is due to the fact that you can't pass higher-o

Re: [Haskell-cafe] Displaying infered type signature of 'offside' functions

2007-05-02 Thread Jules Bean
Simon Peyton-Jones wrote: | I like the strong static type system of Haskell for various | reasons. One reason is, that it makes easier to understand new | code. I.e. when I read code I type ':t foo' in ghci/hugs from | time to time, to check my own idea of the type signature, if it | is not inclu

Re: [Haskell-cafe] Writing guards shorthand

2007-04-19 Thread Jules Bean
Joel Reymont wrote: This is what want. Notice the succinctness. # let infer = function | A | B | C -> true; | D | E | F -> false;; val infer : foo -> bool = Yes, I appreciate what you want, and I know ocaml too :) I was just talking around the other ways you can achieve it. I don't kno

Re: [Haskell-cafe] Writing guards shorthand

2007-04-19 Thread Jules Bean
Neil Mitchell wrote: Hi isBool x = isLT x || isGT x isNum x = not $ isBool x isLT and isGT can be derived automatically using derve [1], with the Is class (or DrIFT if you want). You can also get a long way with GHC's built in derivations for Eq, Enum and Show. If an Enum instance is poss

Re: [Haskell-cafe] Writing guards shorthand

2007-04-19 Thread Jules Bean
Joel Reymont wrote: Support I want to infer the type given an Op that looks like this (incomplete): data Op = Minus | Plus | Mul | LT | GT Is there a shorthand way of bunching Minus, Plus and Mul in a function guard since they all result in TyNum whereas the rest in TyBool

Re: [Haskell-cafe] question about Data.Binary and Double instance

2007-04-19 Thread Jules Bean
Duncan Coutts wrote: Yeah, we've concentrated so far on the serialisation of Haskell values, not reading/writing externally defined binary formats. I don't think we've been especially clear on that. But we do intend to tackle both. Speaking for myself, I certainly didn't realise you were i

[Haskell-cafe] Type classes to 'reflect' constructor structure

2007-04-05 Thread Jules Bean
In the thread 'automatic derivation', Joel Reymont is looking for metaprogramming functionality with which he wants to automatically derive a parser and a pretty printer for his ADT (which is an AST for a minilanguage). I replied showing that a significant amount of the boilerplate could be r

Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Jules Bean
Jules Bean wrote: data paramType = JNum | JBool | JStr paramParser JNum = numExpr paramParser JBool = boolExpr paramParser JStr = strExpr unary x pt = reserved (quasiShow (x undefined)) >> parens (paramParser pt) >>= return . x strCall = choice ( map unary [ELDateToString,T

Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Jules Bean
Joel Reymont wrote: Folks, I have very uniform Parsec code like this and I'm wondering if I can derive it using TemplateHaskell or DrIFT or some other tool. Any ideas? Others have given good answers on how to use code-generation. I am more interested in whether code generation is actually ne

Re: [Haskell-cafe] cost of modules

2007-03-29 Thread Jules Bean
Fawzi Mohamed wrote: good to know, and very important when benchmarking various algorithms: commenting out a variant is better as having it as separate function Yes, but don't get over-paranoid. The 'overhead' of calling as opposed to inlining is relatively small, and only matters if the f

Re: [Haskell-cafe] (newbie) instance Enum MyType where, smarter way?

2007-03-27 Thread Jules Bean
Adrian Neumann wrote: I defined an enumeration datatype like this data MyType = One | Two | Four | Eight and want to make it an instance of the class Enum. deriving Enum won't do what I want, as it labels the items 0,1,2,3. Is there a better way to do this than Define them as deriving Enum. N

Re: [Haskell-cafe] How do I do conditional tail recursion in a monad?

2007-03-21 Thread Jules Bean
David F. Place wrote: So, the next question is: Why isn't this already in Control.Monad? Some people have proposed it. Part of the reason is all the possible variations (monadic action, monadic test, monadic filter, etc etc), and it's all really very easy to write yourself. Perhaps it's e

Re: [Haskell-cafe] How do I do conditional tail recursion in a monad?

2007-03-21 Thread Jules Bean
return x else do y <- f x untilM p f y On Mar 21, 2007, at 5:31 AM, Jules Bean wrote: ..but here 'f' is a pure function, not a monadic action. If you want f to be a monadic action then you want: *Main> :t let untilM p f x = if p x then return x else untilM p f

Re: [Haskell-cafe] How do I do conditional tail recursion in a monad?

2007-03-21 Thread Jules Bean
DavidA wrote: So I figure untilM should look something like: untilM :: Monad m => (a -> Bool) -> (a -> m a) -> a -> m a untilM p f x = return (if p x then x else untilM p f (f x)) The problem is that the two branches of the conditional have different types. If I try to remedy that by changing "t

Re: [Hs-Generics] FW: [Haskell-cafe] SYB vs HList (again)

2007-03-21 Thread Jules Bean
S. Alexander Jacobson wrote: Conceptually, I think what I really want is the data structure equivalent of type inference. Just as I don't want to be forced to declare my function types, I don't want to be forced to declare my data types. The field labels I use should be enough to define the

Re: [Haskell-cafe] Newbie vs. laziness

2007-03-20 Thread Jules Bean
Alex Queiroz wrote: However that's a bit clumsy. What kind of error are you seeing when you say 'it crashes'? I must fetch all rows of the result, otherwise the database will be in an inconsistent state and all subsequent queries crash the application. Fetching all rows automatically fini

Re: [Haskell-cafe] Newbie vs. laziness

2007-03-20 Thread Jules Bean
Alex Queiroz wrote: quickQuery returns a lazy list of results, and I expected ($!) to make it strict. But my program crashes if I use it this way. But, if I add a print to the function: 'Making things strict' isn't that simple. What $! does is force its arguments into WHNF before applying the

Re: [Haskell-cafe] Re: wanted: haskell one-liners (in the perl sense of one-liners)

2007-03-20 Thread Jules Bean
Thomas Hartman wrote: To answer my own post, the Data.List.sort *is* necessary. Otherwise, you get alphabetic sort. Which is why you do the Set trick at a different stage in the process, like this: interact $ unlines . map show -- more efficient than -- reverse . take 10 . reverse . ( \

Re: [Haskell-cafe] flip fix and iterate

2007-03-20 Thread Jules Bean
Matthew Brecknell wrote: There is the question of whether it's preferable to use the "let" form or the "fix" form for embedding a recursive function in the middle of a do-block. I don't know if there's any consensus on this question, but it seems to me to be about whether one prefers to read a fu

Re: [Haskell-cafe] N and R are categories, no?

2007-03-16 Thread Jules Bean
Dominic Steinitz wrote: I haven't formally checked it, but I would bet that this endofunctor over N, called Sign, is a monad: Just to be picky a functor isn't a monad. A monad is a triple consisting of a functor and 2 natural transformations which make certain diagrams commute. Whi

Re: [Haskell-cafe] principle types

2007-03-14 Thread Jules Bean
Vikrant wrote: Hi, I can understand why principle type of map is map :: (a -> b) -> [a] -> [b] , I would interpret this as "map takes a function of type a->b and a list of type [a] as arguments and returns a list of type [b]" but it is going somewhat beyond my imagination why principle t

Re: [Haskell-cafe] Attachments on the List

2007-03-06 Thread Jules Bean
never execute code in an attachment without your express permission. Ultimately you need to be in control, otherwise a random junk mail author may catch you out. Jules Bean ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: process

2007-02-23 Thread Jules Bean
h. wrote: If it basically works, what goes wrong in my programm? Well that depends entirely what your program is supposed to do. Your email doesn't tell us (a) what your program was supposed to do or (b) what goes wrong. Therefore we are forced to guess! The following slight variation

Re: [Haskell-cafe] Re: Map list of functions over a single argument

2007-02-21 Thread Jules Bean
Gene A wrote: Well this is not very sexy, no monads or anything, but I kinda believe in Keep It Simple: Prelude> let revApply a f = f a Prelude> let rMap a fs = map (revApply a) fs Prelude> rMap 2 [(*4),(^2),(+12),(**0.5)] [8.0,4.0,14.0,1.4142135623730951] Note that revApply here is preci

Re: [Haskell-cafe] GHCi and multi-line support ?

2007-02-19 Thread Jules Bean
Dunric wrote: Is it possible to write multi-line definitions in GHC interactive interpreter ? (like in Python interp. ?) When I try to write f.E. if-then-else in more then 1 line I get the following error: :1:30: parse error (possibly incorrect indentation) It would be quite hard to do th

Re: [Haskell-cafe] Newbie Q: GH Ci: Where “List” module is imported f rom?

2007-02-16 Thread Jules Bean
Dmitri O.Kondratiev wrote: Where exactly "the Ord instance for lists is defined in the Prelude"? Depends slightly on your compiler, but you will find that some of the prelude has source, and some of the prelude is inevitably not written in haskell (the type system has to be bootstrapped som

Re: [Haskell-cafe] Newbie Q: GH Ci: Where “List” module is imported f rom?

2007-02-16 Thread Jules Bean
Dmitri O.Kondratiev wrote: "Set" module here is built with list and uses among other things list comparison functions such as (==) and (<=). Q1: Where "List" module is imported from? GHC "Base" package contains "Data.List" module, not just "List" module. List was the old name for it. Da

Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Jules Bean
Yitzchak Gale wrote: You need to use a more sophisticated algorithm - building up trees of potential matches, backtracking in some cases, etc. Why re-invent the wheel? Just use the regex library, where that is already done. It's merely a question of selecting the right wheel. Some problems ar

Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Jules Bean
tphyahoo wrote: So the core question (speaking as a perler) is how do you write my $s= 'abcdefg'; $s =~ s/a/z/g; $s =~ s/b/y/g; print "$s\n"; in haskell? There are various haskell regex libraries out there, But that's such a perler attitude. When all you have is a regex, everythi

Re: [Haskell-cafe] Parser question

2005-03-15 Thread Jules Bean
On 15 Mar 2005, at 12:38, Mark Carroll wrote: Variables (although why they're called that in Haskell I'm not sure) Because the value that they denote can vary between different calls of the same function? Jules ___ Haskell-Cafe mailing list Haskell-Cafe

Re: [Haskell-cafe] YAWQ (Yet Another Wash Question)

2005-02-24 Thread Jules Bean
On 24 Feb 2005, at 17:33, John Goerzen wrote: On Thu, Feb 24, 2005 at 05:22:40PM +, Jules Bean wrote: On 24 Feb 2005, at 16:42, John Goerzen wrote: ... do if cond then x <- textInputField ... else () ... submit ... Well, two problems there... first, the scope

Re: [Haskell-cafe] YAWQ (Yet Another Wash Question)

2005-02-24 Thread Jules Bean
On 24 Feb 2005, at 16:42, John Goerzen wrote: Thanks for everyone that's helped me out with my Wash questions. I have one more. I have a textInputField that I only want to display on a form in certain cituations. I can't figure out how to make this work. For instance: ... do if cond

Re: [Haskell-cafe] new Haskell hacker seeking peer review

2005-02-18 Thread Jules Bean
Hi Sean, I'm not expert, but since you asked for idiomatic comments, here are a few... On 18 Feb 2005, at 09:58, Sean Perry wrote: Also, while talking about untilEOF, it is slightly annoying that hIsEOF returns IO Bool and that functions like 'not' only want Bool. Sure makes the logic tests feel

Re: [Haskell-cafe] Parsing in Haskell

2005-02-15 Thread Jules Bean
On 15 Feb 2005, at 10:36, Johan Glimming wrote: Hi I want to implement a little algebraic specification language in Haskell, and I have a working C implementation available which uses yacc/flex. What is the best way of replacing yacc/bison and (f)lex when migrating the project into Haskell? I

Re: [Haskell-cafe] Getting an attribute of an object

2005-02-11 Thread Jules Bean
On 11 Feb 2005, at 19:09, Dmitri Pissarenko wrote: readClassifiedImages :: [ClassifiedImage] -> [IO (ClassifiedImage, Image)] which is what I want. However, when in the program I insert the statement classifiedImagesWithData :: [IO (ClassifiedImage, Image)] so that it becomes do ... classifiedIma

Re: [Haskell-cafe] Getting an attribute of an object

2005-02-10 Thread Jules Bean
On 10 Feb 2005, at 20:17, Dmitri Pissarenko wrote: Hello! I have a list of instances of the ClassifiedImage class, which is defined as follows. data ClassifiedImage = ClassifiedImage {imageFileName :: String, subjectID :: String} deriving Show Attribute imageFileName contains a file nam

Re: [Haskell-cafe] help with some code. it doesn't whant to compile.

2005-02-08 Thread Jules Bean
On 7 Feb 2005, at 20:23, pablo daniel rey wrote: hello i'm new to haskell so i'm sorry if this is a stupid question, but i'm having problems with some basic code. the code : data Maybe Dir = Just Dir | Nothing (You don't want this. Maybe already exists as a type in the Prelude, you don't want to

Re: [Haskell-cafe] File path programme

2005-01-27 Thread Jules Bean
On 27 Jan 2005, at 11:33, Keean Schupke wrote: Except paths are different on different platforms... for example: /a/b/../c/hello\ there/test and: A:\a\b\ notice how the backslash is used to 'escape' a space or meta-character on only it isn't. That's a property of a shell, the underlying OS allows

Re: [Haskell-cafe] List manipulation

2005-01-27 Thread Jules Bean
On 27 Jan 2005, at 07:32, Sven Panne wrote: Jules Bean wrote: [...] You rather want 'zipWith'. Documentation at: http://www.haskell.org/ghc/docs/latest/html/libraries/base/ GHC.List.html ...along with lots of other funky list processing stuff. Just a small hint: Everything below &q

Re: [Haskell-cafe] List manipulation

2005-01-26 Thread Jules Bean
On 26 Jan 2005, at 16:39, Dmitri Pissarenko wrote: Hello! Hi Dmitri. Have a browse around the haskell wiki! There's loads of interesting information and example code there... add2Img summand1 summand2 = sum where sum = [ (x+y) | x <- summand1, y <- summand2 ] [3.0,4.0,501.0,4.0,5.0,502.0

Re: [Haskell-cafe] Re: What are the MonadPlus laws?

2005-01-26 Thread Jules Bean
On 26 Jan 2005, at 08:41, Keean Schupke wrote: I cannot find any reference to MonadPlus in category theory. At a guess I would say that it was the same as a Monad except the operators are id and co-product (or sum)... That would mean the 'laws' would be exactly the same as a Monad, just with (0,

Re: [Haskell-cafe] Re: What are the MonadPlus laws?

2005-01-26 Thread Jules Bean
On 26 Jan 2005, at 05:57, David Menendez wrote: Philip Wadler listed those as the laws he "would usually insist on" in a 1997 message[1]. [1] He also mentions two other possible, but problematic, laws: m >>= \x -> mzero =

[Haskell-cafe] What are the MonadPlus laws?

2005-01-25 Thread Jules Bean
So, anyone? What are the laws that MonadPlus is supposed to satisfy? The obvious ones are that if MonadPlus m then for all types a, (m a) should be a monoid. But, what about the others, because IO does not appear to satisfy a >> mzero == mzero Jules __

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 13:20, Keean Schupke wrote: f = getChar >>= (\a -> if a == "F" then mzero else return a) In this case if the LHS returns "F" the LHS should not have been run... this contradicts itself, so this is a non option I guess. Good paradox. That is what is upsetting me, too.

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 12:22, Jules Bean wrote: The concrete example for [] is: concat . (map concat) should be the same (on all values of all types [a]) as concat . concat ..tiny correction, sorry. 'On all values of all types [[[a]]]'. ___ Ha

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 11:56, Keean Schupke wrote: I guess I am trying to understand how the Monad laws are derived from category theory... I can only find referneces to associativity being required. Associativity and left and right unit laws. Monads are defined on functors, so the associativity just

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 11:49, Keean Schupke wrote: Jules Bean wrote: A monad T is a (endo)functor T : * -> * where * is the category of types, together with a multiplication mu and a unit eta. So, * is the category of Types, and functions on type (which map values to values), and T is an endofunc

Re: [Haskell-cafe] File path programme

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 11:32, Krasimir Angelov wrote: splitFileName "/foo/bar" ==> ("/foo","bar") splitFileName "/foo//bar" ==> ("/foo/","bar") (definitely a bug) Is "/foo//bar" valid file path and what does "//" mean? pathParents "/foo///bar" ==> ["/","/foo","/foo","/foo","/foo/bar"] Again what

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 10:32, Keean Schupke wrote: I think I see, but if the objects are types, arn't the morphisms functions on types not values? No. Well: they are functions 'on' types, but functions 'on' types map values to values. Analogy: In the category of sets and functions, the objects are

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 09:30, Daniel Fischer wrote: putStrLn "hello" >>= (\_ -> mzero) === (\_ -> mzero) () ...no. That last identity holds for 'return ()' but not for 'putStrLn "hello"'. The monad law is a law for 'return' not for arbitrary things. Jules ___

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 08:53, Daniel Fischer wrote: Am Montag, 24. Januar 2005 22:59 schrieb Benjamin Franksen: getChar = 'the action that, when executed, reads a character from stdin and returns it' and that holds whether we just consider the values returned by an IO action or take the action perfor

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Jules Bean
On 24 Jan 2005, at 18:18, Keean Schupke wrote: Ashley Yakeley wrote: If you remember your category theory, you'll recall that two morphisms are not necessarily the same just because they're between the same two objects. For instance, the objects may be sets, and the morphisms may be functions b

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Jules Bean
On 24 Jan 2005, at 10:32, Keean Schupke wrote: Right, but we are dealing with the type system here. Remember Haskell monoids are functors on types, not on values ... (ie the base objects the 'category theory' is applied to are the types not the values)... Therefore we only consider the types when

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Jules Bean
On 24 Jan 2005, at 09:36, Keean Schupke wrote: Ashley Yakeley wrote: I disagree. Clearly (putStrLn "Hello" >> mzero) is not the same as mzero. Yes it is, side effects are quite clearly not counted. The value of (putStrLn "Hello" >> mzero") is mzero. This makes no sense to me at all. putStrLn "He

Re: [Haskell-cafe] About instance

2005-01-18 Thread Jules Bean
On 18 Jan 2005, at 21:45, Ulises Juarez Martinez wrote: Who can I do an instance of Eq (Ocurrence -> Bool)? Is there another option to avoid the error? In general, you can't define one. To define equality on functions you want to check the value on every possible input, and since Ocurrence is a

Re: [Haskell-cafe] Building GUIs for Haskell programs

2005-01-12 Thread Jules Bean
On 12 Jan 2005, at 11:10, Matthew Roberts wrote: Can anyone attest to the sense (or otherwise) of the following programming "pattern" - program all back end stuff in Haskell and compile to library - program all GUI stuff in *insert imperative language of choice" and link to the library for back

Re: [Haskell-cafe] Signature of a function

2005-01-11 Thread Jules Bean
On 11 Jan 2005, at 16:47, Daniel Fischer wrote: Am Dienstag, 11. Januar 2005 16:45 schrieb Henning Thielemann: On Tue, 11 Jan 2005, Jules Bean wrote: Hint: Don't put signatures on functions, then. Instead, let the compiler infer the type for you! If you want to know what the type is, ask

Re: [Haskell-cafe] Signature of a function

2005-01-11 Thread Jules Bean
On 11 Jan 2005, at 14:49, Dmitri Pissarenko wrote: activityIndicator :: Customer -> Num activityIndicator (Customer id purchases) = length purchases When I try to load this module into GHCi, I get this error: Hint: Don't put signatures on functions, then. Instead, let the compiler infer the type

Re: [Haskell-cafe] Re: Begginer question

2005-01-06 Thread Jules Bean
On 6 Jan 2005, at 14:06, Maurício wrote: * import Complex; a = 3 :+ 4; * and load it into ghci, "a + 4" gives me "7.0 :+ 4.0", although "a + (4::Float)" gives me that error again. Why Haskell converts "4" to Complex but not a Float? The answer lies available to you in ghci: Prelude> :t 4

Re: [Haskell-cafe] Begginer question

2005-01-06 Thread Jules Bean
On 6 Jan 2005, at 01:37, Maurício wrote: import Complex; complex_root :: (Float, Float, Float) -> (Complex Float, Complex Float) complex_root (a,b,c) = (x1,x2) where { delta = b * b - 4 * a * c :: Float; sqr_delta = if delta >= 0 then (sqrt delta) :+ 0 else 0 :+ (sqrt delta) :: (Complex Float);

Re: [Haskell-cafe] Re: Ignorant begginer question

2004-12-24 Thread Jules Bean
On 24 Dec 2004, at 14:53, John Goerzen wrote: On 2004-12-23, Stefan Holdermans <[EMAIL PROTECTED]> wrote: Your problem right now is that the type Complex takes (needs) a type argument. Its definitions is (module strictness flags): data Complex a = a :+ a What does the :+ mean here? It's a data c

Re: [Haskell-cafe] Ignorant begginer question

2004-12-23 Thread Jules Bean
On 23 Dec 2004, at 17:09, Maurício wrote: Kind error: `Complex' is not applied to enough type arguments Complex is a type constructor. Complex Double (e.g.) is a type. So try roots :: (Complex Double, Complex Double, Complex Double) -> (Complex Double, Complex Double); or indeed roots :: (RealFlo

<    1   2   3   4   5   >