Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype PageId = PageId {}
- data PreProcessor
- data Markup = Markup {
- preProcessors :: [PreProcessor]
- markup :: Text
- trust :: Trust
- data PublishStatus
- data PageKind
- newtype Slug = Slug {}
- slugify :: Text -> Slug
- data Page = Page {}
- data FeedConfig = FeedConfig {}
- type Pages = IxSet Page
- initialFeedConfig :: IO FeedConfig
- data PageState
- initialPageState :: IO PageState
- data NewPage = NewPage PageKind UserId UUID UTCTime
- newtype PageById = PageById PageId
- newtype GetPageTitle = GetPageTitle PageId
- newtype IsPublishedPage = IsPublishedPage PageId
- data PagesSummary = PagesSummary
- newtype UpdatePage = UpdatePage Page
- data AllPosts = AllPosts
- data AllPublishedPages = AllPublishedPages
- data GetFeedConfig = GetFeedConfig
- newtype SetFeedConfig = SetFeedConfig FeedConfig
- data GetBlogTitle = GetBlogTitle
- data GetOldUACCT = GetOldUACCT
- data ClearOldUACCT = ClearOldUACCT
Documentation
Instances
Eq PageId Source # | |
Data PageId Source # | |
Defined in Clckwrks.Page.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PageId -> c PageId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PageId # toConstr :: PageId -> Constr # dataTypeOf :: PageId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PageId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PageId) # gmapT :: (forall b. Data b => b -> b) -> PageId -> PageId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PageId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PageId -> r # gmapQ :: (forall d. Data d => d -> u) -> PageId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PageId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PageId -> m PageId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PageId -> m PageId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PageId -> m PageId # | |
Ord PageId Source # | |
Read PageId Source # | |
Show PageId Source # | |
SafeCopy PageId Source # | |
ToJSON PageId Source # | |
Defined in Clckwrks.Page.Types | |
FromJSON PageId Source # | |
PathInfo PageId Source # | |
Defined in Clckwrks.Page.Types toPathSegments :: PageId -> [Text] # |
data PreProcessor Source #
Instances
Markup | |
|
Instances
Eq Markup Source # | |
Data Markup Source # | |
Defined in Clckwrks.Page.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Markup -> c Markup # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Markup # toConstr :: Markup -> Constr # dataTypeOf :: Markup -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Markup) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Markup) # gmapT :: (forall b. Data b => b -> b) -> Markup -> Markup # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Markup -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Markup -> r # gmapQ :: (forall d. Data d => d -> u) -> Markup -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Markup -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Markup -> m Markup # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Markup -> m Markup # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Markup -> m Markup # | |
Ord Markup Source # | |
Read Markup Source # | |
Show Markup Source # | |
SafeCopy Markup Source # | |
Migrate Markup Source # | |
Defined in Clckwrks.Page.Types type MigrateFrom Markup :: Type # migrate :: MigrateFrom Markup -> Markup # | |
type MigrateFrom Markup Source # | |
Defined in Clckwrks.Page.Types |
data PublishStatus Source #
Instances
Instances
Eq PageKind Source # | |
Data PageKind Source # | |
Defined in Clckwrks.Page.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PageKind -> c PageKind # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PageKind # toConstr :: PageKind -> Constr # dataTypeOf :: PageKind -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PageKind) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PageKind) # gmapT :: (forall b. Data b => b -> b) -> PageKind -> PageKind # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PageKind -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PageKind -> r # gmapQ :: (forall d. Data d => d -> u) -> PageKind -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PageKind -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PageKind -> m PageKind # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PageKind -> m PageKind # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PageKind -> m PageKind # | |
Ord PageKind Source # | |
Defined in Clckwrks.Page.Types | |
Read PageKind Source # | |
Show PageKind Source # | |
SafeCopy PageKind Source # | |
Instances
Eq Slug Source # | |
Data Slug Source # | |
Defined in Clckwrks.Page.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Slug -> c Slug # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Slug # dataTypeOf :: Slug -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Slug) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Slug) # gmapT :: (forall b. Data b => b -> b) -> Slug -> Slug # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Slug -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Slug -> r # gmapQ :: (forall d. Data d => d -> u) -> Slug -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Slug -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Slug -> m Slug # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Slug -> m Slug # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Slug -> m Slug # | |
Ord Slug Source # | |
Read Slug Source # | |
Show Slug Source # | |
SafeCopy Slug Source # | |
PathInfo Slug Source # | |
Defined in Clckwrks.Page.Types toPathSegments :: Slug -> [Text] # | |
PathInfo (Maybe Slug) Source # | |
Defined in Clckwrks.Page.Types toPathSegments :: Maybe Slug -> [Text] # fromPathSegments :: URLParser (Maybe Slug) # |
Page | |
|
Instances
Eq Page Source # | |
Data Page Source # | |
Defined in Clckwrks.Page.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Page -> c Page # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Page # dataTypeOf :: Page -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Page) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Page) # gmapT :: (forall b. Data b => b -> b) -> Page -> Page # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Page -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Page -> r # gmapQ :: (forall d. Data d => d -> u) -> Page -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Page -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Page -> m Page # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Page -> m Page # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Page -> m Page # | |
Ord Page Source # | |
Read Page Source # | |
Show Page Source # | |
SafeCopy Page Source # | |
Indexable Page Source # | |
Defined in Clckwrks.Page.Types | |
Migrate Page Source # | |
Defined in Clckwrks.Page.Types type MigrateFrom Page :: Type # migrate :: MigrateFrom Page -> Page # | |
type MigrateFrom Page Source # | |
Defined in Clckwrks.Page.Types |
data FeedConfig Source #
Instances
state
Instances
events
Instances
SafeCopy NewPage Source # | |
UpdateEvent NewPage Source # | |
Defined in Clckwrks.Page.Acid | |
Method NewPage Source # | |
Defined in Clckwrks.Page.Acid type MethodResult NewPage :: Type # type MethodState NewPage :: Type # | |
type MethodState NewPage Source # | |
Defined in Clckwrks.Page.Acid | |
type MethodResult NewPage Source # | |
Defined in Clckwrks.Page.Acid |
Instances
SafeCopy PageById Source # | |
QueryEvent PageById Source # | |
Defined in Clckwrks.Page.Acid | |
Method PageById Source # | |
Defined in Clckwrks.Page.Acid type MethodResult PageById :: Type # type MethodState PageById :: Type # | |
type MethodState PageById Source # | |
Defined in Clckwrks.Page.Acid | |
type MethodResult PageById Source # | |
Defined in Clckwrks.Page.Acid |
newtype GetPageTitle Source #
Instances
SafeCopy GetPageTitle Source # | |
Defined in Clckwrks.Page.Acid | |
QueryEvent GetPageTitle Source # | |
Defined in Clckwrks.Page.Acid | |
Method GetPageTitle Source # | |
Defined in Clckwrks.Page.Acid type MethodResult GetPageTitle :: Type # type MethodState GetPageTitle :: Type # methodTag :: GetPageTitle -> Tag # | |
type MethodState GetPageTitle Source # | |
Defined in Clckwrks.Page.Acid | |
type MethodResult GetPageTitle Source # | |
Defined in Clckwrks.Page.Acid |
newtype IsPublishedPage Source #
Instances
SafeCopy IsPublishedPage Source # | |
Defined in Clckwrks.Page.Acid | |
QueryEvent IsPublishedPage Source # | |
Defined in Clckwrks.Page.Acid | |
Method IsPublishedPage Source # | |
Defined in Clckwrks.Page.Acid type MethodResult IsPublishedPage :: Type # type MethodState IsPublishedPage :: Type # methodTag :: IsPublishedPage -> Tag # | |
type MethodState IsPublishedPage Source # | |
Defined in Clckwrks.Page.Acid | |
type MethodResult IsPublishedPage Source # | |
Defined in Clckwrks.Page.Acid |
data PagesSummary Source #
Instances
SafeCopy PagesSummary Source # | |
Defined in Clckwrks.Page.Acid | |
QueryEvent PagesSummary Source # | |
Defined in Clckwrks.Page.Acid | |
Method PagesSummary Source # | |
Defined in Clckwrks.Page.Acid type MethodResult PagesSummary :: Type # type MethodState PagesSummary :: Type # methodTag :: PagesSummary -> Tag # | |
type MethodState PagesSummary Source # | |
Defined in Clckwrks.Page.Acid | |
type MethodResult PagesSummary Source # | |
Defined in Clckwrks.Page.Acid |
newtype UpdatePage Source #
Instances
SafeCopy UpdatePage Source # | |
Defined in Clckwrks.Page.Acid version :: Version UpdatePage # kind :: Kind UpdatePage # getCopy :: Contained (Get UpdatePage) # putCopy :: UpdatePage -> Contained Put # internalConsistency :: Consistency UpdatePage # objectProfile :: Profile UpdatePage # errorTypeName :: Proxy UpdatePage -> String # | |
UpdateEvent UpdatePage Source # | |
Defined in Clckwrks.Page.Acid | |
Method UpdatePage Source # | |
Defined in Clckwrks.Page.Acid type MethodResult UpdatePage :: Type # type MethodState UpdatePage :: Type # methodTag :: UpdatePage -> Tag # | |
type MethodState UpdatePage Source # | |
Defined in Clckwrks.Page.Acid | |
type MethodResult UpdatePage Source # | |
Defined in Clckwrks.Page.Acid |
Instances
SafeCopy AllPosts Source # | |
QueryEvent AllPosts Source # | |
Defined in Clckwrks.Page.Acid | |
Method AllPosts Source # | |
Defined in Clckwrks.Page.Acid type MethodResult AllPosts :: Type # type MethodState AllPosts :: Type # | |
type MethodState AllPosts Source # | |
Defined in Clckwrks.Page.Acid | |
type MethodResult AllPosts Source # | |
Defined in Clckwrks.Page.Acid |
data AllPublishedPages Source #
Instances
SafeCopy AllPublishedPages Source # | |
QueryEvent AllPublishedPages Source # | |
Defined in Clckwrks.Page.Acid | |
Method AllPublishedPages Source # | |
Defined in Clckwrks.Page.Acid type MethodResult AllPublishedPages :: Type # type MethodState AllPublishedPages :: Type # methodTag :: AllPublishedPages -> Tag # | |
type MethodState AllPublishedPages Source # | |
Defined in Clckwrks.Page.Acid | |
type MethodResult AllPublishedPages Source # | |
Defined in Clckwrks.Page.Acid |
data GetFeedConfig Source #
Instances
SafeCopy GetFeedConfig Source # | |
Defined in Clckwrks.Page.Acid | |
QueryEvent GetFeedConfig Source # | |
Defined in Clckwrks.Page.Acid | |
Method GetFeedConfig Source # | |
Defined in Clckwrks.Page.Acid type MethodResult GetFeedConfig :: Type # type MethodState GetFeedConfig :: Type # methodTag :: GetFeedConfig -> Tag # | |
type MethodState GetFeedConfig Source # | |
Defined in Clckwrks.Page.Acid | |
type MethodResult GetFeedConfig Source # | |
Defined in Clckwrks.Page.Acid |
newtype SetFeedConfig Source #
Instances
SafeCopy SetFeedConfig Source # | |
Defined in Clckwrks.Page.Acid | |
UpdateEvent SetFeedConfig Source # | |
Defined in Clckwrks.Page.Acid | |
Method SetFeedConfig Source # | |
Defined in Clckwrks.Page.Acid type MethodResult SetFeedConfig :: Type # type MethodState SetFeedConfig :: Type # methodTag :: SetFeedConfig -> Tag # | |
type MethodState SetFeedConfig Source # | |
Defined in Clckwrks.Page.Acid | |
type MethodResult SetFeedConfig Source # | |
Defined in Clckwrks.Page.Acid |
data GetBlogTitle Source #
Instances
SafeCopy GetBlogTitle Source # | |
Defined in Clckwrks.Page.Acid | |
QueryEvent GetBlogTitle Source # | |
Defined in Clckwrks.Page.Acid | |
Method GetBlogTitle Source # | |
Defined in Clckwrks.Page.Acid type MethodResult GetBlogTitle :: Type # type MethodState GetBlogTitle :: Type # methodTag :: GetBlogTitle -> Tag # | |
type MethodState GetBlogTitle Source # | |
Defined in Clckwrks.Page.Acid | |
type MethodResult GetBlogTitle Source # | |
Defined in Clckwrks.Page.Acid |
data GetOldUACCT Source #
Instances
SafeCopy GetOldUACCT Source # | |
Defined in Clckwrks.Page.Acid | |
QueryEvent GetOldUACCT Source # | |
Defined in Clckwrks.Page.Acid | |
Method GetOldUACCT Source # | |
Defined in Clckwrks.Page.Acid type MethodResult GetOldUACCT :: Type # type MethodState GetOldUACCT :: Type # methodTag :: GetOldUACCT -> Tag # | |
type MethodState GetOldUACCT Source # | |
Defined in Clckwrks.Page.Acid | |
type MethodResult GetOldUACCT Source # | |
Defined in Clckwrks.Page.Acid |
data ClearOldUACCT Source #
Instances
SafeCopy ClearOldUACCT Source # | |
Defined in Clckwrks.Page.Acid | |
UpdateEvent ClearOldUACCT Source # | |
Defined in Clckwrks.Page.Acid | |
Method ClearOldUACCT Source # | |
Defined in Clckwrks.Page.Acid type MethodResult ClearOldUACCT :: Type # type MethodState ClearOldUACCT :: Type # methodTag :: ClearOldUACCT -> Tag # | |
type MethodState ClearOldUACCT Source # | |
Defined in Clckwrks.Page.Acid | |
type MethodResult ClearOldUACCT Source # | |
Defined in Clckwrks.Page.Acid |