{-# LANGUAGE OverloadedStrings, QuasiQuotes #-} module Clckwrks.Authenticate.Page.ResetPassword where import Control.Applicative ((<$>)) import Clckwrks.Monad (ClckT, ThemeStyleId(..), plugins, themeTemplate) import Clckwrks.URL (ClckURL(..)) import Clckwrks.Authenticate.URL import Control.Monad.State (get) import Happstack.Server (Response, ServerPartT) import HSP import Language.Haskell.HSX.QQ (hsx) resetPasswordPage :: ClckT ClckURL (ServerPartT IO) Response resetPasswordPage :: ClckT ClckURL (ServerPartT IO) Response resetPasswordPage = do ClckPlugins plugins <- ClckState -> ClckPlugins plugins (ClckState -> ClckPlugins) -> ClckT ClckURL (ServerPartT IO) ClckState -> ClckT ClckURL (ServerPartT IO) ClckPlugins forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ClckT ClckURL (ServerPartT IO) ClckState forall s (m :: * -> *). MonadState s m => m s get ClckPlugins -> ThemeStyleId -> Text -> () -> GenChildList (ClckT ClckURL (ServerPartT IO)) -> ClckT ClckURL (ServerPartT IO) Response forall headers body. (EmbedAsChild (ClckT ClckURL (ServerPartT IO)) headers, EmbedAsChild (ClckT ClckURL (ServerPartT IO)) body) => ClckPlugins -> ThemeStyleId -> Text -> headers -> body -> ClckT ClckURL (ServerPartT IO) Response themeTemplate ClckPlugins plugins (Int -> ThemeStyleId ThemeStyleId Int 0) Text "Reset Password" () [hsx| <%> <h2>Reset Password</h2> <div ng-controller="UsernamePasswordCtrl"> <up-reset-password /> </div> </%> |]