Safe Haskell | None |
---|---|
Language | Haskell2010 |
Clckwrks.Acid
Synopsis
- data CoreState_v0 = CoreState_v0 {}
- data CoreState_1 = CoreState_1 {}
- data CoreState = CoreState {}
- coreUACCT :: Lens' CoreState (Maybe UACCT)
- coreSiteName :: Lens' CoreState (Maybe Text)
- coreSendmailPath :: Lens' CoreState (Maybe FilePath)
- coreRootRedirect :: Lens' CoreState (Maybe Text)
- coreReplyToAddress :: Lens' CoreState (Maybe SimpleAddress)
- coreLoginRedirect :: Lens' CoreState (Maybe Text)
- coreFromAddress :: Lens' CoreState (Maybe SimpleAddress)
- coreEnableOpenId :: Lens' CoreState Bool
- initialCoreState :: CoreState
- getSiteName :: Query CoreState (Maybe Text)
- setSiteName :: Maybe Text -> Update CoreState ()
- getUACCT :: Query CoreState (Maybe UACCT)
- setUACCT :: Maybe UACCT -> Update CoreState ()
- getRootRedirect :: Query CoreState (Maybe Text)
- setRootRedirect :: Maybe Text -> Update CoreState ()
- getLoginRedirect :: Query CoreState (Maybe Text)
- setLoginRedirect :: Maybe Text -> Update CoreState ()
- getFromAddress :: Query CoreState (Maybe SimpleAddress)
- setFromAddress :: Maybe SimpleAddress -> Update CoreState ()
- getReplyToAddress :: Query CoreState (Maybe SimpleAddress)
- setReplyToAddress :: Maybe SimpleAddress -> Update CoreState ()
- getSendmailPath :: Query CoreState (Maybe FilePath)
- setSendmailPath :: Maybe FilePath -> Update CoreState ()
- getEnableOpenId :: Query CoreState Bool
- setEnableOpenId :: Bool -> Update CoreState ()
- getCoreState :: Query CoreState CoreState
- setCoreState :: CoreState -> Update CoreState ()
- data GetUACCT = GetUACCT
- newtype SetUACCT = SetUACCT (Maybe UACCT)
- data GetRootRedirect = GetRootRedirect
- newtype SetRootRedirect = SetRootRedirect (Maybe Text)
- data GetLoginRedirect = GetLoginRedirect
- newtype SetLoginRedirect = SetLoginRedirect (Maybe Text)
- data GetSiteName = GetSiteName
- newtype SetSiteName = SetSiteName (Maybe Text)
- data GetFromAddress = GetFromAddress
- newtype SetFromAddress = SetFromAddress (Maybe SimpleAddress)
- data GetReplyToAddress = GetReplyToAddress
- newtype SetReplyToAddress = SetReplyToAddress (Maybe SimpleAddress)
- data GetSendmailPath = GetSendmailPath
- newtype SetSendmailPath = SetSendmailPath (Maybe [Char])
- newtype SetEnableOpenId = SetEnableOpenId Bool
- data GetEnableOpenId = GetEnableOpenId
- data GetCoreState = GetCoreState
- newtype SetCoreState = SetCoreState CoreState
- data Acid = Acid {}
- class GetAcidState m st where
- getAcidState :: m (AcidState st)
- withAcid :: Maybe FilePath -> (Acid -> IO a) -> IO a
Documentation
data CoreState_v0 Source #
CoreState
holds some values that are required by the core
itself, or which are useful enough to be shared with numerous
plugins/themes.
Constructors
CoreState_v0 | |
Fields
|
Instances
data CoreState_1 Source #
CoreState
holds some values that are required by the core
itself, or which are useful enough to be shared with numerous
plugins/themes.
Constructors
CoreState_1 | |
Fields
|
Instances
CoreState
holds some values that are required by the core
itself, or which are useful enough to be shared with numerous
plugins/themes.
Constructors
CoreState | |
Fields
|
Instances
Eq CoreState Source # | |
Data CoreState Source # | |
Defined in Clckwrks.Acid Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CoreState -> c CoreState # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CoreState # toConstr :: CoreState -> Constr # dataTypeOf :: CoreState -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CoreState) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CoreState) # gmapT :: (forall b. Data b => b -> b) -> CoreState -> CoreState # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CoreState -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CoreState -> r # gmapQ :: (forall d. Data d => d -> u) -> CoreState -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CoreState -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CoreState -> m CoreState # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CoreState -> m CoreState # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CoreState -> m CoreState # | |
Show CoreState Source # | |
SafeCopy CoreState Source # | |
IsAcidic CoreState Source # | |
Defined in Clckwrks.Acid Methods acidEvents :: [Event CoreState] # | |
Migrate CoreState Source # | |
Defined in Clckwrks.Acid Associated Types type MigrateFrom CoreState :: Type # Methods migrate :: MigrateFrom CoreState -> CoreState # | |
(Functor m, Monad m) => GetAcidState (ClckT url m) CoreState Source # | |
Defined in Clckwrks.Monad | |
type MigrateFrom CoreState Source # | |
Defined in Clckwrks.Acid |
getLoginRedirect :: Query CoreState (Maybe Text) Source #
get the path that we should redirect to after login
setLoginRedirect :: Maybe Text -> Update CoreState () Source #
set the path that we should redirect to after login
getFromAddress :: Query CoreState (Maybe SimpleAddress) Source #
get the From: address for system emails
setFromAddress :: Maybe SimpleAddress -> Update CoreState () Source #
get the From: address for system emails
getReplyToAddress :: Query CoreState (Maybe SimpleAddress) Source #
get the Reply-To: address for system emails
setReplyToAddress :: Maybe SimpleAddress -> Update CoreState () Source #
get the Reply-To: address for system emails
setSendmailPath :: Maybe FilePath -> Update CoreState () Source #
set the path to the sendmail executable
Constructors
GetUACCT |
Instances
SafeCopy GetUACCT Source # | |
QueryEvent GetUACCT Source # | |
Defined in Clckwrks.Acid | |
Method GetUACCT Source # | |
Defined in Clckwrks.Acid | |
type MethodState GetUACCT Source # | |
Defined in Clckwrks.Acid | |
type MethodResult GetUACCT Source # | |
Defined in Clckwrks.Acid |
Instances
SafeCopy SetUACCT Source # | |
UpdateEvent SetUACCT Source # | |
Defined in Clckwrks.Acid | |
Method SetUACCT Source # | |
Defined in Clckwrks.Acid | |
type MethodState SetUACCT Source # | |
Defined in Clckwrks.Acid | |
type MethodResult SetUACCT Source # | |
Defined in Clckwrks.Acid |
data GetRootRedirect Source #
Constructors
GetRootRedirect |
Instances
SafeCopy GetRootRedirect Source # | |
Defined in Clckwrks.Acid Methods version :: Version GetRootRedirect # kind :: Kind GetRootRedirect # getCopy :: Contained (Get GetRootRedirect) # putCopy :: GetRootRedirect -> Contained Put # internalConsistency :: Consistency GetRootRedirect # objectProfile :: Profile GetRootRedirect # errorTypeName :: Proxy GetRootRedirect -> String # | |
QueryEvent GetRootRedirect Source # | |
Defined in Clckwrks.Acid | |
Method GetRootRedirect Source # | |
Defined in Clckwrks.Acid Associated Types type MethodResult GetRootRedirect :: Type # type MethodState GetRootRedirect :: Type # Methods methodTag :: GetRootRedirect -> Tag # | |
type MethodState GetRootRedirect Source # | |
Defined in Clckwrks.Acid | |
type MethodResult GetRootRedirect Source # | |
Defined in Clckwrks.Acid |
newtype SetRootRedirect Source #
Constructors
SetRootRedirect (Maybe Text) |
Instances
SafeCopy SetRootRedirect Source # | |
Defined in Clckwrks.Acid Methods version :: Version SetRootRedirect # kind :: Kind SetRootRedirect # getCopy :: Contained (Get SetRootRedirect) # putCopy :: SetRootRedirect -> Contained Put # internalConsistency :: Consistency SetRootRedirect # objectProfile :: Profile SetRootRedirect # errorTypeName :: Proxy SetRootRedirect -> String # | |
UpdateEvent SetRootRedirect Source # | |
Defined in Clckwrks.Acid | |
Method SetRootRedirect Source # | |
Defined in Clckwrks.Acid Associated Types type MethodResult SetRootRedirect :: Type # type MethodState SetRootRedirect :: Type # Methods methodTag :: SetRootRedirect -> Tag # | |
type MethodState SetRootRedirect Source # | |
Defined in Clckwrks.Acid | |
type MethodResult SetRootRedirect Source # | |
Defined in Clckwrks.Acid |
data GetLoginRedirect Source #
Constructors
GetLoginRedirect |
Instances
SafeCopy GetLoginRedirect Source # | |
Defined in Clckwrks.Acid | |
QueryEvent GetLoginRedirect Source # | |
Defined in Clckwrks.Acid | |
Method GetLoginRedirect Source # | |
Defined in Clckwrks.Acid Associated Types type MethodResult GetLoginRedirect :: Type # type MethodState GetLoginRedirect :: Type # Methods methodTag :: GetLoginRedirect -> Tag # | |
type MethodState GetLoginRedirect Source # | |
Defined in Clckwrks.Acid | |
type MethodResult GetLoginRedirect Source # | |
Defined in Clckwrks.Acid |
newtype SetLoginRedirect Source #
Constructors
SetLoginRedirect (Maybe Text) |
Instances
SafeCopy SetLoginRedirect Source # | |
Defined in Clckwrks.Acid | |
UpdateEvent SetLoginRedirect Source # | |
Defined in Clckwrks.Acid | |
Method SetLoginRedirect Source # | |
Defined in Clckwrks.Acid Associated Types type MethodResult SetLoginRedirect :: Type # type MethodState SetLoginRedirect :: Type # Methods methodTag :: SetLoginRedirect -> Tag # | |
type MethodState SetLoginRedirect Source # | |
Defined in Clckwrks.Acid | |
type MethodResult SetLoginRedirect Source # | |
Defined in Clckwrks.Acid |
data GetSiteName Source #
Constructors
GetSiteName |
Instances
SafeCopy GetSiteName Source # | |
Defined in Clckwrks.Acid Methods version :: Version GetSiteName # kind :: Kind GetSiteName # getCopy :: Contained (Get GetSiteName) # putCopy :: GetSiteName -> Contained Put # internalConsistency :: Consistency GetSiteName # objectProfile :: Profile GetSiteName # errorTypeName :: Proxy GetSiteName -> String # | |
QueryEvent GetSiteName Source # | |
Defined in Clckwrks.Acid | |
Method GetSiteName Source # | |
Defined in Clckwrks.Acid Methods methodTag :: GetSiteName -> Tag # | |
type MethodState GetSiteName Source # | |
Defined in Clckwrks.Acid | |
type MethodResult GetSiteName Source # | |
Defined in Clckwrks.Acid |
newtype SetSiteName Source #
Constructors
SetSiteName (Maybe Text) |
Instances
SafeCopy SetSiteName Source # | |
Defined in Clckwrks.Acid Methods version :: Version SetSiteName # kind :: Kind SetSiteName # getCopy :: Contained (Get SetSiteName) # putCopy :: SetSiteName -> Contained Put # internalConsistency :: Consistency SetSiteName # objectProfile :: Profile SetSiteName # errorTypeName :: Proxy SetSiteName -> String # | |
UpdateEvent SetSiteName Source # | |
Defined in Clckwrks.Acid | |
Method SetSiteName Source # | |
Defined in Clckwrks.Acid Methods methodTag :: SetSiteName -> Tag # | |
type MethodState SetSiteName Source # | |
Defined in Clckwrks.Acid | |
type MethodResult SetSiteName Source # | |
Defined in Clckwrks.Acid |
data GetFromAddress Source #
Constructors
GetFromAddress |
Instances
SafeCopy GetFromAddress Source # | |
Defined in Clckwrks.Acid Methods version :: Version GetFromAddress # kind :: Kind GetFromAddress # getCopy :: Contained (Get GetFromAddress) # putCopy :: GetFromAddress -> Contained Put # internalConsistency :: Consistency GetFromAddress # objectProfile :: Profile GetFromAddress # errorTypeName :: Proxy GetFromAddress -> String # | |
QueryEvent GetFromAddress Source # | |
Defined in Clckwrks.Acid | |
Method GetFromAddress Source # | |
Defined in Clckwrks.Acid Methods methodTag :: GetFromAddress -> Tag # | |
type MethodState GetFromAddress Source # | |
Defined in Clckwrks.Acid | |
type MethodResult GetFromAddress Source # | |
Defined in Clckwrks.Acid |
newtype SetFromAddress Source #
Constructors
SetFromAddress (Maybe SimpleAddress) |
Instances
SafeCopy SetFromAddress Source # | |
Defined in Clckwrks.Acid Methods version :: Version SetFromAddress # kind :: Kind SetFromAddress # getCopy :: Contained (Get SetFromAddress) # putCopy :: SetFromAddress -> Contained Put # internalConsistency :: Consistency SetFromAddress # objectProfile :: Profile SetFromAddress # errorTypeName :: Proxy SetFromAddress -> String # | |
UpdateEvent SetFromAddress Source # | |
Defined in Clckwrks.Acid | |
Method SetFromAddress Source # | |
Defined in Clckwrks.Acid Methods methodTag :: SetFromAddress -> Tag # | |
type MethodState SetFromAddress Source # | |
Defined in Clckwrks.Acid | |
type MethodResult SetFromAddress Source # | |
Defined in Clckwrks.Acid |
data GetReplyToAddress Source #
Constructors
GetReplyToAddress |
Instances
SafeCopy GetReplyToAddress Source # | |
Defined in Clckwrks.Acid | |
QueryEvent GetReplyToAddress Source # | |
Defined in Clckwrks.Acid | |
Method GetReplyToAddress Source # | |
Defined in Clckwrks.Acid Associated Types type MethodResult GetReplyToAddress :: Type # type MethodState GetReplyToAddress :: Type # Methods methodTag :: GetReplyToAddress -> Tag # | |
type MethodState GetReplyToAddress Source # | |
Defined in Clckwrks.Acid | |
type MethodResult GetReplyToAddress Source # | |
Defined in Clckwrks.Acid |
newtype SetReplyToAddress Source #
Constructors
SetReplyToAddress (Maybe SimpleAddress) |
Instances
SafeCopy SetReplyToAddress Source # | |
Defined in Clckwrks.Acid | |
UpdateEvent SetReplyToAddress Source # | |
Defined in Clckwrks.Acid | |
Method SetReplyToAddress Source # | |
Defined in Clckwrks.Acid Associated Types type MethodResult SetReplyToAddress :: Type # type MethodState SetReplyToAddress :: Type # Methods methodTag :: SetReplyToAddress -> Tag # | |
type MethodState SetReplyToAddress Source # | |
Defined in Clckwrks.Acid | |
type MethodResult SetReplyToAddress Source # | |
Defined in Clckwrks.Acid |
data GetSendmailPath Source #
Constructors
GetSendmailPath |
Instances
SafeCopy GetSendmailPath Source # | |
Defined in Clckwrks.Acid Methods version :: Version GetSendmailPath # kind :: Kind GetSendmailPath # getCopy :: Contained (Get GetSendmailPath) # putCopy :: GetSendmailPath -> Contained Put # internalConsistency :: Consistency GetSendmailPath # objectProfile :: Profile GetSendmailPath # errorTypeName :: Proxy GetSendmailPath -> String # | |
QueryEvent GetSendmailPath Source # | |
Defined in Clckwrks.Acid | |
Method GetSendmailPath Source # | |
Defined in Clckwrks.Acid Associated Types type MethodResult GetSendmailPath :: Type # type MethodState GetSendmailPath :: Type # Methods methodTag :: GetSendmailPath -> Tag # | |
type MethodState GetSendmailPath Source # | |
Defined in Clckwrks.Acid | |
type MethodResult GetSendmailPath Source # | |
Defined in Clckwrks.Acid |
newtype SetSendmailPath Source #
Constructors
SetSendmailPath (Maybe [Char]) |
Instances
SafeCopy SetSendmailPath Source # | |
Defined in Clckwrks.Acid Methods version :: Version SetSendmailPath # kind :: Kind SetSendmailPath # getCopy :: Contained (Get SetSendmailPath) # putCopy :: SetSendmailPath -> Contained Put # internalConsistency :: Consistency SetSendmailPath # objectProfile :: Profile SetSendmailPath # errorTypeName :: Proxy SetSendmailPath -> String # | |
UpdateEvent SetSendmailPath Source # | |
Defined in Clckwrks.Acid | |
Method SetSendmailPath Source # | |
Defined in Clckwrks.Acid Associated Types type MethodResult SetSendmailPath :: Type # type MethodState SetSendmailPath :: Type # Methods methodTag :: SetSendmailPath -> Tag # | |
type MethodState SetSendmailPath Source # | |
Defined in Clckwrks.Acid | |
type MethodResult SetSendmailPath Source # | |
Defined in Clckwrks.Acid |
newtype SetEnableOpenId Source #
Constructors
SetEnableOpenId Bool |
Instances
SafeCopy SetEnableOpenId Source # | |
Defined in Clckwrks.Acid Methods version :: Version SetEnableOpenId # kind :: Kind SetEnableOpenId # getCopy :: Contained (Get SetEnableOpenId) # putCopy :: SetEnableOpenId -> Contained Put # internalConsistency :: Consistency SetEnableOpenId # objectProfile :: Profile SetEnableOpenId # errorTypeName :: Proxy SetEnableOpenId -> String # | |
UpdateEvent SetEnableOpenId Source # | |
Defined in Clckwrks.Acid | |
Method SetEnableOpenId Source # | |
Defined in Clckwrks.Acid Associated Types type MethodResult SetEnableOpenId :: Type # type MethodState SetEnableOpenId :: Type # Methods methodTag :: SetEnableOpenId -> Tag # | |
type MethodState SetEnableOpenId Source # | |
Defined in Clckwrks.Acid | |
type MethodResult SetEnableOpenId Source # | |
Defined in Clckwrks.Acid |
data GetEnableOpenId Source #
Constructors
GetEnableOpenId |
Instances
SafeCopy GetEnableOpenId Source # | |
Defined in Clckwrks.Acid Methods version :: Version GetEnableOpenId # kind :: Kind GetEnableOpenId # getCopy :: Contained (Get GetEnableOpenId) # putCopy :: GetEnableOpenId -> Contained Put # internalConsistency :: Consistency GetEnableOpenId # objectProfile :: Profile GetEnableOpenId # errorTypeName :: Proxy GetEnableOpenId -> String # | |
QueryEvent GetEnableOpenId Source # | |
Defined in Clckwrks.Acid | |
Method GetEnableOpenId Source # | |
Defined in Clckwrks.Acid Associated Types type MethodResult GetEnableOpenId :: Type # type MethodState GetEnableOpenId :: Type # Methods methodTag :: GetEnableOpenId -> Tag # | |
type MethodState GetEnableOpenId Source # | |
Defined in Clckwrks.Acid | |
type MethodResult GetEnableOpenId Source # | |
Defined in Clckwrks.Acid |
data GetCoreState Source #
Constructors
GetCoreState |
Instances
SafeCopy GetCoreState Source # | |
Defined in Clckwrks.Acid Methods version :: Version GetCoreState # kind :: Kind GetCoreState # getCopy :: Contained (Get GetCoreState) # putCopy :: GetCoreState -> Contained Put # internalConsistency :: Consistency GetCoreState # objectProfile :: Profile GetCoreState # errorTypeName :: Proxy GetCoreState -> String # | |
QueryEvent GetCoreState Source # | |
Defined in Clckwrks.Acid | |
Method GetCoreState Source # | |
Defined in Clckwrks.Acid Methods methodTag :: GetCoreState -> Tag # | |
type MethodState GetCoreState Source # | |
Defined in Clckwrks.Acid | |
type MethodResult GetCoreState Source # | |
Defined in Clckwrks.Acid |
newtype SetCoreState Source #
Constructors
SetCoreState CoreState |
Instances
SafeCopy SetCoreState Source # | |
Defined in Clckwrks.Acid Methods version :: Version SetCoreState # kind :: Kind SetCoreState # getCopy :: Contained (Get SetCoreState) # putCopy :: SetCoreState -> Contained Put # internalConsistency :: Consistency SetCoreState # objectProfile :: Profile SetCoreState # errorTypeName :: Proxy SetCoreState -> String # | |
UpdateEvent SetCoreState Source # | |
Defined in Clckwrks.Acid | |
Method SetCoreState Source # | |
Defined in Clckwrks.Acid Methods methodTag :: SetCoreState -> Tag # | |
type MethodState SetCoreState Source # | |
Defined in Clckwrks.Acid | |
type MethodResult SetCoreState Source # | |
Defined in Clckwrks.Acid |
Constructors
Acid | |
class GetAcidState m st where Source #
Methods
getAcidState :: m (AcidState st) Source #
Instances
GetAcidState m st => GetAcidState (XMLGenT m) st Source # | |
Defined in Clckwrks.Monad Methods getAcidState :: XMLGenT m (AcidState st) Source # | |
(Functor m, Monad m) => GetAcidState (ClckT url m) ProfileDataState Source # | |
Defined in Clckwrks.Monad Methods getAcidState :: ClckT url m (AcidState ProfileDataState) Source # | |
(Functor m, Monad m) => GetAcidState (ClckT url m) NavBarState Source # | |
Defined in Clckwrks.Monad Methods getAcidState :: ClckT url m (AcidState NavBarState) Source # | |
(Functor m, Monad m) => GetAcidState (ClckT url m) CoreState Source # | |
Defined in Clckwrks.Monad | |
(Functor m, MonadIO m) => GetAcidState (ClckT url m) AuthenticateState Source # | |
Defined in Clckwrks.Authenticate.Plugin Methods getAcidState :: ClckT url m (AcidState AuthenticateState) Source # |