
Hello all. I was just thinking that there ought to be a better way to write the following code. It seems to be a common case that within a 'do' I bind a variable that I only intend to use once, in an if or case statement. It occurred to me that there ought to be a better way to do this. For example, it seems like the following code: whatisit :: String -> IO String whatisit f = do isdir <- doesDirectoryExist f if isdir then return "dir" else do isfile <- doesFileExist f if isfile then return "file" else return "nothing" could be replaced by something like: whatisit :: String -> IO String whatisit f = do ifM doesDirectoryExist f then return "dir" else ifM doesFileExist f then return "file" else return "nothing" Is there any way I could do something like this? -- David Roundy http://civet.berkeley.edu/droundy/

whatisit :: String -> IO String whatisit f = do ifM doesDirectoryExist f then return "dir" else ifM doesFileExist f then return "file" else return "nothing"
Is there any way I could do something like this?
Not with the syntactic sugar of 'if'. But you can write [warning: untested code ahead] ifM :: IO Bool -> IO a -> IO a -> IO a ifM test yes no = do b <- test if b then yes else no And then ifM (doesDirectoryExist f) (return "dir") (ifM (doesFileExist f) (return "file") (return "nothing)) ) Arjan

Not with the syntactic sugar of 'if'. But you can write [warning: untested code ahead]
ifM :: IO Bool -> IO a -> IO a -> IO a ifM test yes no = do b <- test if b then yes else no
There is a little trick that allows you to "sort-of" get the syntactic sugar. It goes like this [warning: also untested code]:
data Then_ = Then_
data Else_ = Else_
then_ = Then_
else_ = Else_
ifM :: IO Bool -> Then_ -> IO a -> Else_ -> IO a -> IO a
ifM test Then_ yes Else_ no = do
b <- test
if b then yes else no
and then you can write
ifM (doesDirectoryExist f)
then_ (return "dir")
else_ (ifM (doesFileExist f)
then_ (return "file")
else_ (return "nothing"))
Note that this doesn't save you any parentheses, sadly, although there may be tricky ways to do that.
References:
LATOS uses this syntax; see http://www.dsse.ecs.soton.ac.uk/techreports/97-1.html
[Pieter H. Hartel, 1997, LATOS - A Lightweight Animation Tool for Operational Semantics]
http://www.eecs.usma.edu/Personnel/okasaki/pubs.html#hw02 [Chris Okasaki, Haskell Workshop 2002, Techniques for embedding postfix languages in Haskell]
Enjoy!
--KW 8-)
--
Keith Wansbrough

Here's another way to sugar if-then-else that works like C's ?: and Lisp's cond: import Monad (liftM3) import Directory (doesFileExist, doesDirectoryExist) infix 1 ?, ?? (?) :: Bool -> a -> a -> a (c ? t) e = if c then t else e (??) :: (Monad m) => m Bool -> m a -> m a -> m a (??) = liftM3 (?) main = do print $ 1>2 ? 1 $ 2 print =<< fileType "foo" fileType :: String -> IO String fileType name = doesDirectoryExist name ?? return "dir" $ doesFileExist name ?? return "file" $ return "nothing" -- Dean Keith Wansbrough wrote:
Not with the syntactic sugar of 'if'. But you can write [warning: untested code ahead]
ifM :: IO Bool -> IO a -> IO a -> IO a ifM test yes no = do b <- test if b then yes else no
There is a little trick that allows you to "sort-of" get the syntactic sugar. It goes like this [warning: also untested code]:
data Then_ = Then_ data Else_ = Else_ then_ = Then_ else_ = Else_
ifM :: IO Bool -> Then_ -> IO a -> Else_ -> IO a -> IO a ifM test Then_ yes Else_ no = do b <- test if b then yes else no
and then you can write
ifM (doesDirectoryExist f) then_ (return "dir") else_ (ifM (doesFileExist f) then_ (return "file") else_ (return "nothing"))
Note that this doesn't save you any parentheses, sadly, although there may be tricky ways to do that.
References:
LATOS uses this syntax; see http://www.dsse.ecs.soton.ac.uk/techreports/97-1.html [Pieter H. Hartel, 1997, LATOS - A Lightweight Animation Tool for Operational Semantics]
http://www.eecs.usma.edu/Personnel/okasaki/pubs.html#hw02 [Chris Okasaki, Haskell Workshop 2002, Techniques for embedding postfix languages in Haskell]
Enjoy!
--KW 8-) -- Keith Wansbrough
http://www.cl.cam.ac.uk/users/kw217/ University of Cambridge Computer Laboratory.

