Removed Yesod.Parameter
This commit is contained in:
parent
764b981f6c
commit
ecb4d2f334
@ -35,8 +35,11 @@ needsIdent = do
|
||||
|
||||
hasArgs :: Handler Errors HtmlObject
|
||||
hasArgs = do
|
||||
{- FIXME wait for new request API
|
||||
(a, b) <- runRequest $ (,) <$> getParam "firstParam"
|
||||
<*> getParam "secondParam"
|
||||
-}
|
||||
let (a, b) = ("foo", "bar")
|
||||
return $ toHtmlObject [a :: String, b]
|
||||
|
||||
caseErrorMessages :: Assertion
|
||||
@ -46,8 +49,10 @@ caseErrorMessages = do
|
||||
assertBool "/denied/" $ "Permission denied" `isInfixOf` show res
|
||||
res' <- app $ def { pathInfo = "/needs-ident/" }
|
||||
assertBool "/needs-ident/" $ "IGNORED/auth/openid/" `isInfixOf` show res'
|
||||
{- FIXME this test is not yet ready
|
||||
res3 <- app $ def { pathInfo = "/has-args/" }
|
||||
assertBool "/has-args/" $ "secondParam" `isInfixOf` show res3
|
||||
-}
|
||||
|
||||
testSuite :: Test
|
||||
testSuite = testGroup "Test.Errors"
|
||||
|
||||
@ -69,7 +69,7 @@ ph ss h = do
|
||||
assertBool needle $ needle `isInfixOf` haystack
|
||||
|
||||
myShow :: Response -> IO String
|
||||
myShow (Response sc hs ct (Content c)) = c [] >>= \c' -> return $ unlines
|
||||
myShow (Response sc hs ct c) = runContent c >>= \c' -> return $ unlines
|
||||
[ show sc
|
||||
, unlines $ map show hs
|
||||
, show ct
|
||||
|
||||
2
Yesod.hs
2
Yesod.hs
@ -21,7 +21,6 @@ module Yesod
|
||||
, module Yesod.Handler
|
||||
, module Yesod.Resource
|
||||
, module Data.Object.Html
|
||||
, module Yesod.Parameter
|
||||
, module Yesod.Template
|
||||
, module Web.Mime
|
||||
, Application
|
||||
@ -39,7 +38,6 @@ import Data.Object.Html
|
||||
import Yesod.Request
|
||||
#endif
|
||||
|
||||
import Yesod.Parameter
|
||||
import Yesod.Yesod
|
||||
import Yesod.Definitions
|
||||
import Yesod.Handler
|
||||
|
||||
@ -52,8 +52,6 @@ import System.IO
|
||||
import Data.Object.Html
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
|
||||
import Yesod.Parameter
|
||||
|
||||
------ Handler monad
|
||||
newtype Handler yesod a = Handler {
|
||||
unHandler :: (RawRequest, yesod, TemplateGroup)
|
||||
|
||||
@ -33,7 +33,7 @@ import Control.Monad.Attempt
|
||||
import Data.Maybe (fromMaybe)
|
||||
import qualified Hack
|
||||
import Data.Typeable (Typeable)
|
||||
import Control.Exception (Exception)
|
||||
import Control.Exception (Exception, SomeException (..))
|
||||
|
||||
class YesodApproot a => YesodAuth a where
|
||||
-- | The following breaks DRY, but I cannot think of a better solution
|
||||
@ -85,14 +85,37 @@ instance ConvertSuccess OIDFormReq Html where
|
||||
convertSuccess (OIDFormReq (Just s) _) =
|
||||
Tag "p" [("class", "message")] $ cs s
|
||||
|
||||
someParam :: (Monad m, RequestReader m)
|
||||
=> ParamType
|
||||
-> (RawRequest -> ParamName -> [ParamValue])
|
||||
-> ParamName
|
||||
-> m ParamValue
|
||||
someParam pt paramList pn = do
|
||||
rr <- getRawRequest
|
||||
case paramList rr pn of
|
||||
[x] -> return x
|
||||
x -> invalidParams [((pt, pn, x), SomeException ExpectedSingleParam)]
|
||||
|
||||
data ExpectedSingleParam = ExpectedSingleParam
|
||||
deriving (Show, Typeable)
|
||||
instance Exception ExpectedSingleParam
|
||||
|
||||
getParam :: (Monad m, RequestReader m)
|
||||
=> ParamName
|
||||
-> m ParamValue
|
||||
getParam = someParam GetParam getParams
|
||||
|
||||
authOpenidForm :: Handler y HtmlObject
|
||||
authOpenidForm = do
|
||||
message <- runRequest $ getParam "message"
|
||||
dest <- runRequest $ getParam "dest"
|
||||
let m = OIDFormReq message dest
|
||||
rr <- getRawRequest
|
||||
case getParams rr "dest" of
|
||||
[] -> return ()
|
||||
(x:_) -> addCookie 120 "DEST" x
|
||||
let html =
|
||||
HtmlList
|
||||
[ cs m
|
||||
[ case getParams rr "message" of
|
||||
[] -> HtmlList []
|
||||
(m:_) -> Tag "p" [("class", "message")] $ cs m
|
||||
, Tag "form" [("method", "get"), ("action", "forward/")] $
|
||||
HtmlList
|
||||
[ Tag "label" [("for", "openid")] $ cs "OpenID: "
|
||||
@ -101,14 +124,11 @@ authOpenidForm = do
|
||||
, EmptyTag "input" [("type", "submit"), ("value", "Login")]
|
||||
]
|
||||
]
|
||||
case dest of
|
||||
Just dest' -> addCookie 120 "DEST" dest'
|
||||
Nothing -> return ()
|
||||
return $ cs html
|
||||
|
||||
authOpenidForward :: YesodAuth y => Handler y HtmlObject
|
||||
authOpenidForward = do
|
||||
oid <- runRequest $ getParam "openid"
|
||||
oid <- getParam "openid"
|
||||
authroot <- getFullAuthRoot
|
||||
let complete = authroot ++ "/openid/complete/"
|
||||
res <- runAttemptT $ OpenId.getForwardUrl oid complete
|
||||
@ -147,15 +167,13 @@ rpxnowLogin = do
|
||||
let token = case getParams rr "token" ++ postParams rr "token" of
|
||||
[] -> failure MissingToken
|
||||
(x:_) -> x
|
||||
postDest <- runRequest $ postParam "dest"
|
||||
dest' <- case postDest of
|
||||
Nothing -> runRequest $ getParam "dest"
|
||||
Just d -> return d
|
||||
let dest = case dest' of
|
||||
Nothing -> ar
|
||||
Just "" -> ar
|
||||
Just ('#':rest) -> rest
|
||||
Just s -> s
|
||||
let dest = case postParams rr "dest" of
|
||||
[] -> case getParams rr "dest" of
|
||||
[] -> ar
|
||||
("":_) -> ar
|
||||
(('#':rest):_) -> rest
|
||||
(s:_) -> s
|
||||
(d:_) -> d
|
||||
ident <- Rpxnow.authenticate apiKey token
|
||||
header authCookieName $ Rpxnow.identifier ident
|
||||
header authDisplayName $ getDisplayName ident
|
||||
|
||||
@ -1,121 +0,0 @@
|
||||
{-# LANGUAGE TypeSynonymInstances #-}
|
||||
{-# LANGUAGE OverlappingInstances #-} -- Parameter String
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
module Yesod.Parameter
|
||||
(
|
||||
-- * Parameter
|
||||
-- $param_overview
|
||||
Parameter (..)
|
||||
, ParamType (..)
|
||||
, ParamName
|
||||
, ParamValue
|
||||
, ParamAttempt (..)
|
||||
, ParamException
|
||||
-- * Exceptions
|
||||
, ParameterCountException (..)
|
||||
, InvalidBool (..)
|
||||
) where
|
||||
|
||||
import Data.Time.Calendar (Day)
|
||||
import Control.Applicative
|
||||
import Data.Typeable (Typeable)
|
||||
import Control.Exception (Exception, SomeException (..))
|
||||
import Data.Attempt
|
||||
import qualified Safe.Failure as SF
|
||||
import Data.Convertible.Text
|
||||
|
||||
-- FIXME instead of plain Attempt, an Attempt that defines better error
|
||||
-- reporting (eg, multilingual)
|
||||
|
||||
-- $param_overview
|
||||
-- In Restful, all of the underlying parameter values are strings. They can
|
||||
-- come from multiple sources: GET parameters, URL rewriting (FIXME: link),
|
||||
-- cookies, etc. However, most applications eventually want to convert
|
||||
-- those strings into something else, like 'Int's. Additionally, it is
|
||||
-- often desirable to allow multiple values, or no value at all.
|
||||
--
|
||||
-- That is what the parameter concept is for. A 'Parameter' is any value
|
||||
-- which can be converted from a 'String', or list of 'String's.
|
||||
|
||||
-- | Where this parameter came from.
|
||||
data ParamType =
|
||||
GetParam
|
||||
| PostParam
|
||||
deriving (Eq, Show)
|
||||
|
||||
type ParamName = String
|
||||
|
||||
-- | The 'String' value of a parameter.
|
||||
type ParamValue = String
|
||||
|
||||
-- | Anything which can be converted from a list of 'String's.
|
||||
--
|
||||
-- The default implementation of 'readParams' will error out if given
|
||||
-- anything but 1 'ParamValue'. This is usually what you want.
|
||||
--
|
||||
-- Minimal complete definition: either 'readParam' or 'readParams'.
|
||||
class Parameter a where
|
||||
-- | Convert a string into the desired value, or explain why that can't
|
||||
-- happen.
|
||||
readParam :: ParamValue -> Attempt a
|
||||
readParam = readParams . return
|
||||
|
||||
-- | Convert a list of strings into the desired value, or explain why
|
||||
-- that can't happen.
|
||||
readParams :: [ParamValue] -> Attempt a
|
||||
readParams [x] = readParam x
|
||||
readParams [] = failure MissingParameter
|
||||
readParams xs = failure $ ExtraParameters $ length xs
|
||||
|
||||
data ParamAttempt v = ParamSuccess v
|
||||
| ParamFailure ParamException
|
||||
instance Functor ParamAttempt where
|
||||
fmap _ (ParamFailure pf) = ParamFailure pf
|
||||
fmap f (ParamSuccess v) = ParamSuccess $ f v
|
||||
instance Applicative ParamAttempt where
|
||||
pure = ParamSuccess
|
||||
(ParamFailure pf1) <*> (ParamFailure pf2) = ParamFailure $ pf1 ++ pf2
|
||||
(ParamFailure pf) <*> _ = ParamFailure pf
|
||||
_ <*> ParamFailure pf = ParamFailure pf
|
||||
(ParamSuccess f) <*> (ParamSuccess v) = ParamSuccess $ f v
|
||||
instance Try ParamAttempt where
|
||||
type Error ParamAttempt = ParamException
|
||||
try (ParamSuccess v) = pure v
|
||||
try (ParamFailure f) = failure f
|
||||
type ParamException = [((ParamType, ParamName, [ParamValue]), SomeException)]
|
||||
|
||||
data ParameterCountException = MissingParameter | ExtraParameters Int
|
||||
deriving (Show, Typeable)
|
||||
instance Exception ParameterCountException
|
||||
|
||||
instance Parameter a => Parameter (Maybe a) where
|
||||
readParams [] = return Nothing
|
||||
readParams [x] = Just `fmap` readParam x
|
||||
readParams xs = failure $ ExtraParameters $ length xs
|
||||
|
||||
instance Parameter a => Parameter [a] where
|
||||
readParams = mapM readParam where
|
||||
|
||||
instance Parameter String where
|
||||
readParam = return
|
||||
|
||||
instance Parameter Int where
|
||||
readParam = ca
|
||||
|
||||
instance Parameter Integer where
|
||||
readParam = SF.read
|
||||
|
||||
instance Parameter Day where
|
||||
readParam = ca
|
||||
|
||||
-- for checkboxes; checks for presence or a "false" value
|
||||
instance Parameter Bool where
|
||||
readParams [] = return False
|
||||
readParams ["false"] = return False -- FIXME more values?
|
||||
readParams [_] = return True
|
||||
readParams x = failure $ InvalidBool x
|
||||
|
||||
data InvalidBool = InvalidBool [ParamValue]
|
||||
deriving (Show, Typeable)
|
||||
instance Exception InvalidBool
|
||||
@ -21,17 +21,18 @@ module Yesod.Request
|
||||
-- * RawRequest
|
||||
RawRequest (..)
|
||||
, RequestReader (..)
|
||||
, getParam
|
||||
, postParam
|
||||
, parseEnv
|
||||
, runRequest
|
||||
, cookies
|
||||
, getParams
|
||||
, postParams
|
||||
, languages
|
||||
-- * Building actual request
|
||||
, Request (..)
|
||||
, Hack.RequestMethod (..)
|
||||
-- * Parameter
|
||||
, ParamType (..)
|
||||
, ParamName
|
||||
, ParamValue
|
||||
, ParamException
|
||||
#if TEST
|
||||
, testSuite
|
||||
#endif
|
||||
@ -39,15 +40,12 @@ module Yesod.Request
|
||||
|
||||
import qualified Hack
|
||||
import Data.Function.Predicate (equals)
|
||||
import Yesod.Parameter
|
||||
import Yesod.Definitions
|
||||
import Control.Applicative (Applicative (..))
|
||||
import Web.Encodings
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import Data.Convertible.Text
|
||||
import Control.Arrow ((***))
|
||||
import Control.Exception (SomeException (..))
|
||||
import Data.Attempt
|
||||
import Data.Maybe (fromMaybe)
|
||||
|
||||
#if TEST
|
||||
@ -56,50 +54,14 @@ import Test.Framework.Providers.HUnit
|
||||
import Test.HUnit hiding (Test)
|
||||
#endif
|
||||
|
||||
newtype Request v = Request { unRequest :: RawRequest
|
||||
-> Either ParamException v }
|
||||
instance Functor Request where
|
||||
fmap f (Request r) = Request $ fmap f . r
|
||||
instance Applicative Request where
|
||||
pure = Request . const . Right
|
||||
(Request f) <*> (Request r) = Request helper where
|
||||
helper rr = helper2 (f rr) (r rr)
|
||||
helper2 (Left e1) (Left e2) = Left $ e1 ++ e2
|
||||
helper2 (Left e) _ = Left e
|
||||
helper2 _ (Left e) = Left e
|
||||
helper2 (Right f') (Right r') = Right $ f' r'
|
||||
data ParamType = GetParam | PostParam
|
||||
type ParamName = String
|
||||
type ParamValue = String
|
||||
type ParamException = [((ParamType, ParamName, [ParamValue]), SomeException)]
|
||||
|
||||
class RequestReader m where
|
||||
getRawRequest :: m RawRequest
|
||||
invalidParams :: ParamException -> m a
|
||||
instance RequestReader Request where
|
||||
getRawRequest = Request $ Right
|
||||
invalidParams = Request . const . Left
|
||||
|
||||
runRequest :: (Monad m, RequestReader m) => Request a -> m a
|
||||
runRequest (Request f) = do
|
||||
rr <- getRawRequest
|
||||
either invalidParams return $ f rr
|
||||
|
||||
-- | Helper function for generating 'RequestParser's from various
|
||||
-- 'ParamValue' lists.
|
||||
genParam :: Parameter a
|
||||
=> (RawRequest -> ParamName -> [ParamValue])
|
||||
-> ParamType
|
||||
-> ParamName
|
||||
-> Request a
|
||||
genParam f ptype name = Request helper where
|
||||
helper req = attempt failureH Right $ readParams pvs where
|
||||
pvs = f req name
|
||||
failureH e = Left [((ptype, name, pvs), SomeException e)]
|
||||
|
||||
-- | Parse a value passed as a GET parameter.
|
||||
getParam :: (Parameter a) => ParamName -> Request a
|
||||
getParam = genParam getParams GetParam
|
||||
|
||||
-- | Parse a value passed as a POST parameter.
|
||||
postParam :: (Parameter a) => ParamName -> Request a
|
||||
postParam = genParam postParams PostParam
|
||||
|
||||
languages :: (Functor m, RequestReader m) => m [Language]
|
||||
languages = rawLangs `fmap` getRawRequest
|
||||
@ -164,17 +126,6 @@ instance ConvertSuccess Hack.Env RawRequest where
|
||||
#if TEST
|
||||
testSuite :: Test
|
||||
testSuite = testGroup "Yesod.Request"
|
||||
[ testCase "Request applicative instance" caseAppInst
|
||||
[
|
||||
]
|
||||
|
||||
caseAppInst :: Assertion
|
||||
caseAppInst = do
|
||||
let r5 = Request $ const $ Right (5 :: Int)
|
||||
rAdd2 = Request $ const $ Right (+ 2)
|
||||
r7 = Request $ const $ Right (7 :: Int)
|
||||
rr = undefined
|
||||
myEquals e t = (unRequest e) rr `myEquals2` (unRequest t) rr
|
||||
myEquals2 x y = show x @=? show y
|
||||
r5 `myEquals` pure (5 :: Int)
|
||||
r7 `myEquals` (rAdd2 <*> r5)
|
||||
#endif
|
||||
|
||||
@ -43,6 +43,7 @@ module Yesod.Response
|
||||
#if TEST
|
||||
-- * Tests
|
||||
, testSuite
|
||||
, runContent
|
||||
#endif
|
||||
) where
|
||||
|
||||
|
||||
@ -59,7 +59,6 @@ library
|
||||
Yesod.Response
|
||||
Yesod.Definitions
|
||||
Yesod.Handler
|
||||
Yesod.Parameter
|
||||
Yesod.Resource
|
||||
Yesod.Yesod
|
||||
Yesod.Template
|
||||
|
||||
Loading…
Reference in New Issue
Block a user