module Nero.Response
(
Response
, ok
, movedPermanently
, notFound
, _Ok
, _MovedPermanently
, _NotFound
, Status
, status
) where
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as B8
import Data.Text.Lazy (Text)
import Data.Text.Lazy.Lens (utf8)
import Nero.Prelude
import Nero.Payload
import Nero.Url
data Response = Ok Payload
| MovedPermanently Url
| NotFound Payload
deriving (Show,Eq)
instance Location Response where
location f (MovedPermanently u) = MovedPermanently <$> f u
location _ response = pure response
instance HasBody Response where
body (Ok pl) = body pl
body (MovedPermanently _) = mempty
body (NotFound pl) = body pl
ok :: Text -> Response
ok = Ok . payloadText utf8Encoding . review utf8
movedPermanently :: Url -> Response
movedPermanently = MovedPermanently
notFound :: Text -> Response
notFound = NotFound . payloadText utf8Encoding . review utf8
_Ok :: Prism' Response Payload
_Ok = prism' Ok $ \case
Ok p -> Just p
_ -> Nothing
_MovedPermanently :: Prism' Response Url
_MovedPermanently = prism' MovedPermanently $ \case
MovedPermanently u -> Just u
_ -> Nothing
_NotFound :: Prism' Response Payload
_NotFound = prism' NotFound $ \case
NotFound p -> Just p
_ -> Nothing
data Status = Status Int ByteString
instance Show Status where
show (Status code desc) =
"\"" <> show code <> " " <> B8.unpack desc <> "\""
status :: Response -> Status
status (Ok _) = Status 200 "OK"
status (MovedPermanently _) = Status 301 "Moved Permanently"
status (NotFound _) = Status 404 "Not Found"