]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Abortion.hs
Fixed many bugs...
[Lucu.git] / Network / HTTP / Lucu / Abortion.hs
index 4e237c4fe1f220fad90e8aaf63060c788b52741a..eeb1c6b7675ec1e40ba369c8c25035042d657ec3 100644 (file)
@@ -16,7 +16,7 @@ module Network.HTTP.Lucu.Abortion
     , abortPage
     )
     where
-import Control.Arrow
+import Control.Arrow.ArrowIO
 import Control.Arrow.ListArrow
 import Control.Arrow.Unicode
 import Control.Concurrent.STM
@@ -38,9 +38,9 @@ import Text.XML.HXT.Arrow.XmlArrow
 import Text.XML.HXT.Arrow.XmlState
 
 data Abortion = Abortion {
-      aboStatus  :: !StatusCode
-    , aboHeaders :: !Headers
-    , aboMessage :: !(Maybe Text)
+      aboStatus   !StatusCode
+    , aboHeaders  !Headers
+    , aboMessage  !(Maybe Text)
     } deriving (Eq, Show, Typeable)
 
 instance Exception Abortion
@@ -69,36 +69,36 @@ instance Exception Abortion
 -- > abort MovedPermanently
 -- >       [("Location", "http://example.net/")]
 -- >       (Just "It has been moved to example.net")
-abort :: MonadIO m ⇒ StatusCode → [ (CIAscii, Ascii) ] → Maybe Text → m a
+abort  MonadIO m ⇒ StatusCode → [ (CIAscii, Ascii) ] → Maybe Text → m a
 {-# INLINE abort #-}
 abort status headers
     = liftIO ∘ throwIO ∘ Abortion status (toHeaders headers)
 
 -- |This is similar to 'abort' but computes it with
 -- 'System.IO.Unsafe.unsafePerformIO'.
-abortPurely :: StatusCode → [ (CIAscii, Ascii) ] → Maybe Text → a
+abortPurely  StatusCode → [ (CIAscii, Ascii) ] → Maybe Text → a
 {-# INLINE abortPurely #-}
 abortPurely status headers
     = throw ∘ Abortion status (toHeaders headers)
 
 -- |Computation of @'abortSTM' status headers msg@ just computes
 -- 'abort' in a 'Control.Monad.STM.STM' monad.
-abortSTM :: StatusCode → [ (CIAscii, Ascii) ] → Maybe Text → STM a
+abortSTM  StatusCode → [ (CIAscii, Ascii) ] → Maybe Text → STM a
 {-# INLINE abortSTM #-}
 abortSTM status headers
     = throwSTM ∘ Abortion status (toHeaders headers)
 
 -- | Computation of @'abortA' -< (status, (headers, msg))@ just
 -- computes 'abort' in an 'Control.Arrow.ArrowIO.ArrowIO'.
-abortA :: Arrow (⇝) ⇒ (StatusCode, ([ (CIAscii, Ascii) ], Maybe Text)) ⇝ c
+abortA ∷ ArrowIO (⇝) ⇒ (StatusCode, ([ (CIAscii, Ascii) ], Maybe Text)) ⇝ c
 {-# INLINE abortA #-}
 abortA = proc (status, (headers, msg)) →
-         returnA ⤙ abortPurely status headers msg
+         arrIO throwIO ⤙ Abortion status (toHeaders headers) msg
 
 -- aboMessage が Just なら單に mkDefaultPage に渡すだけで良いので樂だが、
 -- Nothing の場合は getDefaultPage を使ってデフォルトのメッセージを得な
 -- ければならない。
-abortPage :: Config → Maybe Request → Response → Abortion → Lazy.Text
+abortPage  Config → Maybe Request → Response → Abortion → Lazy.Text
 abortPage conf reqM res abo
     = case aboMessage abo of
         Just msg