X-Git-Url: http://git.cielonegro.org/gitweb.cgi?a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FAbortion.hs;h=eeb1c6b7675ec1e40ba369c8c25035042d657ec3;hb=72a3e24a952616e32845eeb4fc05048e841c91a2;hp=c36ebc07912176949d2005e37e8e4dc7a8d2c625;hpb=0ff03469c29b791f2c609a659bbf59be97e306f2;p=Lucu.git diff --git a/Network/HTTP/Lucu/Abortion.hs b/Network/HTTP/Lucu/Abortion.hs index c36ebc0..eeb1c6b 100644 --- a/Network/HTTP/Lucu/Abortion.hs +++ b/Network/HTTP/Lucu/Abortion.hs @@ -1,11 +1,9 @@ {-# LANGUAGE Arrows - , BangPatterns , DeriveDataTypeable , TypeOperators , UnicodeSyntax #-} -{-# OPTIONS_HADDOCK prune #-} -- |Aborting the computation of 'Network.HTTP.Lucu.Resource.Resource' -- in any 'Prelude.IO' monads or arrows. @@ -18,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 @@ -40,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 @@ -71,37 +69,37 @@ 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 !conf !reqM !res !abo +abortPage ∷ Config → Maybe Request → Response → Abortion → Lazy.Text +abortPage conf reqM res abo = case aboMessage abo of Just msg → let [html] = runLA ( mkDefaultPage conf (aboStatus abo) (txt $ T.unpack msg)