Re: [Haskell-cafe] Doubting Haskell
Concerning the Haskell program that does some statistics and displays some graphs, I must say that if that were the task I had to solve I would not use either C++ or Haskell, but R, the open source S lookalike. The best way to be productive as a programmer is to not write code if you can steal it. R looks like an imperative language, but it is "value-oriented" in the same way that SETL is, so is by some criteria a functional language of sorts. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
Thanks for an interesting write-up. And not bad for a first Haskell program. :) There's still a number of things you could do to limit the boiler plate code, though. On Tue, Mar 4, 2008 at 6:29 AM, Alan Carter <[EMAIL PROTECTED]> wrote: > Many thanks for the explanations when I was first experimenting with > Haskell. I managed to finish translating a C++ wxWidgets program into > Haskell wxHaskell, and am certainly impressed. > > I've written up some reflections on my newbie experience together with > both versions, which might be helpful to people interested in > popularizing Haskell, at: > > http://the-programmers-stone.com/2008/03/04/a-first-haskell-experience/ > > Regards, > > Alan > > -- > ... the PA system was moaning unctuously, like a lady hippopotamus > reading A. E. Housman ..." > -- James Blish, "They Shall Have Stars" > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
chaddai.fouche: > 2008/3/4, Alan Carter <[EMAIL PROTECTED]>: > > I've written up some reflections on my newbie experience together with > > both versions, which might be helpful to people interested in > > popularizing Haskell, at: > > > > http://the-programmers-stone.com/2008/03/04/a-first-haskell-experience/ > > > I also do concur that a flag or a warning to signal mixed tabulations > and space would be a _very_ good idea ! > Such a flag already exists: -fwarn-tabs As in: $ ghc -fwarn-tabs A.hs -no-recomp A.hs:3:0: Tab character -- Don ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
2008/3/4, Alan Carter <[EMAIL PROTECTED]>: > I've written up some reflections on my newbie experience together with > both versions, which might be helpful to people interested in > popularizing Haskell, at: > > http://the-programmers-stone.com/2008/03/04/a-first-haskell-experience/ This is truly interesting, any learning experience is enlightening, we truly do need to lower this barrier of admittance of which you speak. On another subject, there are still point in your code that could be clearer or done with less cruft : maxOfHistogram stats = snd (foldl (\(cA, vA) (cB, vB) -> if (vA > vB) then (cA, vA) else (cB, vB)) (0, 0) stats) can become : maxofHistogram stats = foldl' max 0 (map snd stats) ("foldl' max 0" could be replaced by "maximum" but there wouldn't be a default 0 anymore) more importantly, you can replace this kind of code : vA <- varCreate [] vB <- varCreate [] -- ... vL <- varCreate [] vM <- varCreate [] vN <- varCreate [] vO <- varCreate [] by : [vA, vB, vC, vD, vE, vF, vG, vH, vI, vJ, vK, vL, vM, vN, vO] <- replicateM 15 (varCreate []) (true also for the "dA <- textEntry statusFrame [text := "0", alignment := AlignRight]" sequence) I'm not sure that functions like getdTotal couldn't be improved, I wonder if a small Map for the elements of d wouldn't make the code much better and offer other opportunities for abstractions. As it is, enumeration like : [[label "Total Entries", widget (getdTotal d)] ,[label "Valid Entries", widget (getdValid d)] -- ... ,[label "MDMA",widget (getdMdma d)] ,[label "Caffeine",widget (getdCaffeine d)]] could be slightly reduced by : let bindLabelAndWidget (lbl,getter) = [label lbl, widget (getter d)] in map bindLabelAndWidget [("Total Entries", getdTotal), ("Valid Entries", getdValid) ,(...)] And little thing like : mapM_ (\f -> do repaint f) knownFrames becoming : mapM_ repaint knownFrames I also do concur that a flag or a warning to signal mixed tabulations and space would be a _very_ good idea ! -- Jedaï ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
About the line length needed for Haskell programs, there was a discussion about this some time ago, that could be regarded as a tutorial for reducing indentation: http://haskell.org/pipermail/haskell-cafe/2007-July/028787.html As for the idle core you mention: I keep one core fully occupied with a program that searches for a cure against cancer, see: http://www.computeagainstcancer.org/ The example you gave for the use of "map" can be simplified: map func (take (10 [0..])) -- should actually be: map func (take 10 [0..]) -> map func [0..9] Regards, Henk-Jan van Tuyl -- http://functor.bamikanarie.com http://Van.Tuyl.eu/ -- On Tue, 04 Mar 2008 07:29:24 +0100, Alan Carter <[EMAIL PROTECTED]> wrote: Many thanks for the explanations when I was first experimenting with Haskell. I managed to finish translating a C++ wxWidgets program into Haskell wxHaskell, and am certainly impressed. I've written up some reflections on my newbie experience together with both versions, which might be helpful to people interested in popularizing Haskell, at: http://the-programmers-stone.com/2008/03/04/a-first-haskell-experience/ Regards, Alan -- -- Met vriendelijke groet, Henk-Jan van Tuyl -- http://functor.bamikanarie.com http://Van.Tuyl.eu/ -- ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
> Especially if mixing tabs and spaces indeed. Haskell does the Python > thing of assuming that a tab is 8 spaces, which IMO is a mistake. The FWIW, most people in python land think the same thing, and the -t flag makes mixed tabs and spaces a warning or error. At the least, -Wall could report mixed usage. At the most, make it an error. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On 04/03/2008, Luke Palmer <[EMAIL PROTECTED]> wrote: > On Tue, Mar 4, 2008 at 4:16 AM, Ketil Malde <[EMAIL PROTECTED]> wrote: > > Paul Johnson <[EMAIL PROTECTED]> writes: > > > > > I'm surprised you found the significant whitespace difficult. > > > > I wonder if this has something to do with the editor one uses? I use > > Emacs, and just keep hitting TAB, cycling through possible alignments, > > until things align sensibly. I haven't really tried, but I can > > imagine lining things up manually would be more painful, especially > > if mixing tabs and spaces. > > > Especially if mixing tabs and spaces indeed. Haskell does the Python > thing of assuming that a tab is 8 spaces, which IMO is a mistake. The > sensible thing to do if you have a whitespace-sensitive language that > accepts both spaces in tabs is to make them incomparable to each > other; i.e. I honestly think that tab characters occurring anywhere but in a comment should be considered a lexical error and rejected by the compiler outright. More problems are caused by trying to continue with only tabs, or some mixture of tabs and spaces than just getting one's editor to expand tabs automatically. - Cale ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On 04/03/2008, Alan Carter <[EMAIL PROTECTED]> wrote: > http://the-programmers-stone.com/2008/03/04/a-first-haskell-experience/ That was an interesting read. Thanks for posting it. I also liked the tale of the BBC ULA - it reminded me of a demo I saw once at an Acorn show, where they had a RISC PC on show, with a (IBM) PC card in it. They were demonstrating how hot the PC chip runs compared to the ARM RISC chip by using it to make toast. I dread to think what you could do with one of today's monsters :-) Paul. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On Tue, Mar 4, 2008 at 4:16 AM, Ketil Malde <[EMAIL PROTECTED]> wrote: > Paul Johnson <[EMAIL PROTECTED]> writes: > > > I'm surprised you found the significant whitespace difficult. > > I wonder if this has something to do with the editor one uses? I use > Emacs, and just keep hitting TAB, cycling through possible alignments, > until things align sensibly. I haven't really tried, but I can > imagine lining things up manually would be more painful, especially > if mixing tabs and spaces. Especially if mixing tabs and spaces indeed. Haskell does the Python thing of assuming that a tab is 8 spaces, which IMO is a mistake. The sensible thing to do if you have a whitespace-sensitive language that accepts both spaces in tabs is to make them incomparable to each other; i.e. main = do putStrLn $ "Hello" ++ "World" -- compiles fine main = do putStrLn $ "Hello" ++ "World" -- error, can't tell how indented '++ "World"' is... Luke ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
Paul Johnson <[EMAIL PROTECTED]> writes: > I'm surprised you found the significant whitespace difficult. I wonder if this has something to do with the editor one uses? I use Emacs, and just keep hitting TAB, cycling through possible alignments, until things align sensibly. I haven't really tried, but I can imagine lining things up manually would be more painful, especially if mixing tabs and spaces. -k -- If I haven't seen further, it is by standing in the footprints of giants ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
Alan Carter wrote: I've written up some reflections on my newbie experience together with both versions, which might be helpful to people interested in popularizing Haskell, at: http://the-programmers-stone.com/2008/03/04/a-first-haskell-experience/ Thank you for writing this. On the lack of simple examples showing, for example, file IO: I seem to recall a Perl book (maybe it was Edition 1 of the Camel Book) which had lots of very short programs each illustrating one typical job. Also the Wiki does have some pages of "worked example" programs. But I agree, we could do better. I'm surprised you found the significant whitespace difficult. Yes, the formal rules are a bit arcane, but I just read them as "does the Right Thing", and it generally works for me. I didn't know about the significance of comments, but then I've never written an outdented comment. I had a look through your code, and although I admit I haven't done the work, I'm sure that there would be ways of factoring out all the commonality and thereby reducing the length. Finally, thanks for that little story about the BBC B. I had one of those, and I always wondered about that heatsink, and the stonking big resistor next to it. They looked out of scale with the rest of the board. Paul. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
Many thanks for the explanations when I was first experimenting with Haskell. I managed to finish translating a C++ wxWidgets program into Haskell wxHaskell, and am certainly impressed. I've written up some reflections on my newbie experience together with both versions, which might be helpful to people interested in popularizing Haskell, at: http://the-programmers-stone.com/2008/03/04/a-first-haskell-experience/ Regards, Alan -- ... the PA system was moaning unctuously, like a lady hippopotamus reading A. E. Housman ..." -- James Blish, "They Shall Have Stars" ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
A quick note here. This is a *really* excellent tutorial on a variety of subjects. It shows how monad operators can be used responsibly (to clarify code, not obfuscate it), it shows how chosing a good data structure and a good algorithm can work wonders for your code, and on a simplistic level, it shows how to build a database in Haskell. Would it be possible to clean this up and put it in the wiki somewhere? Thanks Bob On 20 Feb 2008, at 09:58, Cale Gibbard wrote: (I'm copying the list on this, since my reply contains a tutorial which might be of use to other beginners.) On 19/02/2008, Alan Carter <[EMAIL PROTECTED]> wrote: Hi Cale, On Feb 19, 2008 3:48 PM, Cale Gibbard <[EMAIL PROTECTED]> wrote: Just checking up, since you haven't replied on the list. Was my information useful? Did I miss any questions you might have had? If you'd like, I posted some examples of using catch here: Thanks for your enquiry! My experiment continues. I did put a progress report on the list - your examples together with a similar long an short pair got me over the file opening problem, and taught me some things about active whitespace :-) I couldn't get withFile working (says out of scope, maybe 'cos I'm ghc 6.6 on my Mac) Make sure to put: import System.IO at the top of your source file, if you haven't been. This should import everything documented here: http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-IO.html but it turned out the line I was looking for (collapsed from the examples) was: text <- readFile "data.txt" `catch` \_ -> return "" This ensures the program never loses control, crashing or becoming unpredictable by attempting to use an invalid resource, by yielding an empty String if for any reason the file read fails. Then an empty String makes it very quickly through parsing. I guess that's quite "functiony" :-) Amazing how easy once I knew how. Even stranger that I couldn't find a "bread and butter" example of it. Then I was going very quickly for a while. My file is dumped from a WordPress MySql table. Well formed lines have 4 tab separated fields (I'm using pipes for tabs here): line id | record id | property | value Line IDs are unique and don't matter. All lines with the same record ID give a value to a property in the same record, similar to this: 1|1|name|arthur 2|1|quest|seek holy grail 3|1|colour|blue 4|2|name|robin 5|2|quest|run away 6|2|colour|yellow Organizing that was a joy. It took minutes: let cutUp = tail (filter (\fields -> (length fields) == 4) (map (\x -> split x '\t') (lines text))) This should almost certainly be a function of text: cutUp text = tail (filter (\fields -> (length fields) == 4) (map (\x -> split x '\t') (lines text))) I found a split on someone's blog (looking for a library tokenizer), but I can understand it just fine. I even get to chuck out ill-formed lines and remove the very first (which contains MySql column names) on the way through! Sadly, there's no general library function for doing this. We have words and lines (and words would work here, if your fields never have spaces), but nobody's bothered to put anything more general for simple splitting into the base libraries (though I'm sure there's plenty on hackage -- MissingH has a Data.String.Utils module which contains split and a bunch of others, for example). However, for anything more complicated, there are also libraries like Parsec, which are generally really effective, so I highly recommend looking at that at some point. I then made a record to put things in, and wrote some lines to play with it (these are the real property names): data Entry = Entry { occupation:: String , iEnjoyMyJob :: Int , myJobIsWellDefined:: Int , myCoworkersAreCooperative :: Int , myWorkplaceIsStressful:: Int , myJobIsStressful :: Int , moraleIsGoodWhereIWork:: Int , iGetFrustratedAtWork :: Int } ... let e = Entry{occupation = "", iEnjoyMyJob = 0} let f = e {occupation = "alan"} let g = f {iEnjoyMyJob = 47} putStrLn ((occupation g) ++ " " ++ (show (iEnjoyMyJob g))) Then I ran into another quagmire. I think I have to use Data.Map to build a collection of records keyed by record id, and fill them in by working through the list of 4 item lists called cutUp. As with the file opening problem I can find a few examples that convert a list of tuples to a Data.Map, one to one. I found a very complex example that convinced me a map from Int to a record is possible, but gave me no understanding of how to do it. I spent a while trying to use foldl before I decided it can't be appropriate (I need to pass more values). So I tried a couple of recursive functions, something like: type Entries = M.Map Int Entry ... let entries = loadEntries cutUp ... loadEntries :: [[String]] -> Entries loadEntries [] = M.empty Entries loadEntries
Re: [Haskell-cafe] Doubting Haskell
Cale Gibbard wrote: > I woke up rather early, and haven't much to do, so I'll turn this into > a tutorial. :) Cale, this is fantastic, as always. I often find myself searching for material like this when introducing people to Haskell. Would you be willing to put this on the wiki? Thanks, Yitz ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
Cale, On Feb 20, 2008 10:58 AM, Cale Gibbard <[EMAIL PROTECTED]> wrote: > (I'm copying the list on this, since my reply contains a tutorial > which might be of use to other beginners.) Thank you so much for this - I've just started playing with it so few intelligent responses yet. I'm sure it will be of *huge* use to others, right in the middle of the "gap" I fell into. The experiment continues - I'll be back :-) Many thanks, Alan -- ... the PA system was moaning unctuously, like a lady hippopotamus reading A. E. Housman ..." -- James Blish, "They Shall Have Stars" ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
(I'm copying the list on this, since my reply contains a tutorial which might be of use to other beginners.) On 19/02/2008, Alan Carter <[EMAIL PROTECTED]> wrote: > Hi Cale, > > On Feb 19, 2008 3:48 PM, Cale Gibbard <[EMAIL PROTECTED]> wrote: > > Just checking up, since you haven't replied on the list. Was my > > information useful? Did I miss any questions you might have had? If > > you'd like, I posted some examples of using catch here: > > Thanks for your enquiry! My experiment continues. I did put a progress > report on the list - your examples together with a similar long an > short pair got me over the file opening problem, and taught me some > things about active whitespace :-) I couldn't get withFile working > (says out of scope, maybe 'cos I'm ghc 6.6 on my Mac) Make sure to put: import System.IO at the top of your source file, if you haven't been. This should import everything documented here: http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-IO.html > but it turned out the line I was looking for (collapsed from the examples) > was: > > text <- readFile "data.txt" `catch` \_ -> return "" > > This ensures the program never loses control, crashing or becoming > unpredictable by attempting to use an invalid resource, by yielding an > empty String if for any reason the file read fails. Then an empty > String makes it very quickly through parsing. I guess that's quite > "functiony" :-) > > Amazing how easy once I knew how. Even stranger that I couldn't find a > "bread and butter" example of it. > > Then I was going very quickly for a while. My file is dumped from a > WordPress MySql table. Well formed lines have 4 tab separated fields > (I'm using pipes for tabs here): > > line id | record id | property | value > > Line IDs are unique and don't matter. All lines with the same record > ID give a value to a property in the same record, similar to this: > > 1|1|name|arthur > 2|1|quest|seek holy grail > 3|1|colour|blue > 4|2|name|robin > 5|2|quest|run away > 6|2|colour|yellow > > Organizing that was a joy. It took minutes: let cutUp = tail (filter (\fields -> (length fields) == 4) (map (\x -> split x '\t') (lines text))) This should almost certainly be a function of text: cutUp text = tail (filter (\fields -> (length fields) == 4) (map (\x -> split x '\t') (lines text))) > I found a split on someone's blog (looking for a library tokenizer), > but I can understand it just fine. I even get to chuck out ill-formed > lines and remove the very first (which contains MySql column names) on > the way through! Sadly, there's no general library function for doing this. We have words and lines (and words would work here, if your fields never have spaces), but nobody's bothered to put anything more general for simple splitting into the base libraries (though I'm sure there's plenty on hackage -- MissingH has a Data.String.Utils module which contains split and a bunch of others, for example). However, for anything more complicated, there are also libraries like Parsec, which are generally really effective, so I highly recommend looking at that at some point. > I then made a record to put things in, and wrote some lines to play > with it (these are the real property names): > > data Entry = Entry > { occupation:: String > , iEnjoyMyJob :: Int > , myJobIsWellDefined:: Int > , myCoworkersAreCooperative :: Int > , myWorkplaceIsStressful:: Int > , myJobIsStressful :: Int > , moraleIsGoodWhereIWork:: Int > , iGetFrustratedAtWork :: Int > } > ... > let e = Entry{occupation = "", iEnjoyMyJob = 0} > let f = e {occupation = "alan"} > let g = f {iEnjoyMyJob = 47} > putStrLn ((occupation g) ++ " " ++ (show (iEnjoyMyJob g))) > > Then I ran into another quagmire. I think I have to use Data.Map to > build a collection of records keyed by record id, and fill them in by > working through the list of 4 item lists called cutUp. As with the > file opening problem I can find a few examples that convert a list of > tuples to a Data.Map, one to one. I found a very complex example that > convinced me a map from Int to a record is possible, but gave me no > understanding of how to do it. I spent a while trying to use foldl > before I decided it can't be appropriate (I need to pass more values). > So I tried a couple of recursive functions, something like: > > type Entries = M.Map Int Entry > ... > let entries = loadEntries cutUp > ... > loadEntries :: [[String]] -> Entries > loadEntries [] = M.empty Entries > loadEntries [x : xs] = loadEntry (loadEntries xs) x -- Possible common beginner error here: [x:xs] means the list with one element which is a list whose first element is x and whose tail is xs. Your type signature and the type of cutUp seems to confirm that this is the right type, but you don't seem to have a case to handle a longer list of lists. If yo
Re: [Haskell-cafe] Doubting Haskell
On Sat, Feb 16, 2008 at 05:04:53PM -0800, Donn Cave wrote: > But in Haskell, you cannot read a file line by line without writing an > exception handler, because end of file is an exception! as if a file does > not normally have an end where the authors of these library functions > came from? Part of it is that using 'getLine' is not idiomatic haskell when you don't want to worry about exceptions. Generally you do something like doMyThing xs = print (length xs) main = do contents <- readFile "my.file" mapM_ doMyThing (lines contents) which will call 'doMyThing' on each line of the file, in this case printing the length of each line. or more succinctly: main = readFile "my.file" >>= mapM_ doMyThing . lines John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
Hi Alan I can help but feeling curious. Did some of the answers actually help you? Are you still as doubtful about Haskell as when you wrote your email? Greetings, Mads Lindstrøm ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On Sun, 17 Feb 2008, Anton van Straaten wrote: > Is there a benefit to reusing a generic Either type for this sort of thing? > For code comprehensibility, wouldn't it be better to use more specific > names? If I want car and cdr, I know where to find it. > It's Haskell's standard sum type, with a pile of instances already written. There's an instance of MonadError such that you only need to see an Either when you run the computation for example (and then you get an Either whatever the actual error monad was!). If we had appropriate language extensions to map an isomorphic Success/Failure type onto it then I'd probably use them - as it is, the level of inertia around Either is great enough to mean that's only worth doing if I'm expecting to roll a third constructor in at some point. That said, generally I'll wrap it up pretty fast if I have to handle Either directly. Not that that's necessarily any different to cons, car and cdr of course, but there's plenty of library support for doing so. -- [EMAIL PROTECTED] "I think you mean Philippa. I believe Phillipa is the one from an alternate universe, who has a beard and programs in BASIC, using only gotos for control flow." -- Anton van Straaten on Lambda the Ultimate ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On 17 feb 2008, at 08.46, Anton van Straaten wrote: Colin Paul Adams wrote: "Cale" == Cale Gibbard <[EMAIL PROTECTED]> writes: Cale> So, the first version: Cale> import System.IO import Control.Exception (try) Cale> main = do mfh <- try (openFile "myFile" ReadMode) case mfh Cale> of Left err -> do putStr "Error opening file for reading: " Cale> print err Right fh -> do mline <- try (hGetLine fh) case Cale> mline of Left err -> do putStr "Error reading line: " print Cale> err hClose fh Right line -> putStrLn ("Read: " ++ line) Left? Right? Hardly descriptive terms. Sounds like a sinister language to me. I was thinking along the same lines. Politically-sensitive left- handed people everywhere ought to be offended that "Left" is the alternative used to represent errors, mnemonic value notwithstanding. Is there a benefit to reusing a generic Either type for this sort of thing? For code comprehensibility, wouldn't it be better to use more specific names? If I want car and cdr, I know where to find it. Haskell doesn't have constructor aliases and keeping around dozens of isomorphic types would be stupid. (Views could help, though.) Also, "Right" is naturally used when the everything was alright. It might be arbitrary, but it's not hard to remember - once you're past the newbie phase no-one confuses car and cdr anyways... ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On Sun, 2008-02-17 at 02:46 -0500, Anton van Straaten wrote: > Colin Paul Adams wrote: > >> "Cale" == Cale Gibbard <[EMAIL PROTECTED]> writes: > > > > Cale> So, the first version: > > > > Cale> import System.IO import Control.Exception (try) > > > > Cale> main = do mfh <- try (openFile "myFile" ReadMode) case mfh > > Cale> of Left err -> do putStr "Error opening file for reading: " > > Cale> print err Right fh -> do mline <- try (hGetLine fh) case > > Cale> mline of Left err -> do putStr "Error reading line: " print > > Cale> err hClose fh Right line -> putStrLn ("Read: " ++ line) > > > > Left? Right? > > > > Hardly descriptive terms. Sounds like a sinister language to me. > > I was thinking along the same lines. Politically-sensitive left-handed > people everywhere ought to be offended that "Left" is the alternative > used to represent errors, mnemonic value notwithstanding. > > Is there a benefit to reusing a generic Either type for this sort of > thing? For code comprehensibility, wouldn't it be better to use more > specific names? If I want car and cdr, I know where to find it. Actually, it's either intentional or ironic that Colin uses the word "sinister" in his response as "Left" is etymologically related to it. See http://en.wikipedia.org/wiki/Left-handed#Negative_associations_of_left-handedness_in_language (to the extent wikipedia can be trusted) Indeed, also as wikipedia mentions, there are entire connotations with both words along the lines of how Haskell libraries use them. The benefit of reusing Either is that a) it -is- already mnemonic, b) there are several functions that operate on Eithers in the standard, there's little point in rewriting all of them just so you can say Ok or Error. That said, you often don't see too many explicit uses of the constructors of Either (as functions or patterns) in Haskell code as it is usually more convenient to use combinators (e.g. either or the monad methods) rather than explicit cases. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On 16 Feb 2008, at 11:46 PM, Anton van Straaten wrote: Colin Paul Adams wrote: "Cale" == Cale Gibbard <[EMAIL PROTECTED]> writes: Cale> So, the first version: Cale> import System.IO import Control.Exception (try) Cale> main = do mfh <- try (openFile "myFile" ReadMode) case mfh Cale> of Left err -> do putStr "Error opening file for reading: " Cale> print err Right fh -> do mline <- try (hGetLine fh) case Cale> mline of Left err -> do putStr "Error reading line: " print Cale> err hClose fh Right line -> putStrLn ("Read: " ++ line) Left? Right? Hardly descriptive terms. Sounds like a sinister language to me. I was thinking along the same lines. Politically-sensitive left- handed people everywhere ought to be offended that "Left" is the alternative used to represent errors, mnemonic value notwithstanding. Is there a benefit to reusing a generic Either type for this sort of thing? Standardization. It's already a standard, we need a standard sum type anyway, and it'd be kind of silly to have two isomorphic types with the same signature in the Prelude. jcc ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
Colin Paul Adams wrote: "Cale" == Cale Gibbard <[EMAIL PROTECTED]> writes: Cale> So, the first version: Cale> import System.IO import Control.Exception (try) Cale> main = do mfh <- try (openFile "myFile" ReadMode) case mfh Cale> of Left err -> do putStr "Error opening file for reading: " Cale> print err Right fh -> do mline <- try (hGetLine fh) case Cale> mline of Left err -> do putStr "Error reading line: " print Cale> err hClose fh Right line -> putStrLn ("Read: " ++ line) Left? Right? Hardly descriptive terms. Sounds like a sinister language to me. I was thinking along the same lines. Politically-sensitive left-handed people everywhere ought to be offended that "Left" is the alternative used to represent errors, mnemonic value notwithstanding. Is there a benefit to reusing a generic Either type for this sort of thing? For code comprehensibility, wouldn't it be better to use more specific names? If I want car and cdr, I know where to find it. Anton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
> "Cale" == Cale Gibbard <[EMAIL PROTECTED]> writes: Cale> So, the first version: Cale> import System.IO import Control.Exception (try) Cale> main = do mfh <- try (openFile "myFile" ReadMode) case mfh Cale> of Left err -> do putStr "Error opening file for reading: " Cale> print err Right fh -> do mline <- try (hGetLine fh) case Cale> mline of Left err -> do putStr "Error reading line: " print Cale> err hClose fh Right line -> putStrLn ("Read: " ++ line) Left? Right? Hardly descriptive terms. Sounds like a sinister language to me. -- Colin Adams Preston Lancashire ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On 16 Feb 2008, at 5:04 PM, Donn Cave wrote: On Feb 16, 2008, at 3:46 PM, Philippa Cowderoy wrote: On Sat, 16 Feb 2008, Alan Carter wrote: I'm a Haskell newbie, and this post began as a scream for help. Extremely understandable - to be blunt, I don't really feel that Haskell is ready as a general-purpose production environment unless users are willing to invest considerably more than usual. Not only is it not as "batteries included" as one might like, sometimes it's necessary to build your own batteries! Ironically, the simple task of reading a file is more work than I expect precisely because I don't want to bother to handle exceptions. I mean, in some applications it's perfectly OK to let an exception go to the top. But in Haskell, you cannot read a file line by line without writing an exception handler, because end of file is an exception! as if a file does not normally have an end where the authors of these library functions came from? I agree 100%; to make life tolerable around Haskell I/O, I usually end up binding the moral equivalent of tryJust (\ exc -> case exc of IOException e | isEOFError e -> return () _ -> Nothing) $ getLine somewhere at top level and then calling that where it's needed. For the author of the original post ... can't make out what you actually found and tried, so you should know about "catch" in the Prelude, the basic exception handler. Also, you might need to know that bracket nests in various ways: bracket openFile hClose $ bracket readLine cleanUpLine $ proceed There's also finally, for when the first argument to bracket is ommitted, and (>>) for when the second argument is :) jcc ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
Stefan O'Rear wrote: > Well... that's what I meant by break horribly. Buh? That behaviour makes perfect sense to me. http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On Sat, Feb 16, 2008 at 06:23:54PM -0800, Bryan O'Sullivan wrote: > Stefan O'Rear wrote: > > > I'll bet that breaks horribly in the not-so-corner case of /dev/tty. > > Actually, it doesn't. It seems to do a read behind the scenes if the > buffer is empty, so it blocks until you type something. Well... that's what I meant by break horribly. Stefan signature.asc Description: Digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
Stefan O'Rear wrote: > I'll bet that breaks horribly in the not-so-corner case of /dev/tty. Actually, it doesn't. It seems to do a read behind the scenes if the buffer is empty, so it blocks until you type something. http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On Sat, Feb 16, 2008 at 05:11:59PM -0800, Bryan O'Sullivan wrote: > Donn Cave wrote: > > > But in Haskell, you cannot read a file line by line without writing an > > exception handler, because end of file is an exception! > > Ah, yet another person who has never found System.IO.hIsEOF :-) > > Whereas in C or Python you would check the return value of read against > zero or an empty string, in Haskell you call hIsEOF *before* a read. I'll bet that breaks horribly in the not-so-corner case of /dev/tty. Stefan signature.asc Description: Digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
Donn Cave wrote: > But in Haskell, you cannot read a file line by line without writing an > exception handler, because end of file is an exception! Ah, yet another person who has never found System.IO.hIsEOF :-) Whereas in C or Python you would check the return value of read against zero or an empty string, in Haskell you call hIsEOF *before* a read. http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On Feb 16, 2008, at 3:46 PM, Philippa Cowderoy wrote: On Sat, 16 Feb 2008, Alan Carter wrote: I'm a Haskell newbie, and this post began as a scream for help. Extremely understandable - to be blunt, I don't really feel that Haskell is ready as a general-purpose production environment unless users are willing to invest considerably more than usual. Not only is it not as "batteries included" as one might like, sometimes it's necessary to build your own batteries! Ironically, the simple task of reading a file is more work than I expect precisely because I don't want to bother to handle exceptions. I mean, in some applications it's perfectly OK to let an exception go to the top. But in Haskell, you cannot read a file line by line without writing an exception handler, because end of file is an exception! as if a file does not normally have an end where the authors of these library functions came from? For the author of the original post ... can't make out what you actually found and tried, so you should know about "catch" in the Prelude, the basic exception handler. Donn Cave, [EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
Since everyone's been focusing on the IO so far, I wanted to take a quick stab at his mention of "green" vs. OS threads... I like the term "green", actually, as it's what my grandmother calls decaffeinated coffee, owing to the fact that decaf taster's choice has a big green plastic lid. Distrust all coffee that comes in a plastic lid, folks. Life is better that way... However, Haskell very much has real, caffeinated parallelism mechanisms. There is explicit concurrency, which says that things can happen at the same time (see Control.Concurrent) and there is the whole question of Glasgow Parallel Haskell and Data Parallel Haskell, which I won't really begin to cover, as Manuel Chakravarty and Simon Peyton Jones will do TONS better at explaining these than I can. I will however mention Control.Parallel and Control.Parallel.Strategies, because they're my personal favorite way of being parallel. The Haskell thread is semantically much like the Java thread, it's green, in other words, but you can control the number of real OS threads that Haskell threads are executed on at the command line. Thus you might call them "half caffeinated" But, at least with Control.Parallel.Strategies, they're SO much easier to use. There are a couple of caveats, but I'll give an example first. Let's say you're doing some heavy computer graphics, but you're doing it all in spherical coordinates (I do this all the time, which is why I'm using it as an example) and before you go to OpenGL, you need to transform everything into Carteisan coordinates. vertices :: [GL.Vertex3] -- a list of oh, say, 150,000 vertices or so in spherical coordinates sphericalToCart :: GL.Vertex3 -> GL.Vertex3 sphericalToCart (GL.Vertex3 r a z) = (GL.Vertex3 (r * cos a * sin z) (r * sin a * sin z) (r * cos a)) Now to convert them all, you'd just do a map sphericalToCart vertices and that would do a lazy conversion of everything, but since you know you're going to use all the vertices, strictness is just as well, and you can do strict things in parallel this way: parMap rwhnf sphericalToCart vertices or even more efficiently, map rwhnf sphericalToCart vertices `using` parListChunk 1024 That'll execute on all cores of your processor and do the same operation much faster, if you were going to have to do the entire operation anyway. -- Jeff On Sat, Feb 16, 2008 at 5:05 PM, Alan Carter <[EMAIL PROTECTED]> wrote: > Greetings Haskellers, > > I'm a Haskell newbie, and this post began as a scream for help. Having > slept on it I find myself thinking of Simon Peyton-Jones' recent > request for good use cases. Perhaps a frustrated - and doubting - > newbie can also provide a data point. If my worries are unfounded (and > I hope they are), I think it's significant that to me, today, they > seem real enough. Please understand that I'm not being negative for > the sake of it - rather I'm describing what Haskell looks like from > the outside. > > Let me put it this way. Imagine that two weeks ago my forward-thinking > and risk-embracing boss asked me to evaluate Haskell for the upcoming > Project X. Further imagine that she ensured I was able to sit in the > corner emitting curses for the whole two weeks, and on Monday I have > to provide my report. > > At this point, two weeks in, I would be forced to say that I have no > reason to believe that Haskell is useful for real world tasks. ghc is > an industrial strength compiler for a toy language. While remarkable > claims are made for it, in practice even the experts are often unable > to implement the most basic behaviours, and where they are able to > implement, they find that their program has become so complex that > they are unable to describe or discuss the result. Likely this is a > deep problem, not a shallow one. The Haskell community is in denial > over this, leading to phenomenal time wasting as one goes round and > round in circles playing word games with documentation. This risks a > return of the chronic embuggerance that we thought we'd escaped when > Vista appeared and the set of people who would have to write Windows > device drivers reduced to Hewlett Packard employees, Joanna Rutkowska > and criminals. When people enthuse about Haskell, we should run a > program called Cat.hs from the haskell.org website, throw fruit at > them and laugh. > > Strong words, but in all honesty I *want* to believe, and if I would > make such a report I imagine hundreds if not thousands would say the > same thing. I'm hoping I'm wrong about this, and what's actually > needed is some work on communication (perhaps from a production > programming point of view, which I'd be keen to help with). > > What got me started with Haskell was the video of an Intel employee > holding a Teraflops in his hand. I still remember the very silly > September 1991 edition of Scientific American, which asked if a > Teraflops would *ever* be built. What a stupid question! Stack up > enough
Re: [Haskell-cafe] Doubting Haskell
On Sat, Feb 16, 2008 at 06:50:03PM -0500, Cale Gibbard wrote: > On 16/02/2008, Alan Carter <[EMAIL PROTECTED]> wrote: > > Then when all this was going on, question number five appeared: What > > the hell are these "lightweight Haskell threads"? Are they some kind > > of green threads running non-preemptively inside a single OS thread? > > Are they OS threads that could run concurrently on multi-core > > hardware? If they are green threads (and it sounds like they are) then > > this is all an academic exercise which has no production application > > yet. > > > > Best wishes - and still hoping I'm wrong after all > > > > Alan Carter Yes, they are green threads. But not the stupid kind you are used to. Consider an operating system. You are running hundreds of threads in a typical system. You don't have hundreds of processors - let's be generous and say you have 8. Obviously these threads are in some sense 'green'. But they are still being run with (limited) parallelism! There is no reason to expect anything less of user-level 'green threads', and if all the systems you have been using are incapable of running threads in paralell, then all the systems you have been using are toys or broken. GHC is not a toy (in this regard), and contains a mini-operating system that schedules how ever many millions of threads you have onto a number of OS threads specified with the +RTS -N option. Stefan signature.asc Description: Digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On 16/02/2008, Alan Carter <[EMAIL PROTECTED]> wrote: > Then when all this was going on, question number five appeared: What > the hell are these "lightweight Haskell threads"? Are they some kind > of green threads running non-preemptively inside a single OS thread? > Are they OS threads that could run concurrently on multi-core > hardware? If they are green threads (and it sounds like they are) then > this is all an academic exercise which has no production application > yet. > > Best wishes - and still hoping I'm wrong after all > > Alan Carter Sorry for missing this question in my first response. The answer of course depends on the Haskell implementation in question, but of course, we're talking about GHC here. Haskell threads, in the sense of Control.Concurrent.forkIO, are essentially a sort of green thread which is scheduled by the Haskell runtime system. Threads can either be bound to a particular OS thread, or (as is default), not be bound to a particular OS thread, allowing the scheduler to manage n Haskell threads with m OS threads, where usually you want to set m to something like the number of processors in your machine. I'm a little hazy on the details, and perhaps someone more familiar with the GHC runtime can fill in some more details for you if you'd like. Aside from Concurrent Haskell (which was originally designed for single-processor concurrency and later extended to allow for scheduling threads to execute in multiple OS threads), there is Parallel Haskell, which is used to annotate pure computations for parallelism (but since they're pure, there is no concurrency). At its core, Parallel Haskell has an extremely simple programmer interface: par :: a -> b -> b Evaluation of an expression of the form (par x y) will cause x to be put in a queue of expressions to be evaluated by a worker on some OS thread, if there is free time, before resulting in y. If there is no time to evaluate x on some processor before it is eventually needed, then evaluation just proceeds normally, but if there is, then it won't need evaluation later, due to the usual sharing from lazy evaluation. >From this extremely simple form of parallel annotation, it's possible to build lots of interesting mechanisms for carrying out evaluation in parallel. You can read more about that in a paper titled "Algorithm + Strategy = Parallelism" by PW Trinder, K Hammond, H-W Loidl and Simon Peyton Jones, or check out the documentation for Control.Parallel.Strategies. - Cale ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On Sat, 16 Feb 2008, Alan Carter wrote: > I'm a Haskell newbie, and this post began as a scream for help. Extremely understandable - to be blunt, I don't really feel that Haskell is ready as a general-purpose production environment unless users are willing to invest considerably more than usual. Not only is it not as "batteries included" as one might like, sometimes it's necessary to build your own batteries! It's also sometimes hard to tell who the experts are, especially as many of us mostly work in fairly restricted areas - often way away from any IO, which is often a source of woe but whose avoidance leaves something of a hole in some coders' expertise. The current state of error-handling is something of a mess, and there are at least two good reasons for this: * Errors originating in the IO monad have a significantly different nature to those generated by pure code * We don't have[1] extensible variants, leading to the kinds of problem you complain about with scalability as the number of potential errors increases It's been a while since I was in the tutorial market, but I don't think many tutorials address the first point properly and it's a biggie. Most IO functions are written to throw exceptions in the IO monad if they fail, which forces you to handle them as such. So, here's an example: import System.IO fileName = "foo.bar" main = (do h <- openFile fileName ReadMode catch (hGetContents h >>= putStr) (\e -> do putStrLn "Error reading file" hClose h ) ) `catch` (\e -> putStrLn "Error opening file") On my machine, putting this through runhaskell results in a line "Error opening file", as unsurprisingly there's no foo.bar. Producing an error opening is harder work, whereas if I change filename to the program's source I get the appropriate output. It may say something about me that I didn't get this to compile first time - the culprit being a layout error, followed by having got the parms to openFile in the wrong order. Caveats so far: there are such things as non-IO exceptions in the IO monad, and catching them requires Control.Error.catch, which thankfully also catches the IO exceptions. If putStr were to throw an exception, I'd need yet another catch statement to distinguish it (though it'd be handled as-is). The sensible thing though is probably to use Control.Error.bracket (which is written in terms of catch) thusly: import System.IO import Control.Error filename = "foo.bar" main = bracket (openFile filename ReadMode) (\h -> hGetContents h >>= putStr) (\h -> hClose h) So from here, we have two remaining problems: 1) What about pure errors? 2) What about new exception types? I'll attack the second first, as there's a standard solution for IO and a similar approach can be adopted in pure code. It's a fairly simple, if arguably unprincipled, solution - use dynamic typing! Control.Error offers us throwDyn and catchDyn, which take advantage of facilities in Data.Dynamic. Pure code can make use of Data.Dynamic in a similar manner if needed. Personally I'm not too happy with this as a solution in most cases, but it's no worse than almost every other language ever - I guess Haskell's capabilities elsewhere have spoiled me. As for pure errors, there're essentially two steps: 1) Find a type that'll encode both the errors and the success cases (Maybe and Either are in common use) 2) Write the appropriate logic I'll not go into step 1 much, most of the time you want to stick with Maybe or Either (there's a punning mnemonic that "if it's Left it can't have gone right" - it's usual to use Right for success and Left for failure). The second point is where you get to adopt any approach from writing out all the case analysis longhand to using a monad or monad transformer based around your error type. It's worth being aware of Control.Monad.Error at this point, though personally I find it a little irritating to work with. By the time you're building customised monads, you're into architecture land - you're constructing an environment for code to run in and defining how that code interfaces with the rest of the world, it's perhaps the closest thing Haskellers have to layers in OO design. If you find you're using multiple monads (I ended up with three in a 300 line lambda calculus interpreter, for example - Parsec, IO and a custom-built evaluation monad) then getting things right at the boundaries is important - if you've got that right and the monad's been well chosen then everything else should come easily. Thankfully, with a little practice it becomes possible to keep your code factored in such a manner that it's easy to refactor your way around the occasional snarl-ups that happen when a new change warrants re-architecting. That or someone just won buzzword bingo, anyway. Anyway, I hope this's been helpful. [1] There are ways of impl
Re: [Haskell-cafe] Doubting Haskell
I'm going to try to respond the the main practical question in this message; perhaps others will feel up to addressing the more philosophical aspects. (I see now that Cale has beaten me to the punch, but I guess I'll post this anyways...) > Greetings Haskellers, [snip quite a bit of discussion] > Great. Next, translate the bit that > says (pseudocode): > > if(attempt_file_open) > if(attempt_file_read) > process > > That's it. No fancy, complex error messages. Just check the error > returns and only proceed if I have something to proceed with. Like > grown-ups do. I *will* check my error returns. I have tormented too > many newbies to *ever* consider doing anything else. If I cannot check > my error returns I will not write the program. You'll find in Haskell that the normal way of handling things like I/O errors is to use the exception handling mechanism. There aren't usually "error returns" to check. Instead you usually place error handlers at the positions where you want to be notified of errors using the "catch" or "handle" functions. If you want to you can convert any IO action into one with an error return by using the "try" function. The Control.Exception module is probably the one you want to check out. http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Exception.html [snip more discussion] > If so, > I sincerely suggest an example or two, like the small but well formed > programs in K&R, Stroustrup or Gosling saying things like: > > if((fp = fopen(...)) != NULL) > { > if(fgets(...) != NULL) > { > printf(...); > } > > fclose(...) > } Here is a quick example I whipped up. It includes both a pretty direct translation of the above code, and another version which is a little more idiomatic. Rob Dockins --- code follows import Control.Exception import System.IO main = direct_translation direct_translation = do tryh <- try (openFile "test.txt" ReadMode) case tryh of Left err -> print err Right h -> do tryl <- try (hGetLine h) case tryl of Left err -> do print err; hClose h Right l -> do putStrLn l hClose h the_way_I_would_do_it = handle (\err -> print err) $ bracket (openFile "test.txt" ReadMode) hClose $ \h -> do l <- hGetLine h putStrLn l ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Doubting Haskell
On 16/02/2008, Alan Carter <[EMAIL PROTECTED]> wrote: > Greetings Haskellers, > > I'm still hoping that this is solvable. That the instinctive > priorities of production programmers are just different to those of > researchers, and in fact it *is* possible to open a file *and* read > it, checking *both* error returns, without being driven insane. If so, > I sincerely suggest an example or two, like the small but well formed > programs in K&R, Stroustrup or Gosling saying things like: > > if((fp = fopen(...)) != NULL) > { > if(fgets(...) != NULL) > { > printf(...); > } > > fclose(...) > } > > Best wishes - and still hoping I'm wrong after all > > Alan Carter Well, first of all, have you read the documentation for System.IO? http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-IO.html That has all the corresponding functions you need. I'm not sure I understand completely how you managed to spend two weeks struggling with this before asking. Two minutes on #haskell, or a quick question about how to open and read a file should have got you a useful response. :) First, I'll write the program in a straightforward, but extremely explicit manner, handling possible errors and managing clean up explicitly. This code is rather verbose, so I'll then show some other less verbose ways to handle things while still maintaining safety. So, the first version: import System.IO import Control.Exception (try) main = do mfh <- try (openFile "myFile" ReadMode) case mfh of Left err -> do putStr "Error opening file for reading: " print err Right fh -> do mline <- try (hGetLine fh) case mline of Left err -> do putStr "Error reading line: " print err hClose fh Right line -> putStrLn ("Read: " ++ line) Okay, so this is hopefully fairly self-explanatory to a C-programmer. The only potentially-confusing part is the function 'try', imported from Control.Exception. What it does is to catch all possible exceptions, and reflect them through the return value of the action. If an exception is thrown, 'try' will catch it, and give us a value of the form (Left e), for e being the exception. If instead, the operation succeeds without an exception, we get a value (Right x), where x is the normal return value of the action. The successive 'case' expressions are used to pattern match on this, and handle the errors by printing out an explanatory message. Some example runs of this program: [EMAIL PROTECTED]:~$ rm myFile [EMAIL PROTECTED]:~$ ./read Error opening file for reading: myFile: openFile: does not exist (No such file or directory) [EMAIL PROTECTED]:~$ touch myFile [EMAIL PROTECTED]:~$ ./read Error reading line: myFile: hGetLine: end of file [EMAIL PROTECTED]:~$ echo "hello" >> myFile [EMAIL PROTECTED]:~$ ./read Read: hello This program actually does more error handling than your example C program, so let's tone it down a bit, and make use of some nice IO operations provided to handle errors and clean things up safely in the event of a failure. import System.IO main = withFile "myFile" ReadMode $ \fh -> do line <- hGetLine fh putStrLn ("Read: " ++ line) The function 'withFile' takes a filename, a mode in which to open the file, and a function, taking a filehandle, and giving an action to be performed with that handle, and wraps that action up inside an exception handler, which ensures that the file handle is safely closed if an exception is thrown. (This doesn't matter much in our small example, but I'm sure you'll appreciate how that's an important thing.) We don't handle the exceptions explicitly in this program, but we still could. There are a host of exception-handling mechanisms in Control.Exception, ranging from simple value-oriented things like try, to more explicit operations for wrapping things in exception handlers, like catch: catch :: IO a -> (Exception -> IO a) -> IO a Or to get more selective: catchJust :: (Exception -> Maybe b) -> IO a -> (b -> IO a) -> IO a Which takes a function that gets to decide whether to handle the exception, and at the same time, transform the exception in some way before passing it on to the exception handler. For more information about exceptions, check out the documentation for Control.Exception here: http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Exception.html I assure you that Haskell is a very reasonable programming language in which to write safe and correct programs. There are whole companies founded on writing high-assurance software in Haskell. If you have more questions, I would be happy to answer them, either here, or perhaps more comfortably, on IRC, #haskell on irc.freenode.net. It's a very beginner friendly channel, and asking questions there is a great way to learn the language
[Haskell-cafe] Doubting Haskell
Greetings Haskellers, I'm a Haskell newbie, and this post began as a scream for help. Having slept on it I find myself thinking of Simon Peyton-Jones' recent request for good use cases. Perhaps a frustrated - and doubting - newbie can also provide a data point. If my worries are unfounded (and I hope they are), I think it's significant that to me, today, they seem real enough. Please understand that I'm not being negative for the sake of it - rather I'm describing what Haskell looks like from the outside. Let me put it this way. Imagine that two weeks ago my forward-thinking and risk-embracing boss asked me to evaluate Haskell for the upcoming Project X. Further imagine that she ensured I was able to sit in the corner emitting curses for the whole two weeks, and on Monday I have to provide my report. At this point, two weeks in, I would be forced to say that I have no reason to believe that Haskell is useful for real world tasks. ghc is an industrial strength compiler for a toy language. While remarkable claims are made for it, in practice even the experts are often unable to implement the most basic behaviours, and where they are able to implement, they find that their program has become so complex that they are unable to describe or discuss the result. Likely this is a deep problem, not a shallow one. The Haskell community is in denial over this, leading to phenomenal time wasting as one goes round and round in circles playing word games with documentation. This risks a return of the chronic embuggerance that we thought we'd escaped when Vista appeared and the set of people who would have to write Windows device drivers reduced to Hewlett Packard employees, Joanna Rutkowska and criminals. When people enthuse about Haskell, we should run a program called Cat.hs from the haskell.org website, throw fruit at them and laugh. Strong words, but in all honesty I *want* to believe, and if I would make such a report I imagine hundreds if not thousands would say the same thing. I'm hoping I'm wrong about this, and what's actually needed is some work on communication (perhaps from a production programming point of view, which I'd be keen to help with). What got me started with Haskell was the video of an Intel employee holding a Teraflops in his hand. I still remember the very silly September 1991 edition of Scientific American, which asked if a Teraflops would *ever* be built. What a stupid question! Stack up enough VIC20s and eventually you'll get a Teraflops. The question should have been "when". Now it's the size of a CD, and only 80 cores are needed. Unfortunately keeping 80 cores running is tricky. I know this from writing some heavy parallel stuff in the mid-90s. It was all quite clever in it's day. Chuck bloated and unguessable CORBA, do something light with TCP/IP (Beuwolf took that to extremes). Neat linkage like rpcgen gave C, so that I could run fast on an SMP Sequent with 30 cores or on a floorfull of about 70 Sun pizza boxen at night. Unfortunately despite having a nice framework, tracing rays is still hard (the rays and medium were... interesting). Making a problem parallel required a sneaky and dedicated person's sincere skull-sweat. Worse, the solutions so produced had a horrible structural instability about them. Just a small change to the requirement could require a computed value where it wasn't needed before, so that it resulted in big changes to the implementation. The skull-sweating would be needed all over again. (Remember that the big point about objects, which e.g. Booch always emphasized, was that a well chosen set of classes maps well to the domain and so reduces such structural instability.) Even then, it was devilish hard to keep 70 "cores" busy. So watching the Intel guy got my klaxons going. We now need to be able to do parallel with ease. Functional programming just got really important. It's years since I last played with Scheme, but I quickly moved on because I could see the "which Scheme" problem becoming a millstone round everyone's necks outside of research contexts. Ditto Lisp. So Haskell. Grown-up compiler, one standard and (apparently) a decent corpus of example code and tutorials. I might be an imperative programmer, but I do lapse - for example I find it very easy to generate swathes of cross referenced documentation using m4. My head goes kind of weird after a few hours, such that m4 seems sane and it's the rest of the world that's ungainly, so maybe it should be banned like DMT, but I like it. I felt able to enter the functional world. I'll omit the first week of suffering, which I see is a well documented rite of passage. (Although most evaluators will have left the building by the end of week one so it's not helping popularity. Perhaps there could be Squires of the Lambda Calculus who haven't done the vigil, mortification of flesh and so on?) Eventually a 3 page introduction on the O'Reilly website together with a good document called "Haskell for C Programmers"