Removed conditional compilation

This commit is contained in:
Michael Snoyman 2013-03-11 11:46:05 +02:00
parent e2cd292877
commit eecda0c80e
12 changed files with 5 additions and 122 deletions

View File

@ -247,17 +247,10 @@ handlePluginR plugin pieces = do
ap:_ -> apDispatch ap method pieces
maybeAuth :: ( YesodAuth master
#if MIN_VERSION_persistent(1, 1, 0)
, PersistMonadBackend (b (GHandler sub master)) ~ PersistEntityBackend val
, b ~ YesodPersistBackend master
, Key val ~ AuthId master
, PersistStore (b (GHandler sub master))
#else
, b ~ YesodPersistBackend master
, b ~ PersistEntityBackend val
, Key b val ~ AuthId master
, PersistStore b (GHandler sub master)
#endif
, PersistEntity val
, YesodPersist master
) => GHandler sub master (Maybe (Entity val))
@ -271,15 +264,9 @@ requireAuthId = maybeAuthId >>= maybe redirectLogin return
requireAuth :: ( YesodAuth master
, b ~ YesodPersistBackend master
#if MIN_VERSION_persistent(1, 1, 0)
, PersistMonadBackend (b (GHandler sub master)) ~ PersistEntityBackend val
, Key val ~ AuthId master
, PersistStore (b (GHandler sub master))
#else
, b ~ PersistEntityBackend val
, Key b val ~ AuthId master
, PersistStore b (GHandler sub master)
#endif
, PersistEntity val
, YesodPersist master
) => GHandler sub master (Entity val)

View File

@ -19,11 +19,7 @@ import Yesod.Auth
import qualified Web.Authenticate.OpenId as OpenId
import Yesod.Core
#if MIN_VERSION_blaze_html(0, 5, 0)
import Text.Blaze.Html (toHtml)
#else
import Text.Blaze (toHtml)
#endif
import Data.Text (Text)
import qualified Yesod.Auth.Message as Msg
import qualified Data.Text as T

View File

@ -134,24 +134,13 @@ setPassword pwd u = do salt <- randomSalt
-- | Given a user ID and password in plaintext, validate them against
-- the database values.
validateUser :: ( YesodPersist yesod
#if MIN_VERSION_persistent(1, 1, 0)
, b ~ YesodPersistBackend yesod
, PersistMonadBackend (b (GHandler sub yesod)) ~ PersistEntityBackend user
, PersistUnique (b (GHandler sub yesod))
#else
, b ~ YesodPersistBackend yesod
, b ~ PersistEntityBackend user
, PersistStore b (GHandler sub yesod)
, PersistUnique b (GHandler sub yesod)
#endif
, PersistEntity user
, HashDBUser user
) =>
#if MIN_VERSION_persistent(1, 1, 0)
Unique user -- ^ User unique identifier
#else
Unique user b -- ^ User unique identifier
#endif
-> Text -- ^ Password in plaint-text
-> GHandler sub yesod Bool
validateUser userID passwd = do
@ -172,22 +161,11 @@ login = PluginR "hashdb" ["login"]
-- username (whatever it might be) to unique user ID.
postLoginR :: ( YesodAuth y, YesodPersist y
, HashDBUser user, PersistEntity user
#if MIN_VERSION_persistent(1, 1, 0)
, b ~ YesodPersistBackend y
, PersistMonadBackend (b (GHandler Auth y)) ~ PersistEntityBackend user
, PersistUnique (b (GHandler Auth y))
#else
, b ~ YesodPersistBackend y
, b ~ PersistEntityBackend user
, PersistStore b (GHandler Auth y)
, PersistUnique b (GHandler Auth y)
#endif
)
#if MIN_VERSION_persistent(1, 1, 0)
=> (Text -> Maybe (Unique user))
#else
=> (Text -> Maybe (Unique user b))
#endif
-> GHandler Auth y ()
postLoginR uniq = do
(mu,mp) <- runInputPost $ (,)
@ -207,25 +185,13 @@ postLoginR uniq = do
-- can be used if authHashDB is the only plugin in use.
getAuthIdHashDB :: ( YesodAuth master, YesodPersist master
, HashDBUser user, PersistEntity user
#if MIN_VERSION_persistent(1, 1, 0)
, Key user ~ AuthId master
, b ~ YesodPersistBackend master
, PersistMonadBackend (b (GHandler sub master)) ~ PersistEntityBackend user
, PersistUnique (b (GHandler sub master))
#else
, Key b user ~ AuthId master
, b ~ YesodPersistBackend master
, b ~ PersistEntityBackend user
, PersistUnique b (GHandler sub master)
, PersistStore b (GHandler sub master)
#endif
)
=> (AuthRoute -> Route master) -- ^ your site's Auth Route
#if MIN_VERSION_persistent(1, 1, 0)
-> (Text -> Maybe (Unique user)) -- ^ gets user ID
#else
-> (Text -> Maybe (Unique user b)) -- ^ gets user ID
#endif
-> Creds master -- ^ the creds argument
-> GHandler sub master (Maybe (AuthId master))
getAuthIdHashDB authR uniq creds = do
@ -249,18 +215,10 @@ getAuthIdHashDB authR uniq creds = do
authHashDB :: ( YesodAuth m, YesodPersist m
, HashDBUser user
, PersistEntity user
#if MIN_VERSION_persistent(1, 1, 0)
, b ~ YesodPersistBackend m
, PersistMonadBackend (b (GHandler Auth m)) ~ PersistEntityBackend user
, PersistUnique (b (GHandler Auth m)))
=> (Text -> Maybe (Unique user)) -> AuthPlugin m
#else
, b ~ YesodPersistBackend m
, b ~ PersistEntityBackend user
, PersistStore b (GHandler Auth m)
, PersistUnique b (GHandler Auth m))
=> (Text -> Maybe (Unique user b)) -> AuthPlugin m
#endif
authHashDB uniq = AuthPlugin "hashdb" dispatch $ \tm -> toWidget [hamlet|
$newline never
<div id="header">

View File

@ -16,11 +16,7 @@ import qualified Web.Authenticate.OpenId as OpenId
import Yesod.Form
import Yesod.Core
import Text.Cassius (cassius)
#if MIN_VERSION_blaze_html(0, 5, 0)
import Text.Blaze.Html (toHtml)
#else
import Text.Blaze (toHtml)
#endif
import Data.Text (Text, isPrefixOf)
import qualified Yesod.Auth.Message as Msg
import Control.Exception.Lifted (SomeException, try)

View File

@ -60,10 +60,8 @@ import Text.Blaze (ToMarkup (toMarkup), preEscapedToMarkup, unsafeByteString)
import Text.Cassius
import Data.Time (Day, TimeOfDay(..))
import qualified Text.Email.Validate as Email
#if MIN_VERSION_email_validate(1, 0, 0)
import Data.Text.Encoding (encodeUtf8, decodeUtf8With)
import Data.Text.Encoding.Error (lenientDecode)
#endif
import Network.URI (parseURI)
import Database.Persist (PersistField)
import Database.Persist.Store (Entity (..))
@ -75,9 +73,7 @@ import qualified Blaze.ByteString.Builder.Html.Utf8 as B
import Blaze.ByteString.Builder (writeByteString, toLazyByteString)
import Blaze.ByteString.Builder.Internal.Write (fromWriteList)
import Database.Persist.Store (PersistEntityBackend)
#if MIN_VERSION_persistent(1, 1, 0)
import Database.Persist.Store (PersistMonadBackend)
#endif
import Text.Blaze.Html.Renderer.String (renderHtml)
import qualified Data.ByteString as S
@ -295,16 +291,10 @@ timeParser = do
emailField :: RenderMessage master FormMessage => Field sub master Text
emailField = Field
{ fieldParse = parseHelper $
#if MIN_VERSION_email_validate(1, 0, 0)
\s ->
case Email.canonicalizeEmail $ encodeUtf8 s of
Just e -> Right $ decodeUtf8With lenientDecode e
Nothing -> Left $ MsgInvalidEmail s
#else
\s -> if Email.isValid (unpack s)
then Right s
else Left $ MsgInvalidEmail s
#endif
, fieldView = \theId name attrs val isReq -> toWidget [hamlet|
$newline never
<input id="#{theId}" name="#{name}" *{attrs} type="email" :isReq:required="" value="#{either id id val}">
@ -505,15 +495,9 @@ optionsEnum :: (Show a, Enum a, Bounded a) => GHandler sub master (OptionList a)
optionsEnum = optionsPairs $ map (\x -> (pack $ show x, x)) [minBound..maxBound]
optionsPersist :: ( YesodPersist master, PersistEntity a
#if MIN_VERSION_persistent(1, 1, 0)
, PersistQuery (YesodPersistBackend master (GHandler sub master))
, PathPiece (Key a)
, PersistEntityBackend a ~ PersistMonadBackend (YesodPersistBackend master (GHandler sub master))
#else
, PersistQuery (YesodPersistBackend master) (GHandler sub master)
, PathPiece (Key (YesodPersistBackend master) a)
, PersistEntityBackend a ~ YesodPersistBackend master
#endif
, RenderMessage master msg
)
=> [Filter a] -> [SelectOpt a] -> (a -> msg) -> GHandler sub master (OptionList (Entity a))

View File

@ -14,14 +14,8 @@ import Yesod.Form
import Text.HTML.SanitizeXSS (sanitizeBalance)
import Text.Hamlet (Html, shamlet)
import Text.Julius (julius, rawJS)
#if MIN_VERSION_blaze_html(0, 5, 0)
import Text.Blaze (preEscapedToMarkup)
import Text.Blaze.Html.Renderer.String (renderHtml)
#define preEscapedText preEscapedToMarkup
#else
import Text.Blaze (preEscapedText)
import Text.Blaze.Renderer.String (renderHtml)
#endif
import Data.Text (Text, pack)
import Data.Maybe (listToMaybe)
@ -32,7 +26,7 @@ class Yesod a => YesodNic a where
nicHtmlField :: YesodNic master => Field sub master Html
nicHtmlField = Field
{ fieldParse = \e _ -> return . Right . fmap (preEscapedText . sanitizeBalance) . listToMaybe $ e
{ fieldParse = \e _ -> return . Right . fmap (preEscapedToMarkup . sanitizeBalance) . listToMaybe $ e
, fieldView = \theId name attrs val _isReq -> do
toWidget [shamlet|
$newline never

View File

@ -27,7 +27,7 @@ library
, xss-sanitize >= 0.3.0.1
, blaze-builder >= 0.2.1.4
, network >= 2.2
, email-validate >= 0.2.6
, email-validate >= 1.0
, bytestring >= 0.9.1.4
, text >= 0.9
, wai >= 1.3

View File

@ -23,7 +23,6 @@ class YesodPersist master where
runDB :: YesodDB sub master a -> GHandler sub master a
-- | Get the given entity by ID, or return a 404 not found if it doesn't exist.
#if MIN_VERSION_persistent(1, 1, 0)
get404 :: ( PersistStore (t m)
, PersistEntity val
, Monad (t m)
@ -32,15 +31,6 @@ get404 :: ( PersistStore (t m)
, PersistMonadBackend (t m) ~ PersistEntityBackend val
)
=> Key val -> t m val
#else
get404 :: ( PersistStore b m
, PersistEntity val
, Monad (b m)
, m ~ GHandler sub master
, MonadTrans b
)
=> Key b val -> b m val
#endif
get404 key = do
mres <- get key
case mres of
@ -49,7 +39,6 @@ get404 key = do
-- | Get the given entity by unique key, or return a 404 not found if it doesn't
-- exist.
#if MIN_VERSION_persistent(1, 1, 0)
getBy404 :: ( PersistUnique (t m)
, PersistEntity val
, m ~ GHandler sub master
@ -58,16 +47,6 @@ getBy404 :: ( PersistUnique (t m)
, PersistEntityBackend val ~ PersistMonadBackend (t m)
)
=> Unique val -> t m (Entity val)
#else
getBy404 :: ( PersistUnique b m
, PersistEntity val
, m ~ GHandler sub master
, Monad (b m)
, MonadTrans b
, PersistEntityBackend val ~ b
)
=> Unique val b -> b m (Entity val)
#endif
getBy404 key = do
mres <- getBy key
case mres of

View File

@ -15,8 +15,8 @@ description: Some helpers for using Persistent from Yesod.
library
build-depends: base >= 4 && < 5
, yesod-core >= 1.1 && < 1.2
, persistent >= 1.0 && < 1.2
, persistent-template >= 1.0 && < 1.2
, persistent >= 1.1 && < 1.2
, persistent-template >= 1.1 && < 1.2
, transformers >= 0.2.2 && < 0.4
exposed-modules: Yesod.Persist
ghc-options: -Wall

View File

@ -70,13 +70,8 @@ injectDefaultP env path p@(OptP o)
let (Just parseri) = f cmd
in parseri { infoParser = injectDefaultP env (path ++ [normalizeName cmd]) (infoParser parseri) }
in OptP (Option (CmdReader cmds (`M.lookup` cmdMap)) props)
#if MIN_VERSION_optparse_applicative(0, 5, 0)
| (Option (OptReader names (CReader _ rdr) _) _) <- o =
p <|> either (const empty) pure (msum $ map (rdr <=< (maybe (Left $ ErrorMsg "Missing environment variable") Right . getEnvValue env path)) names)
#else
| (Option (OptReader names (CReader _ rdr)) _) <- o =
p <|> maybe empty pure (msum $ map (rdr <=< getEnvValue env path) names)
#endif
| (Option (FlagReader names a) _) <- o =
p <|> if any ((==Just "1") . getEnvValue env path) names then pure a else empty
| otherwise = p

View File

@ -17,9 +17,7 @@ import Options (injectDefaults)
import qualified Paths_yesod
import Scaffolding.Scaffolder
#if MIN_VERSION_optparse_applicative(0, 5, 0)
import Options.Applicative.Builder.Internal (Mod, OptionFields)
#endif
#ifndef WINDOWS
import Build (touch)
@ -166,11 +164,7 @@ optStr :: Mod OptionFields (Maybe String) -> Parser (Maybe String)
optStr m =
nullOption $ value Nothing <> reader (success . str) <> m
where
#if MIN_VERSION_optparse_applicative(0, 5, 0)
success = Right
#else
success = Just
#endif
-- | Like @rawSystem@, but exits if it receives a non-success result.
rawSystem' :: String -> [String] -> IO ()

View File

@ -97,7 +97,7 @@ executable yesod
, system-fileio >= 0.3 && < 0.4
, unordered-containers
, yaml >= 0.8 && < 0.9
, optparse-applicative >= 0.4
, optparse-applicative >= 0.5
, fsnotify >= 0.0 && < 0.1
, split >= 0.2 && < 0.3
, file-embed