On Thu, Feb 13, 2003 at 01:21:35PM -0500, Dean Herington wrote:
Here's another way to sugar if-then-else that works like C's ?: and Lisp's cond:
import Monad (liftM3) import Directory (doesFileExist, doesDirectoryExist)
infix 1 ?, ??
(?) :: Bool -> a -> a -> a (c ? t) e = if c then t else e
(??) :: (Monad m) => m Bool -> m a -> m a -> m a (??) = liftM3 (?)
main = do print $ 1>2 ? 1 $ 2 print =<< fileType "foo"
fileType :: String -> IO String fileType name = doesDirectoryExist name ?? return "dir" $ doesFileExist name ?? return "file" $ return "nothing"
That's pretty nice (although not quite as nice as it would be to be able to use real ifs with no extra parentheses). Any idea how to do something like this with a case? I imagine it's considerably harder, since case statements do pattern matching, which is rather heavy duty syntactic sugar. I often have functions like mp <- fun case mp of Nothing -> deal with error Just p -> do something with p where it would be much nicer to be able to just use caseM fun of Nothing -> deal with error Just p -> do something with p which would avoid confusion when reading the code as to whether the value mp may be used later in the function. Any ideas how to do something like this? -- David Roundy http://civet.berkeley.edu/droundy/

On Thu, 13 Feb 2003, David Roundy wrote:
On Thu, Feb 13, 2003 at 01:21:35PM -0500, Dean Herington wrote:
Here's another way to sugar if-then-else that works like C's ?: and Lisp's cond:
import Monad (liftM3) import Directory (doesFileExist, doesDirectoryExist)
infix 1 ?, ??
(?) :: Bool -> a -> a -> a (c ? t) e = if c then t else e
(??) :: (Monad m) => m Bool -> m a -> m a -> m a (??) = liftM3 (?)
main = do print $ 1>2 ? 1 $ 2 print =<< fileType "foo"
fileType :: String -> IO String fileType name = doesDirectoryExist name ?? return "dir" $ doesFileExist name ?? return "file" $ return "nothing"
That's pretty nice (although not quite as nice as it would be to be able to use real ifs with no extra parentheses). Any idea how to do something like this with a case? I imagine it's considerably harder, since case statements do pattern matching, which is rather heavy duty syntactic sugar. I often have functions like
mp <- fun case mp of Nothing -> deal with error Just p -> do something with p
where it would be much nicer to be able to just use
caseM fun of Nothing -> deal with error Just p -> do something with p
which would avoid confusion when reading the code as to whether the value mp may be used later in the function. Any ideas how to do something like this?
Not really. As you point out, the difficulty is the patttern matching. However, I often use `maybe` in cases such as your example: fun >>= maybe (deal with error) (\p -> do something with p) as long as the alternatives are not too long. Then it's very clear that there are no other references to the scrutinee. And, of course, there are other functions like `maybe` for other types. The Prelude defines `either`, and I've defined `bool`, `ordering`, `list`, and `tuple<n>`. -- Dean

There is now a way to do this :). What used to be the Haskell Array Preprocessor is not the Haskell STate Preprocessor (STPP) and it supports now many things: - sugared array reading/writing/updating - sugared hash table reading/writing/updating - monadic if - monadic case Get it from http://www.isi.edu/~hdaume/STPP/ using stpp, you would write monadic case expressions as:
mcase fun of Nothing -> ...
etc, just as you wanted :). mif works the same way (the 'm' prefix was chosen to look like 'mdo'). Of course, it still supprots array reading/writing, such as: do a <- newArray (0,100) 0 a[|5|] <- 7 a[|6|] <- 8 a[|6|] <<- a[|5|] * 2 + a[|6|] furthermore, it supports hash table reading/writing (based on the hash table implementation found at http://www.isi.edu/~hdaume/haskell/Util), as in: do ht <- emptyHT ht{|"hello"|} <- "goodbye" print ht{|"hello"|} All of this works both in the IO monad and the ST monad. Comments/Suggestions/Bug reports to me please. -- Hal Daume III "Computer science is no more about computers | hdaume@isi.edu than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
mp <- fun case mp of Nothing -> deal with error Just p -> do something with p
where it would be much nicer to be able to just use
caseM fun of Nothing -> deal with error Just p -> do something with p
which would avoid confusion when reading the code as to whether the value mp may be used later in the function. Any ideas how to do something like this?

G'day all. On Thu, Feb 13, 2003 at 02:54:42PM -0500, David Roundy wrote:
That's pretty nice (although not quite as nice as it would be to be able to use real ifs with no extra parentheses). Any idea how to do something like this with a case? http://www.haskell.org/mailman/listinfo/haskell-cafe
In the case of Maybe, what you're really trying to do there is a kind of exception handling. You may or may not be better off using a real exception monad transformer on top of IO (or whatever the underlying monad is). One possibility is Control.Monad.Error (fromt he MTL). Here's another possibility: http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/hfl/hfl/mtl/Negate.hs?rev=1.2 I know this didn't directly answer your question, but it's good to explore the design space. Cheers, Andrew Bromage
participants (6)
-
Andrew J Bromage
-
Arjan van IJzendoorn
-
David Roundy
-
Dean Herington
-
Hal Daume III
-
Keith Wansbrough