[Haskell-cafe] IO in HApps handler ?
Luc TAESCH
luc.taesch at googlemail.com
Sun Aug 19 17:19:46 EDT 2007
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"
More information about the Haskell-Cafe
mailing list