]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Resource.hs
"driftTo Done" was trying to change the response header, which is impossible.
[Lucu.git] / Network / HTTP / Lucu / Resource.hs
index 883cc149188a404f2007425cf88d6bcfc8a2b1d8..318599f40c7347bc54ac2c13a64d5de92f9516a0 100644 (file)
@@ -1,48 +1,98 @@
+-- |This is the Resource Monad; monadic actions to define the behavior
+-- of each resources. The 'Resource' Monad is a kind of IO Monad thus
+-- it implements MonadIO class. It is also a state machine.
+-- 
+-- Request Processing Flow:
+--
+--   1. A client issues an HTTP request.
+--
+--   2. If the URI of it matches to any resource, the corresponding
+--      'Resource' Monad starts running on a newly spawned thread.
+--
+--   3. The 'Resource' Monad looks at the request header, find (or not
+--      find) an entity, receive the request body (if any), decide the
+--      response header, and decide the response body. This process
+--      will be discussed later.
+--
+--   4. The 'Resource' Monad and its thread stops running. The client
+--      may or may not be sending us the next request at this point.
+--
+-- 'Resource' Monad is composed of the following states. The initial
+-- state is /Examining Request/ and the final state is /Done/.
+--
+--   [/Examining Request/] In this state, a 'Resource' looks at the
+--   request header and thinks about an entity for it. If there is a
+--   suitable entity, the 'Resource' tells the system an entity tag
+--   and its last modification time ('foundEntity'). If it found no
+--   entity, it tells the system so ('foundNoEntity'). In case it is
+--   impossible to decide the existence of entity, which is a typical
+--   case for POST requests, 'Resource' does nothing in this state.
+--
+--   [/Getting Body/] A 'Resource' asks the system to receive a
+--   request body from client. Before actually reading from the
+--   socket, the system sends \"100 Continue\" to the client if need
+--   be. When a 'Resource' transits to the next state without
+--   receiving all or part of request body, the system still reads it
+--   and just throws it away.
+--
+--   [/Deciding Header/] A 'Resource' makes a decision of status code
+--   and response headers. When it transits to the next state, ...
+--
+--   [/Deciding Body/]
+--
+--   [/Done/]
+
+
+-- 一方通行であること、その理由
+
+-- FIXME: 續きを書く
+
 module Network.HTTP.Lucu.Resource
