Hello,
| Just wondering if someone uses Hugs for writing Unix-Shell Scripts. Or
| what would you think about a Haskell-Shell.
These are two quite separate issues of course. I can comment on the first
one.
A while ago, we had a discussion among some Haskell hackers here at
Chalmers how we could make the writing of shell scripts in Haskell easier.
Some of us had been bitten by the fact that, in Haskell, you _can_ call
shell commands like "rm" and "cp", but it is not easy to use shell
commands like "date", "grep", "lynx" or "metamail".
This is because the only official way to call a shell command in Haskell
is:
system :: String -> IO ExitCode
And there is _no_ handle to the output of the command! An obvious hack is
to use redirecting; here is how you implement a simple date function in
Haskell:
date :: IO String
date =
do system "date > /tmp/answer"
readFile "/tmp/answer"
But this gets hairy after a while. We came to the conclusion that it would
be extremely handy to have some kind of library supporting the following
functions:
module Unix where
( Command --:: String
, sys --:: Command -> IO ()
-- using stdin and stdout
, sysIn --:: Command -> String -> IO ()
, sysOut --:: Command -> IO String
, sysInOut --:: Command -> String -> IO String
-- ...
)
Now we can define nice combinators (monadic composition, etc.) to pipe
commands, etc.
I implemented these functions and a couple more (dealing with lazily
generating output) in Hugs, using dynamic named pipe generation and
redirecting. This is a hack; it would be much nicer to have a function
like "sysInOut" builtin in Hugs (Haskell98).
I have used the module to implement a great number of Haskell shell
scripts, including the following:
- a mail-filter, redirecting a summary of my e-mail to
my mobile phone, and redirecting messages from my mobile
phone to e-mail.
- a script connecting several theorem provers together,
gathering, redirecting and interpreting their respective outputs.
- a sort of xbiff, displaying the e-mail's sender's names.
- a script managing the weekly functional programming meetings
at Calmers.
- a script that uses several different search engines on the web
to search for a keyword, displaying the resulting URLs.
- a script that checks every so many hours popular cartoon sites
(Dilbert, Calvin and Hobbes) and displays a new episode if there is
one.
etc.
If people are interested, I can post my Unix module on this list. Note
that the module itself is a terrible hack! I would really like it to be
possible in Hugs to get a handle to the input and output of a system
command.
Regards,
Koen.
--
Koen Claessen http://www.cs.chalmers.se/~koen
phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED]
-----------------------------------------------------
Chalmers University of Technology, Gothenburg, Sweden