Benja Fallenstein wrote:
> Hi Peter,
> 
> 2007/6/25, peterv <[EMAIL PROTECTED]>:
>> I'm baffled. So using the Arrow abstraction (which I don't know yet) would
>> solve this problem? How can (perfectActionB x) be checked with without
>> ever executing performActionA which evaluates to x? This can only be done
>> when x is a constant expression no?
> 
> Arrows separate the action -- 'performActionB' -- from the argument --
> 'x', so you can look at the action before you have to compute the
> argument to it. Of course, this means that you can no longer compute
> the action from the argument -- that is, 'if x then performActionB
> else performActionC' is something you can't directly do; you have to
> use a choice primitive instead, which explicitly says "use one of
> these two arrows depending on what value this argument is," which then
> lets the library check these two arrows before actually applying them
> to an argument.

Well, arrows can't solve the problem as well iff performActionB may be
permissible _depending_ on x, i.e.

  performActionB x = if x then pickFlowers else eraseHardDrive

There's no way to check whether performActionB is permissible for a
given run without executing performActionA for the permissibility of B
depends on the output of A.

But I think that Michael had conditions in mind that can be checked
before executing any of the actions. Of course, the simplest way is to
check manually:

 do
   if i'mRoot
     then do
       x <- performActionA
       y <- performActionB
       z <- performActionC
       return $ calculateStuff x y z
     else
       cry "gimme root"

but you could still write performActionA somewhere without having
checked/established root permission. This can be solved by using a
custom monad

  newtype Sudo a = Sudo { act :: IO a }
                   deriving (Functor,Monad,MonadIO)

which has the following operations

  performActionA :: Sudo Int
  performActionB :: Sudo String
  etc.

and that can only be run with

  sudo :: Sudo a -> IO (Either String a)
  sudo m = do
    b <- makeMeRoot
    if b
      then liftM Right $ act m
      else return $ Left "Could not become Root"

Putting Sudo into a module and making it abstract ensures that you can't
break the invariant that stuff of type "Sudo a" will either be run as
root or not at all.

Regards,
apfelmus

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

Reply via email to