-    ( ResourceDef(..)
-    , Resource
-    , ResTree
-    , mkResTree    -- [ ([String], ResourceDef) ] -> ResTree
-    , findResource -- ResTree -> URI -> Maybe ResourceDef
-    , runResource  -- ResourceDef -> Interaction -> IO ThreadId
-
-    , getMethod -- Resource Method
-    , getHeader -- String -> Resource (Maybe String)
-
-    , foundEntity    -- Bool -> String -> ClockTime -> Resource ()
-    , foundETag      -- Bool -> String -> Resource ()
-    , foundTimeStamp -- ClockTime -> Resource ()
-    , foundNoEntity  -- Maybe String -> Resource ()
-
-    , input        -- Int -> Resource String
-    , inputChunk   -- Int -> Resource String
-    , inputBS      -- Int -> Resource ByteString
-    , inputChunkBS -- Int -> Resource ByteString
-    , defaultLimit -- Int
-
-    , setStatus -- StatusCode -> Resource ()
-    , setHeader -- String -> String -> Resource ()
-    , redirect  -- StatusCode -> URI -> Resource ()
-    , setETag   -- Bool -> String -> Resource ()
-    , setLastModified -- ClockTime -> Resource ()
-
-    , output        -- String -> Resource ()
-    , outputChunk   -- String -> Resource ()
-    , outputBS      -- ByteString -> Resource ()
-    , outputChunkBS -- ByteString -> Resource ()
+    ( Resource
+
+    , getConfig
+    , getRequest
+    , getMethod
+    , getRequestURI
+    , getResourcePath
+    , getPathInfo
+    , getHeader
+    , getAccept
+    , getContentType
+
+    , foundEntity
+    , foundETag
+    , foundTimeStamp
+    , foundNoEntity
+
+    , input
+    , inputChunk
+    , inputBS
+    , inputChunkBS
+    , inputForm
+    , defaultLimit
+
+    , setStatus
+    , setHeader
+    , redirect
+    , setETag
+    , setLastModified
+    , setContentType
+
+    , output
+    , outputChunk
+    , outputBS
+    , outputChunkBS
+
+    , driftTo
     )
     where
 
-import           Control.Concurrent
 import           Control.Concurrent.STM
-import           Control.Exception
 import           Control.Monad.Reader
 import qualified Data.ByteString.Lazy.Char8 as B
 import           Data.ByteString.Lazy.Char8 (ByteString)
-import           Data.Dynamic
 import           Data.List
-import qualified Data.Map as M
-import           Data.Map (Map)
 import           Data.Maybe
 import           GHC.Conc (unsafeIOToSTM)
 import           Network.HTTP.Lucu.Abortion
@@ -57,177 +107,51 @@ import           Network.HTTP.Lucu.Postprocess
 import           Network.HTTP.Lucu.RFC1123DateTime
 import           Network.HTTP.Lucu.Request
 import           Network.HTTP.Lucu.Response
+import           Network.HTTP.Lucu.MIMEType
 import           Network.HTTP.Lucu.Utils
 import           Network.URI
-import           Prelude hiding (catch)
-import           System.IO
-import           System.IO.Error hiding (catch)
 import           System.Time
 
 
 type Resource a = ReaderT Interaction IO a
 
 
-{- /aaa/bbb/ccc にアクセスされた時、もし /aaa/bbb に貪欲なリソースがあ
-   れば、假に /aaa/bbb/ccc に何らかのリソースがあったとしても必ず
-   /aaa/bbb が撰ばれる。/aaa/bbb のリソースが貪欲でなければ、それは無視
-   される。 -}
-data ResourceDef = ResourceDef {
-      resUsesNativeThread :: Bool
-    , resIsGreedy         :: Bool
-    , resGet              :: Maybe (Resource ())
-    , resHead             :: Maybe (Resource ())
-    , resPost             :: Maybe (Resource ())
-    , resPut              :: Maybe (Resource ())
-    , resDelete           :: Maybe (Resource ())
-    }
-type ResTree    = ResNode -- root だから Map ではない
-type ResSubtree = Map String ResNode
-data ResNode    = ResNode (Maybe ResourceDef) ResSubtree
-
-
-mkResTree :: [ ([String], ResourceDef) ] -> ResTree
-mkResTree list = processRoot list
-    where
-      processRoot :: [ ([String], ResourceDef) ] -> ResTree
-      processRoot list
-          = let (roots, nonRoots) = partition (\ (path, _) -> path == []) list
-                children = processNonRoot nonRoots
-            in
-              if null roots then
-                  -- / にリソースが定義されない。/foo とかにはあるかも。
-                  ResNode Nothing children
-              else
-                  -- / がある。
-                  let (_, def) = last roots
-                  in 
-                    ResNode (Just def) children
-
-      processNonRoot :: [ ([String], ResourceDef) ] -> ResSubtree
-      processNonRoot list
-          = let subtree    = M.fromList [(name, node name)
-                                             | name <- childNames]
-                childNames = [name | (name:_, _) <- list]
-                node name  = let defs = [def | (path, def) <- list, path == [name]]
-                             in
-                               if null defs then
-                                   -- この位置にリソースが定義されない。
-                                   -- もっと下にはあるかも。
-                                   ResNode Nothing children
-                               else
-                                   -- この位置にリソースがある。
-                                   ResNode (Just $ last defs) children
-                children   = processNonRoot [(path, def)
-                                                 | (_:path, def) <- list, not (null path)]
-            in
-              subtree
-
-
-findResource :: ResTree -> URI -> Maybe ResourceDef
-findResource (ResNode rootDefM subtree) uri
-    = let pathStr = uriPath uri
-          path    = [x | x <- splitBy (== '/') pathStr, x /= ""]
-      in
-        if null path then
-            rootDefM
-        else
-            walkTree subtree path
-    where
-      walkTree :: ResSubtree -> [String] -> Maybe ResourceDef
-
-      walkTree subtree (name:[])
-          = case M.lookup name subtree of
-              Nothing               -> Nothing
-              Just (ResNode defM _) -> defM
-
-      walkTree subtree (x:xs)
-          = case M.lookup x subtree of
-              Nothing                      -> Nothing
-              Just (ResNode defM children) -> case defM of
-                                                Just (ResourceDef { resIsGreedy = True })
-                                                    -> defM
-                                                _   -> walkTree children xs
-
-
-runResource :: ResourceDef -> Interaction -> IO ThreadId
-runResource def itr
-    = fork
-      $ catch ( runReaderT ( do fromMaybe notAllowed rsrc 
-                                driftTo Done
-                           ) itr
-              )
-      $ \ exc -> processException (itrConfig itr) exc
-    where
-      fork :: IO () -> IO ThreadId
-      fork = if (resUsesNativeThread def)
-             then forkOS
-             else forkIO
-      
-      rsrc :: Maybe (Resource ())
-      rsrc = case reqMethod $ fromJust $ itrRequest itr of
-               GET    -> resGet def
-               HEAD   -> case resHead def of
-                           Just r  -> Just r
-                           Nothing -> resGet def
-               POST   -> resPost def
-               PUT    -> resPut def
-               DELETE -> resDelete def
-
-      notAllowed :: Resource ()
-      notAllowed = do setStatus MethodNotAllowed
-                      setHeader "Allow" $ joinWith ", " allowedMethods
-
-      allowedMethods :: [String]
-      allowedMethods = nub $ foldr (++) [] [ methods resGet    ["GET"]
-                                           , methods resHead   ["GET", "HEAD"]
-                                           , methods resPost   ["POST"]
-                                           , methods resPut    ["PUT"]
-                                           , methods resDelete ["DELETE"]
-                                           ]
-
-      methods :: (ResourceDef -> Maybe a) -> [String] -> [String]
-      methods f xs = case f def of
-                       Just _  -> xs
-                       Nothing -> []
-
-      processException :: Config -> Exception -> IO ()
-      processException conf exc
-          = do let abo = case exc of
-                           ErrorCall    msg  -> Abortion InternalServerError [] msg
-                           IOException  ioE  -> Abortion InternalServerError [] $ formatIOE ioE
-                           DynException dynE -> case fromDynamic dynE of
-                                                  Just (abo :: Abortion) -> abo
-                                                  Nothing
-                                                      -> Abortion InternalServerError []
-                                                         $ show exc
-                           _                 -> Abortion InternalServerError [] $ show exc
-               -- まだ DecidingHeader 以前の状態だったら、この途中終了
-               -- を應答に反映させる餘地がある。さうでなければ stderr
-               -- にでも吐くしか無い。
-               state <- atomically $ readItr itr itrState id
-               if state <= DecidingHeader then
-                   flip runReaderT itr
-                      $ do setStatus $ aboStatus abo
-                           -- FIXME: 同じ名前で複數の値があった時は、こ
-                           -- れではまずいと思ふ。
-                           mapM_ (\ (name, value) -> setHeader name value) $ aboHeaders abo
-                           setHeader "Content-Type" "application/xhtml+xml"
-                           output $ aboPage conf abo
-                 else
-                   hPutStrLn stderr $ show abo
+getConfig :: Resource Config
+getConfig = do itr <- ask
+               return $ itrConfig itr
 
-               flip runReaderT itr $ driftTo Done
 
-      formatIOE :: IOError -> String
-      formatIOE ioE = if isUserError ioE then
-                          ioeGetErrorString ioE
-                      else
-                          show ioE
+getRequest :: Resource Request
+getRequest = do itr <- ask
+                return $ fromJust $ itrRequest itr
 
 
 getMethod :: Resource Method
-getMethod = do itr <- ask
-               return $ reqMethod $ fromJust $ itrRequest itr
+getMethod = do req <- getRequest
+               return $ reqMethod req
+
+
+getRequestURI :: Resource URI
+getRequestURI = do req <- getRequest
+                   return $ reqURI req
+
+
+getResourcePath :: Resource [String]
+getResourcePath = do itr <- ask
+                     return $ fromJust $ itrResourcePath itr
+
+
+getPathInfo :: Resource [String]
+getPathInfo = do rsrcPath <- getResourcePath
+                 reqURI   <- getRequestURI
+                 let reqPathStr = uriPath reqURI
+                     reqPath    = [x | x <- splitBy (== '/') reqPathStr, x /= ""]
+                 -- rsrcPath と reqPath の共通する先頭部分を reqPath か
+                 -- ら全部取り除くと、それは PATH_INFO のやうなものにな
+                 -- る。rsrcPath は全部一致してゐるに決まってゐる(でな
+                 -- ければこの Resource が撰ばれた筈が無い)ので、
+                 -- rsrcPath の長さの分だけ削除すれば良い。
+                 return $ drop (length rsrcPath) reqPath
 
 
 getHeader :: String -> Resource (Maybe String)
@@ -235,25 +159,44 @@ getHeader name = do itr <- ask
                     return $ H.getHeader name $ fromJust $ itrRequest itr
 
 
+getAccept :: Resource [MIMEType]
+getAccept = do accept <- getHeader "Accept"
+               if accept == Nothing then
+                   return []
+                 else
+                   case parseStr mimeTypeListP $ fromJust accept of
+                     (Success xs, _) -> return xs
+                     _               -> return []
+
+
+getContentType :: Resource (Maybe MIMEType)
+getContentType = do cType <- getHeader "Content-Type"
+                    if cType == Nothing then
+                        return Nothing
+                      else
+                        case parseStr mimeTypeP $ fromJust cType of
+                          (Success t, _) -> return $ Just t
+                          _              -> return Nothing
+
+
+
 {- ExaminingRequest 時に使用するアクション群 -}
 
-foundEntity :: Bool -> String -> ClockTime -> Resource ()
-foundEntity isWeak token timeStamp
+foundEntity :: ETag -> ClockTime -> Resource ()
+foundEntity tag timeStamp
     = do driftTo ExaminingRequest
 
          method <- getMethod
          when (method == GET || method == HEAD)
                   $ setHeader' "Last-Modified" $ formatHTTPDateTime timeStamp
-         foundETag isWeak token
+         foundETag tag
 
          driftTo GettingBody
 
 
-foundETag :: Bool -> String -> Resource ()
-foundETag isWeak token
+foundETag :: ETag -> Resource ()
+foundETag tag
     = do driftTo ExaminingRequest
-
-         let tag = mkETag isWeak token
       
          method <- getMethod
          when (method == GET || method == HEAD)
@@ -269,8 +212,9 @@ foundETag isWeak token
                               -- tags の中に一致するものが無ければ
                               -- PreconditionFailed で終了。
                               -> when (not $ any (== tag) tags)
-                                 $ abort PreconditionFailed [] ("The entity tag doesn't match: " ++ list)
-                          _   -> abort BadRequest [] ("Unparsable If-Match: " ++ fromJust ifMatch)
+                                 $ abort PreconditionFailed []
+                                       $ Just ("The entity tag doesn't match: " ++ list)
+                          _   -> abort BadRequest [] $ Just ("Unparsable If-Match: " ++ fromJust ifMatch)
 
          let statusForNoneMatch = if method == GET || method == HEAD then
                                       NotModified
@@ -281,12 +225,12 @@ foundETag isWeak token
          ifNoneMatch <- getHeader "If-None-Match"
          case ifNoneMatch of
            Nothing   -> return ()
-           Just "*"  -> abort statusForNoneMatch [] ("The entity tag matches: *")
+           Just "*"  -> abort statusForNoneMatch [] $ Just ("The entity tag matches: *")
            Just list -> case parseStr eTagListP list of
                           (Success tags, _)
                               -> when (any (== tag) tags)
-                                 $ abort statusForNoneMatch [] ("The entity tag matches: " ++ list)
-                          _   -> abort BadRequest [] ("Unparsable If-None-Match: " ++ list)
+                                 $ abort statusForNoneMatch [] $ Just ("The entity tag matches: " ++ list)
+                          _   -> abort BadRequest [] $ Just ("Unparsable If-None-Match: " ++ list)
 
          driftTo GettingBody
 
@@ -310,7 +254,8 @@ foundTimeStamp timeStamp
            Just str -> case parseHTTPDateTime str of
                          Just lastTime
                              -> when (timeStamp <= lastTime)
-                                $ abort statusForIfModSince [] ("The entity has not been modified since " ++ str)
+                                $ abort statusForIfModSince []
+                                      $ Just ("The entity has not been modified since " ++ str)
                          Nothing
                              -> return () -- 不正な時刻は無視
            Nothing  -> return ()
@@ -321,7 +266,8 @@ foundTimeStamp timeStamp
            Just str -> case parseHTTPDateTime str of
                          Just lastTime
                              -> when (timeStamp > lastTime)
-                                $ abort PreconditionFailed [] ("The entity has not been modified since " ++ str)
+                                $ abort PreconditionFailed []
+                                      $ Just  ("The entity has not been modified since " ++ str)
                          Nothing
                              -> return () -- 不正な時刻は無視
            Nothing  -> return ()
@@ -333,17 +279,15 @@ foundNoEntity :: Maybe String -> Resource ()
 foundNoEntity msgM
     = do driftTo ExaminingRequest
 
-         let msg = fromMaybe "The requested entity was not found in this server." msgM
-
          method <- getMethod
          when (method /= PUT)
-              $ abort NotFound [] msg
+              $ abort NotFound [] msgM
 
          -- エンティティが存在しないと云ふ事は、"*" も含めたどのやうな
          -- If-Match: 條件も滿たさない。
          ifMatch <- getHeader "If-Match"
          when (ifMatch /= Nothing)
-                  $ abort PreconditionFailed [] msg
+                  $ abort PreconditionFailed [] msgM
 
          driftTo GettingBody
 
@@ -410,8 +354,8 @@ inputBS limit
 
       tooLarge :: Int -> STM ()
       tooLarge lim = abortSTM RequestEntityTooLarge []
-                     ("Request body must be smaller than "
-                      ++ show lim ++ " bytes.")
+                     $ Just ("Request body must be smaller than "
+                             ++ show lim ++ " bytes.")
          
 
 inputChunk :: Int -> Resource String
@@ -463,6 +407,35 @@ inputChunkBS limit
                return chunk
 
 
+-- application/x-www-form-urlencoded または multipart/form-data をパー
+-- スする。もし Content-Type が無かったら BadRequest で終了し、未對應の
+-- タイプであったら UnsupportedMediaType で終了する。
+inputForm :: Int -> Resource [(String, String)]
+inputForm limit
+    = do cTypeM <- getContentType
+         case cTypeM of
+           Nothing
+               -> abort BadRequest [] (Just "Missing Content-Type")
+           Just (MIMEType "application" "x-www-form-urlencoded" _)
+               -> readWWWFormURLEncoded
+           Just (MIMEType "multipart" "form-data" _)
+               -> readMultipartFormData
+           Just cType
+               -> abort UnsupportedMediaType [] (Just $ "Unsupported media type: "
+                                                          ++ show cType)
+    where
+      readWWWFormURLEncoded
+          = do src <- input limit
+               return $ do pairStr <- splitBy (\ c -> c == ';' || c == '&') src
+                           let pair = break (== '=') pairStr
+                           return ( unEscapeString $ fst pair
+                                  , unEscapeString $ snd pair
+                                  )
+      readMultipartFormData -- FIXME: 未對應
+          = abort UnsupportedMediaType []
+            (Just $ "Sorry, inputForm does not currently support multipart/form-data.")
+
+
 defaultLimit :: Int
 defaultLimit = (-1)
 
@@ -475,15 +448,9 @@ setStatus code
     = do driftTo DecidingHeader
          itr <- ask
          liftIO $ atomically $ updateItr itr itrResponse
-                    $ \ resM -> case resM of
-                                  Nothing  -> Just $ Response {
-                                                resVersion = HttpVersion 1 1
-                                              , resStatus  = code
-                                              , resHeaders = []
-                                              }
-                                  Just res -> Just $ res {
-                                                resStatus = code
-                                              }
+                    $ \ res -> res {
+                                 resStatus = code
+                               }
 
 
 setHeader :: String -> String -> Resource ()
@@ -494,28 +461,23 @@ setHeader name value
 setHeader' :: String -> String -> Resource()
 setHeader' name value
     = do itr <- ask
-         liftIO $ atomically $ updateItr itr itrResponse
-                    $ \ resM -> case resM of
-                                  Nothing  -> Just $ Response {
-                                                resVersion = HttpVersion 1 1
-                                              , resStatus  = Ok
-                                              , resHeaders = [ (name, value) ]
-                                              }
-                                  Just res -> Just $ H.setHeader name value res
+         liftIO $ atomically
+                    $ updateItr itr itrResponse
+                          $ H.setHeader name value
 
 
 redirect :: StatusCode -> URI -> Resource ()
 redirect code uri
     = do when (code == NotModified || not (isRedirection code))
                   $ abort InternalServerError []
-                        $ "Attempted to redirect with status " ++ show code
+                        $ Just ("Attempted to redirect with status " ++ show code)
          setStatus code
          setHeader "Location" (uriToString id uri $ "")
 
 
-setETag :: Bool -> String -> Resource ()
-setETag isWeak token
-    = setHeader "ETag" $ show $ mkETag isWeak token
+setETag :: ETag -> Resource ()
+setETag tag
+    = setHeader "ETag" $ show tag
 
 
 setLastModified :: ClockTime -> Resource ()
@@ -523,6 +485,11 @@ setLastModified lastmod
     = setHeader "Last-Modified" $ formatHTTPDateTime lastmod
 
 
+setContentType :: MIMEType -> Resource ()
+setContentType mType
+    = setHeader "Content-Type" $ show mType
+
+
 {- DecidingBody 時に使用するアクション群 -}
 
 output :: String -> Resource ()
@@ -538,14 +505,47 @@ outputChunk :: String -> Resource ()
 outputChunk = outputChunkBS . B.pack
 
 
+{- チャンクの大きさは Config で制限されてゐる。もし例へば /dev/zero を
+   B.readFile して作った ByteString をそのまま ResponseWriter に渡した
+   りすると大變な事が起こる。何故なら ResponseWriter は
+   Transfer-Encoding: chunked の時、ヘッダを書く爲にチャンクの大きさを
+   測るから、その時に起こるであらう事は言ふまでも無い。 -}
+
 outputChunkBS :: ByteString -> Resource ()
-outputChunkBS str = do driftTo DecidingBody
-                       itr <- ask
-                       liftIO $ atomically $
-                              do updateItr itr itrBodyToSend (flip B.append str)
-                                 unless (B.null str)
-                                            $ writeItr itr itrBodyIsNull False
+outputChunkBS str
+    = do driftTo DecidingBody
+         itr <- ask
+         
+         let limit = cnfMaxOutputChunkLength $ itrConfig itr
+         when (limit <= 0)
+                  $ fail ("cnfMaxOutputChunkLength must be positive: "
+                          ++ show limit)
 
+         discardBody <- liftIO $ atomically $
+                        readItr itr itrWillDiscardBody id
+
+         unless (discardBody)
+                    $ sendChunks str limit
+
+         unless (B.null str)
+                    $ liftIO $ atomically $
+                      writeItr itr itrBodyIsNull False
+    where
+      sendChunks :: ByteString -> Int -> Resource ()
+      sendChunks str limit
+          | B.null str = return ()
+          | otherwise  = do let (chunk, remaining) = B.splitAt (fromIntegral limit) str
+                            itr <- ask
+                            liftIO $ atomically $ 
+                                   do buf <- readItr itr itrBodyToSend id
+                                      if B.null buf then
+                                          -- バッファが消化された
+                                          writeItr itr itrBodyToSend chunk
+                                        else
+                                          -- 消化されるのを待つ
+                                          retry
+                            -- 殘りのチャンクについて繰り返す
+                            sendChunks remaining limit
 
 {-
 
@@ -562,8 +562,7 @@ outputChunkBS str = do driftTo DecidingBody
   [Done に遷移する時]
 
   bodyIsNull が False ならば何もしない。True だった場合は出力補完す
-  る。Content-Type も變はる。但し(デフォルトのまま)Status が 200 OK
-  だった場合は、補完の代はりに 204 No Content に變へる。
+  る。
 
 -}
 
@@ -600,23 +599,7 @@ driftTo newState
       drift itr _ Done
           = do bodyIsNull <- readItr itr itrBodyIsNull id
                when bodyIsNull
-                        $ do status <- readStatus itr
-                             if status == Ok then
-                                 do updateItrF itr itrResponse
-                                                   $ \ res -> res { resStatus = NoContent }
-                                    updateItrF itr itrResponse
-                                                   $ H.deleteHeader "Content-Type"
-                                    updateItrF itr itrResponse
-                                                   $ H.deleteHeader "ETag"
-                                    updateItrF itr itrResponse
-                                                   $ H.deleteHeader "Last-Modified"
-                               else
-                                 writeDefaultPage itr
-                                       
+                        $ writeDefaultPage itr
 
       drift _ _ _
           = return ()
-
-
-      readStatus :: Interaction -> STM StatusCode
-      readStatus itr = readItr itr itrResponse (resStatus . fromJust)
\ No newline at end of file