module Snap.Predicates.Params
( Parameter (..)
, Param (..)
, ParamOpt (..)
, ParamDef (..)
)
where
import Data.ByteString (ByteString)
import Data.ByteString.Readable
import Data.Either
import Data.Monoid
import Data.String
import Data.Typeable
import Data.Predicate
import Snap.Core hiding (headers)
import Snap.Predicates.Error
import Snap.Predicates.Internal
import qualified Data.Predicate.Env as E
import qualified Data.ByteString as S
data Parameter a = Parameter
{ _name :: !ByteString
, _read :: [ByteString] -> Either ByteString a
, _default :: !(Maybe a)
}
instance Typeable a => Predicate (Parameter a) Request where
type FVal (Parameter a) = Error
type TVal (Parameter a) = a
apply (Parameter nme f def) r =
E.lookup (key nme) >>= maybe work result
where
work = case params r nme of
[] -> maybe (return (F (err 400 ("Missing parameter '" <> nme <> "'."))))
(return . (T 0))
def
vs -> do
let x = f vs
E.insert (key nme) x
case x of
Left msg -> return $ maybe (F (err 400 msg)) (T 0) def
Right v -> return $ T 0 v
result (Left msg) = return (F (err 400 msg))
result (Right v) = return (T 0 v)
key name = "parameter:" <> name <> ":" <> (fromString . show . typeOf $ def)
instance Show (Parameter a) where
show p = "Parameter: " ++ show (_name p)
data Param a = Param ByteString
instance (Typeable a, Readable a) => Predicate (Param a) Request where
type FVal (Param a) = Error
type TVal (Param a) = a
apply (Param x) = apply (Parameter x f Nothing)
where
f vs = let (es, xs) = partitionEithers $ map fromByteString vs
in if null xs
then Left (S.intercalate "\n" es)
else Right (head xs)
instance Show (Param a) where
show (Param x) = "Param: " ++ show x
data ParamOpt a = ParamOpt ByteString
instance (Typeable a, Readable a) => Predicate (ParamOpt a) Request where
type FVal (ParamOpt a) = Error
type TVal (ParamOpt a) = Maybe a
apply (ParamOpt x) = apply (Parameter x f (Just Nothing))
where
f vs = let xs = rights $ map fromByteString vs
in if null xs then Right Nothing else Right (head xs)
instance Show (ParamOpt a) where
show (ParamOpt x) = "ParamOpt: " ++ show x
data ParamDef a = ParamDef ByteString a
instance (Typeable a, Readable a) => Predicate (ParamDef a) Request where
type FVal (ParamDef a) = Error
type TVal (ParamDef a) = a
apply (ParamDef x d) = apply (Param x :|: Const d)
instance Show a => Show (ParamDef a) where
show (ParamDef x d) = "ParamDef: " ++ show x ++ " [" ++ show d ++ "]"