{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
module Dormouse.Client.Status
( ok
, created
, accepted
, nonAuthoritativeInformation
, noContent
, resetContent
, partialContent
, badRequest
, notFound
, internalServerError
, pattern Informational
, pattern Successful
, pattern Redirect
, pattern ClientError
, pattern ServerError
, pattern Ok
, pattern Created
, pattern Accepted
, pattern NonAuthoritativeInformation
, pattern NoContent
, pattern ResetContent
, pattern PartialContent
, pattern BadRequest
, pattern NotFound
, pattern InternalServerError
) where
isInformational :: Int -> Bool
isInformational :: Int -> Bool
isInformational Int
x = Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
100 Bool -> Bool -> Bool
&& Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
200
isSuccessful :: Int -> Bool
isSuccessful :: Int -> Bool
isSuccessful Int
x = Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
200 Bool -> Bool -> Bool
&& Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
300
isRedirect :: Int -> Bool
isRedirect :: Int -> Bool
isRedirect Int
x = Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
300 Bool -> Bool -> Bool
&& Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
400
isClientError :: Int -> Bool
isClientError :: Int -> Bool
isClientError Int
x = Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
400 Bool -> Bool -> Bool
&& Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
500
isServerError :: Int -> Bool
isServerError :: Int -> Bool
isServerError Int
x = Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
500 Bool -> Bool -> Bool
&& Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
600
ok :: Int
ok :: Int
ok = Int
200
created :: Int
created :: Int
created = Int
201
accepted :: Int
accepted :: Int
accepted = Int
202
nonAuthoritativeInformation :: Int
nonAuthoritativeInformation :: Int
nonAuthoritativeInformation = Int
203
noContent :: Int
noContent :: Int
noContent = Int
204
resetContent :: Int
resetContent :: Int
resetContent = Int
205
partialContent :: Int
partialContent :: Int
partialContent = Int
206
badRequest :: Int
badRequest :: Int
badRequest = Int
400
notFound :: Int
notFound :: Int
notFound = Int
404
internalServerError :: Int
internalServerError :: Int
internalServerError = Int
500
pattern Informational :: Int
pattern $mInformational :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
Informational <- (isInformational -> True)
pattern Successful :: Int
pattern $mSuccessful :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
Successful <- (isSuccessful -> True)
pattern Redirect :: Int
pattern $mRedirect :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
Redirect <- (isRedirect -> True)
pattern ClientError :: Int
pattern $mClientError :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
ClientError <- (isClientError -> True)
pattern ServerError :: Int
pattern $mServerError :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
ServerError <- (isServerError -> True)
pattern Ok :: Int
pattern $mOk :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
Ok <- ((==) ok -> True)
pattern Created :: Int
pattern $mCreated :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
Created <- ((==) created -> True)
pattern Accepted :: Int
pattern $mAccepted :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
Accepted <- ((==) accepted -> True)
pattern NonAuthoritativeInformation :: Int
pattern $mNonAuthoritativeInformation :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
NonAuthoritativeInformation <- ((==) nonAuthoritativeInformation -> True)
pattern NoContent :: Int
pattern $mNoContent :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
NoContent <- ((==) noContent -> True)
pattern ResetContent :: Int
pattern $mResetContent :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
ResetContent <- ((==) resetContent -> True)
pattern PartialContent :: Int
pattern $mPartialContent :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
PartialContent <- ((==) partialContent -> True)
pattern BadRequest :: Int
pattern $mBadRequest :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
BadRequest <- ((==) badRequest -> True)
pattern NotFound :: Int
pattern $mNotFound :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
NotFound <- ((==) notFound -> True)
pattern InternalServerError :: Int
pattern $mInternalServerError :: forall r. Int -> (Void# -> r) -> (Void# -> r) -> r
InternalServerError <- ((==) internalServerError -> True)