MonadLift instance for AForm

This commit is contained in:
Michael Snoyman 2012-09-19 09:03:53 +03:00
parent fef3024d30
commit 0c68f46762
2 changed files with 7 additions and 2 deletions

View File

@ -2,6 +2,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Yesod.Form.Types
( -- * Helpers
Enctype (..)
@ -30,7 +31,7 @@ import Text.Blaze (Markup, ToMarkup (toMarkup))
import Control.Applicative ((<$>), Applicative (..))
import Control.Monad (liftM)
import Data.String (IsString (..))
import Yesod.Core (GHandler, GWidget, SomeMessage)
import Yesod.Core (GHandler, GWidget, SomeMessage, MonadLift (..))
import qualified Data.Map as Map
-- | A form can produce three different results: there was no data available,
@ -97,6 +98,10 @@ instance Applicative (AForm sub master) where
instance Monoid a => Monoid (AForm sub master a) where
mempty = pure mempty
mappend a b = mappend <$> a <*> b
instance MonadLift (GHandler sub master) (AForm sub master) where
lift f = AForm $ \_ _ ints -> do
x <- f
return (FormSuccess x, id, ints, mempty)
data FieldSettings master = FieldSettings
{ fsLabel :: SomeMessage master

View File

@ -1,5 +1,5 @@
name: yesod-form
version: 1.1.1.2
version: 1.1.2
license: MIT
license-file: LICENSE
author: Michael Snoyman <michael@snoyman.com>