Equivalent of if/then/else for IO Bool?

Is there some sort of equivalent of the if/then/else construct for use in the IO monad? For instance the following can get quite tedious:
do bool <- doesFileExist filename if bool then sth else sth'
Is there a more compact way of writing that? Something akin to:
condM (doesFileExist filename) (sth) (sth')
Or maybe there's a more sensible way of doing the above that I've missed. I seem to use endless alternate conditions sometimes and there's bound to be a better way.

On 11/23/06, Dougal Stanton
Is there some sort of equivalent of the if/then/else construct for use in the IO monad? For instance the following can get quite tedious:
do bool <- doesFileExist filename if bool then sth else sth'
Is there a more compact way of writing that? Something akin to:
condM (doesFileExist filename) (sth) (sth')
Maybe there is one built in but don't know it or see anything in hoogle. I'd use something like the following (and then just make it a standard part of the libraries I use personally): import Control.Monad if' b t e = if b then t else e ifM = liftM3 if' which gives ifM :: (Monad m) => m Bool -> m t -> m t -> m t HTH, Jason

Jason Dagit wrote:
On 11/23/06, Dougal Stanton
wrote: Is there some sort of equivalent of the if/then/else construct for use in the IO monad? For instance the following can get quite tedious:
do bool <- doesFileExist filename if bool then sth else sth'
Is there a more compact way of writing that? Something akin to:
condM (doesFileExist filename) (sth) (sth')
Maybe there is one built in but don't know it or see anything in hoogle. I'd use something like the following (and then just make it a standard part of the libraries I use personally):
import Control.Monad
if' b t e = if b then t else e ifM = liftM3 if'
which gives ifM :: (Monad m) => m Bool -> m t -> m t -> m t
No! You can really screw up this way... Your function will perform the effects of the Bool and *both* branch computation in sequence, then use the returned Bool value to select between the returned 'then' value and the returned 'else' value. Do not use it to operate machinery! *Grr> ifM (Just True) (Just 3) Nothing Nothing More care required! Conor

On 11/23/06, Conor McBride
*Grr> ifM (Just True) (Just 3) Nothing Nothing
More care required!
Thank you. Now that you point this out I recall that I've made this mistake in the past with (&&), I once wrote something like liftM2 (&&). I forget that the liftM* family binds the parameters before passing them on. Hopefully the lesson will stick this time. Jason

Jason Dagit wrote:
On 11/23/06, Conor McBride
wrote: *Grr> ifM (Just True) (Just 3) Nothing Nothing
More care required!
Thank you. Now that you point this out I recall that I've made this mistake in the past
You and me both. It's really insidious and can hide for weeks, looking perfectly innocent and doing all sorts of mad stuff. Ross and I talk about this issue in our 'Applicative' paper. It's really what distinguishes monads from applicative functors. Monads let you use the value from one computation to choose which *computation* to run next; applicative functors fix the structure of computations but allow you to do what you like with the *values*. So, again, I know it's not going to happen in the immediate future, but I hope we will eventually adopt Ashley's Functor Hierarchy proposal, then shift the liftM family to the Applicative layer, where they belong. The fact that the above ifM can be typed with Applicative m, not just Monad m, is the clue to why it is broken. All the best Conor

Dougal Stanton wrote:
Is there some sort of equivalent of the if/then/else construct for use in the IO monad? For instance the following can get quite tedious:
do bool <- doesFileExist filename if bool then sth else sth'
Is there a more compact way of writing that? Something akin to:
condM (doesFileExist filename) (sth) (sth')
Or maybe there's a more sensible way of doing the above that I've missed. I seem to use endless alternate conditions sometimes and there's bound to be a better way.
Roll your own control structures! Haskell has higher order functions for a reason. This should do the trick (untested): condM condAction thenBranch elseBranch = do bool <- condAction if bool then thenBranch else elseBranch (Hack it into ghci or hugs to find out the type, it's a bit more general than what you need.) Cheers Ben

You can use 'when' or 'unless' from the module Control.Monad, but they
each have only one branch, see:
http://members.chello.nl/hjgtuyl/tourdemonad.html#unless
and
http://members.chello.nl/hjgtuyl/tourdemonad.html#when
You can create a monadic 'if' like this (in an interactive session):
Control.Monad> let ifM p a b = do { p' <- p; if p' then return a else
return b } in ifM (Just True) 1 2
Just 1
Met vriendelijke groet,
Henk-Jan van Tuyl
--
On Thu, 23 Nov 2006 22:34:49 +0100, Dougal Stanton
Is there some sort of equivalent of the if/then/else construct for use in the IO monad? For instance the following can get quite tedious:
do bool <- doesFileExist filename if bool then sth else sth'
Is there a more compact way of writing that? Something akin to:
condM (doesFileExist filename) (sth) (sth')
Or maybe there's a more sensible way of doing the above that I've missed. I seem to use endless alternate conditions sometimes and there's bound to be a better way. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- http://Van.Tuyl.eu/ -- Using Opera's revolutionary e-mail client: https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433

Hello Dougal, Friday, November 24, 2006, 12:34:49 AM, you wrote:
Is there some sort of equivalent of the if/then/else construct for use in the IO monad? For instance the following can get quite tedious:
just a list of my control structures: whenM cond action = do allow <- cond when allow action unlessM = whenM . liftM not whenJustM x action = x >>= maybe (return Nothing) action whenJustM_ x action = x >>= maybe (return ()) (action .>> return ()) foreach = flip mapM for = flip mapM_ on = flip when repeat_foreverM action = do action repeat_foreverM action repeat_whileM inp cond out = do x <- inp if (cond x) then do out x repeat_whileM inp cond out else return x repeat_untilM action = do done <- action when (not done) $ do repeat_untilM action doChunks size chunk action = case size of 0 -> return () _ -> do let n = minI size chunk action (fromIntegral n) doChunks (size-n) chunk action recursiveM action x = action x >>= mapM_ (recursiveM action) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Dougal Stanton wrote:
Is there some sort of equivalent of the if/then/else construct for use in the IO monad? For instance the following can get quite tedious:
do bool <- doesFileExist filename if bool then sth else sth'
Is there a more compact way of writing that? Something akin to:
condM (doesFileExist filename) (sth) (sth')
I'd suggest cond t f True = t cond t f False = f and then you use it like doesFileExist filename >>= cond sth sth' I find it strange that we have 'maybe' for 'Maybe', 'either' for 'Either', 'foldr' for '[]', but a special syntactic form for 'Bool'. Why is there no 'cond' in the Prelude? -Udo -- There is no snooze button on a cat who wants breakfast.

Dougal Stanton wrote:
Is there some sort of equivalent of the if/then/else construct for use in the IO monad? For instance the following can get quite tedious:
do bool <- doesFileExist filename if bool then sth else sth'
Is there a more compact way of writing that? Something akin to:
condM (doesFileExist filename) (sth) (sth')
Or maybe there's a more sensible way of doing the above that I've missed. I seem to use endless alternate conditions sometimes and there's bound to be a better way.
I don't know any existing function like this in the current libs. Here i paste probably a possible implementation for one. if' :: (Monad m) => m Bool -> m b -> m b -> m b if' mb mt mf = mb >>= if'' where if'' b = if b then mt else mf Regards,
participants (8)
-
Benjamin Franksen
-
Bulat Ziganshin
-
Conor McBride
-
Dougal Stanton
-
Henk-Jan van Tuyl
-
Jason Dagit
-
Luis F. Araujo
-
Udo Stenzel