Re: [Haskell-cafe] Haskell and C++ program

2009-01-15 Thread Yitzchak Gale
Sukit Tretriluxana:
 I was looking around Stroustrup's website and found
 a simple program... I wondered how a Haskell
 program equivalent to it looks like...

 main = E.catch (interact reverseDouble) (\_ - print format error)
  toDoubles = map (read::String-Double)

For a safe program in Haskell, we would not normally use
an unsafe function like read, and then try to rescue it by
catching IO exceptions. Instead, we would write the program
safely to begin with. Something like this (building on
Jonathan's idea):

import Data.Maybe (listToMaybe)

main = interact reverseDouble

reverseDouble =
  unlines . intro .
  maybe [format error] (map show . reverse) .
  mapM (readMaybe :: String - Maybe Double) .
  takeWhile (/= end) . words
   where
 intro l =
   (read  ++ show (length l) ++  elements) :
   elements in reversed order :
   l

readMaybe :: Read a = String - Maybe a
readMaybe = listToMaybe . map fst . reads

The function readMaybe returns the pure value
Nothing if there is a format error instead of throwing
an IO exception. It has been proposed to make it part
of the standard libraries - I'm not sure what the status
is of that process.

Regards,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell and C++ program

2009-01-14 Thread Sukit Tretriluxana
Hi all,

I was looking around Stroustrup's website and found a simple program that he
showed how standard library can be used to make the program succinct and
safe. See http://www.research.att.com/~bs/bs_faq2.html#simple-program. I
wondered how a Haskell program equivalent to it looks like and I came up
with the code below.

import qualified Control.Exception as E

main = E.catch (interact reverseDouble) (\_ - print format error)

reverseDouble = unlines . doIt . words
   where doIt = intro . toStrings . reverse . toDoubles . input
 toDoubles = map (read::String-Double)
 toStrings = map show
 input = takeWhile (/= end)
 intro l = (read  ++ (show $ length l) ++  elements) :
   elements in reversed order :

I'm not a Haskell expert and I am pretty sure that this is not the optimal
form a Haskell program that's equivalent to the C++ one. So I would like to
see, from the Haskell experts in this group, how else (of course better
form) such a program can be written.

Thanks,
Ed
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell and C++ program

2009-01-14 Thread Jonathan Cast
On Wed, 2009-01-14 at 12:45 -0800, Sukit Tretriluxana wrote:
 Hi all,
 
 I was looking around Stroustrup's website and found a simple program
 that he showed how standard library can be used to make the program
 succinct and safe. See
 http://www.research.att.com/~bs/bs_faq2.html#simple-program. I
 wondered how a Haskell program equivalent to it looks like and I came
 up with the code below.
 
 import qualified Control.Exception as E
 
 main = E.catch (interact reverseDouble) (\_ - print format error)
 
 reverseDouble = unlines . doIt . words
where doIt = intro . toStrings . reverse . toDoubles . input
  toDoubles = map (read::String-Double)
  toStrings = map show
  input = takeWhile (/= end)
  intro l = (read  ++ (show $ length l) ++  elements) :
elements in reversed order :

My only criticism is that I find code written with lots of secondary
definitions like this confusing; so I would inline most of the
definitions:

  reverseDouble =
unlines
  . intro
  . map show
  . reverse
  . map (read :: String - Double)
  . takeWhile (/= end)
  . words
where
  intro l =
(read  ++ show (length l) ++  elements) :
elements in reversed order :
l

I observe also in passing that the cast on read is somewhat inelegant;
in a real application, the consumer of map read's output would specify
its type sufficiently that the cast would be un-necessary.

For example, the program could be specified to compute sines instead:

main = E.catch (interact unlines . intro . map (show . sin . read) .
words) $ \ _ - print format error
  where
intro l =
  (read  ++ show (length l) ++  arguments) :
  computed sins :
  l

(Others will no doubt object to the use of lazy I/O.  I disagree in
principle with those objections.)

jcc

PS Stroustrup's comments about vectors are at best half right; push_back
may extend the vector's length correctly, but operator[] on a vector
certainly does not do bounds checking.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell and C++ program

2009-01-14 Thread Peter Verswyvelen


 PS Stroustrup's comments about vectors are at best half right; push_back
 may extend the vector's length correctly, but operator[] on a vector
 certainly does not do bounds checking.


Sure it does, depending on how you configured the STL library. But this is
off topic :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Haskell and C++ program

2009-01-14 Thread Bulat Ziganshin
Hello Jonathan,

Thursday, January 15, 2009, 1:41:23 AM, you wrote:

   reverseDouble =
 unlines
   . intro
   . map show
   . reverse
   . map (read :: String - Double)
   . takeWhile (/= end)
   . words

using arrows, this may be reversed:

  reverseDouble =
  words
   takeWhile (/= end)
  ...

 I observe also in passing that the cast on read is somewhat inelegant;
 in a real application, the consumer of map read's output would specify
 its type sufficiently that the cast would be un-necessary.

in small scripts explicit read casts are rather common


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe