now builds with both yesod 1.2 and 1.1

This commit is contained in:
Joey Hess 2013-06-03 16:33:05 -04:00
parent 31753bad46
commit 1198b5444d
14 changed files with 103 additions and 35 deletions

View file

@ -178,7 +178,11 @@ lookupRequestField k req = fromMaybe "" . lookup k $ Wai.requestHeaders req
{- Rather than storing a session key on disk, use a random key
- that will only be valid for this run of the webapp. -}
#if MIN_VERSION_yesod(1,2,0)
webAppSessionBackend :: Yesod.Yesod y => y -> IO (Maybe Yesod.SessionBackend)
#else
webAppSessionBackend :: Yesod.Yesod y => y -> IO (Maybe (Yesod.SessionBackend y))
#endif
webAppSessionBackend _ = do
g <- newGenIO :: IO SystemRandom
case genBytes 96 g of
@ -218,7 +222,11 @@ genRandomToken = do
- Note that the usual Yesod error page is bypassed on error, to avoid
- possibly leaking the auth token in urls on that page!
-}
#if MIN_VERSION_yesod(1,2,0)
checkAuthToken :: (Monad m, Yesod.MonadHandler m) => (Yesod.HandlerSite m -> T.Text) -> m Yesod.AuthResult
#else
checkAuthToken :: forall t sub. (t -> T.Text) -> Yesod.GHandler sub t Yesod.AuthResult
#endif
checkAuthToken extractToken = do
webapp <- Yesod.getYesod
req <- Yesod.getRequest

View file

@ -8,20 +8,21 @@
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE CPP, RankNTypes #-}
{-# LANGUAGE CPP, RankNTypes, FlexibleContexts #-}
module Utility.Yesod where
import Yesod
#if MIN_VERSION_yesod_default(1,2,0)
import Yesod.Core
#endif
#ifndef __ANDROID__
import Yesod.Default.Util
import Language.Haskell.TH.Syntax
import Language.Haskell.TH.Syntax (Q, Exp)
#if MIN_VERSION_yesod_default(1,1,0)
import Data.Default (def)
import Text.Hamlet
#endif
#if MIN_VERSION_yesod_default(1,2,0)
import Yesod.Core
#endif
widgetFile :: String -> Q Exp
#if ! MIN_VERSION_yesod_default(1,1,0)
@ -39,10 +40,10 @@ hamletTemplate f = globFile "hamlet" f
#endif
{- Lift Handler to Widget -}
#if ! MIN_VERSION_yesod(1,2,0)
liftH :: forall t. Lift t => t -> Q Exp
liftH = lift
#else
#if MIN_VERSION_yesod(1,2,0)
liftH :: Monad m => HandlerT site m a -> WidgetT site m a
liftH = liftH
#else
liftH :: MonadLift base m => base a -> m a
liftH = lift
#endif