
Subject: IO in HApps handler ? I am trying to add a handler that would run an external command in HApps 0.8.8, and I got a type issue I do not know how to get around.. can we have IO in a handler ? testcmdpost.hs:52:8: Couldn't match expected type `Ev st Request' against inferred type `IO' Expected type: ServerPart (Ev st Request) Request IO Result Inferred type: ServerPart IO Request im Result In the expression: (h ["xxx"] GET) $ (ok $ (\ () () -> do (MySt val) <- get runCommand "ls" ["."] respond (show "dfdf"))) here is the handler iI am adding : ,h ["xxx"] GET $ ok $ \() () -> do (MySt val) <- get; runCommand "ls" ["."]; respond (show "dfdf" ) in there : import HAppS.Util.Common... ... main :: IO () main = stdHTTP [debugFilter -- we want to see debug messages in the console ,h [""] GET $ ok $ val "GETting root hello" -- ,h (Prefix ["s"]) GET $ respIO $ fileServe staticPath , hs (Prefix ["s"]) GET $ basicFileServe staticPath -- 0.8.8 -- /val shows us the current value ,h ["val"] GET $ ok $ \() () -> do (MySt val) <- get; respond (show val) -- /set with the POST data "val"=56 would set the value to 56 ,h ["xxx"] GET $ ok $ \() () -> do (MySt val) <- get; runCommand "ls" ["."]; respond (show "dfdf" ) ,h ["set"] POST $ ok $ \() newVal -> do put newVal; respond ("New value is " ++ show newVal) -- The first one is FromReqURI and the second one is FromMessage -- The cryptic comment about is referring to the arguments () and newVal -- to the method. The type of newVal being MyState is what -- invokes our custom FromMessage instance above. ] this is the runcommand from HAppS.Util.Common , not from defined as -- | Run an external command. Upon failure print status -- to stderr. runCommand :: String -> [String] -> IO () runCommand cmd args = do (_, outP, errP, pid) <- runInteractiveProcess cmd args Nothing Nothing let pGetContents h = do mv <- newEmptyMVar let put [] = putMVar mv [] put xs = last xs `seq` putMVar mv xs forkIO (hGetContents h >>= put) takeMVar mv os <- pGetContents outP es <- pGetContents errP ec <- waitForProcess pid case ec of ExitSuccess -> return () ExitFailure e -> do hPutStrLn stderr ("Running process "++unwords (cmd:args)++" FAILED ("++show e++")") hPutStrLn stderr os hPutStrLn stderr es hPutStrLn stderr ("Raising error...") fail "Running external command failed"

Hi TAESCH, THat's what haskell is good for. It prevents you from doing unsafe things by accident. You must get the source and have a look at the definition of the Ev type: (module HAppS.MACID.Types where:) (Not sure wether this code is most recent or not (Version: 0.8.8)) ============= ======================================================= [...] data Env st ev = Env { -- | Read only event. evEvent :: TxContext ev, -- | State, can be used with get and put. evState :: MutVar st, -- | Internal. List of side effects. evSideEffects :: MutVar [(Seconds, IO ())], -- | Internal. Used to signal completion of background IO. evBackgroundIOCompletion :: IO (), -- | Internal. Random numbers that should be used. evRandoms :: MutVar StdGen -- -- | Internal. New event generation. -- evCreateEvent :: ev -> IO () } type TxId = Int64 type EpochTime = Int64 type Seconds = Int instance Typeable StdGen where typeOf _ = undefined -- !! for default serial data TxContext evt = TxContext { txId :: TxId, txTime :: EpochTime, txStdGen :: StdGen, txEvent :: evt } deriving (Read,Show,Typeable) -- | ACID computations that work with any state and event types. type AnyEv a = forall state event. Ev state event a -- | Monad for ACID event handlers. newtype Ev state event t = Ev { unEv :: Env state event -> STM t } -- unsafe lifting unsafeIOToEv :: IO a -> AnyEv a unsafeIOToEv c = Ev $ \_ -> unsafeIOToSTM c unsafeSTMToEv :: STM a -> AnyEv a unsafeSTMToEv c = Ev $ \_ -> c unsafeIOToSTM :: IO a -> STM a unsafeIOToSTM = GHC.Conc.unsafeIOToSTM [...] ============= ======================================================= Now have a look at the line newtype Ev state event t = Ev { unEv :: Env state event -> STM t } which shows that you have some kind of state passed (Env state event) which results in STM t ) The next thing is having a look at either Env or STM.. data Env st ev = Env { [...] evBackgroundIOCompletion :: IO (), shows that an IO may be passed, which must be transformed into STM somehow: Yeah. STM permits this newtype STM a = STM (IORef (IO ()) -> IO a) this ( lifting an IO action into a different monad) is called lift(IO) most of the time.. and as you can see theere are some transformers defined: unsafeIOToEv :: IO a -> AnyEv a unsafeIOToEv c = Ev $ \_ -> unsafeIOToSTM c unsafeSTMToEv :: STM a -> AnyEv a unsafeSTMToEv c = Ev $ \_ -> c unsafeIOToSTM :: IO a -> STM a unsafeIOToSTM = GHC.Conc.unsafeIOToSTM But why they are called unsafe etc you should ask people familiar with HaPPS and its design.. But at least you can now use grep or google to see wether you can find some more info on those unsafe functions HTH Marc

Subject: IO in HApps handler ? I am trying to add a handler that would run an external command in HApps 0.8.8, and I got a type issue I do not know how to get around..
can we have IO in a handler ?
http://www.haskell.org/haskellwiki/HAppS_tutorial#Application "The MACID monad lets you update your state and *schedule* side-effects. To be clear, MACID is not in the IO monad so you cannot execute side effects, you can only schedule them. The framework takes care of making sure they are executed at-least-once (if they can be completed by a deadline you specify)." I don't know the specifics. Tim Newsham http://www.thenewsh.com/~newsham/
participants (3)
-
Luc TAESCH
-
Marc Weber
-
Tim Newsham