Proposal: add ifM and whenM to Control.Monad

Evan Laforge qdunkan at gmail.com
Mon Apr 21 22:13:01 UTC 2014


On Mon, Apr 21, 2014 at 2:55 PM, Greg Weber <greg at gregweber.info> wrote:
> agreed. additionally, while when/unless/whenM/unlessM gets rid of a `return
> ()` branch, ifM does not.
> In situations where I have branching code containing more than just properly
> curried functions I will prefer an intermediate variable if I get to use the
> language built-in if/then/else that gets syntax highlighted and avoids
> parentheses. `$ do` avoids parentheses with when/unless/whenM/unlessM, but
> with a second branch the parentheses return for both.

Looking at my own uses of 'ifM', I use it either when the branches are short:

    ifM ((<=) <$> Pitches.pitch_nn prev_pitch <*> Pitches.pitch_nn this_pitch)
        (return (Pitch.Diatonic (-1))) (return (Pitch.Diatonic 1))

    ifM (Maybe.isJust <$> get)
        cmd_advance (cmd_set play_selected_tracks)

    ifM (not . wanted <$> State.get_track_title track_id)
        (return Nothing) (f block_id track_id events)

Or when the first branch is a short exception:

    ifM (Directory.doesFileExist fn) (return (Just fn)) $
    ifM (Directory.doesFileExist (fn ++ "c"))
        (return (Just (fn ++ "c"))) (return Nothing)

    stretch_to_1 <- ifM Internal.is_root_block (return id) $ do

    ) $ \omit _args deriver -> ifM (Util.chance omit) (return mempty) $ do

Granted that first one is not very good.


More information about the Libraries mailing list