Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Clck url = ClckT url (ServerPartT IO)
- type ClckPlugins = Plugins Theme (ClckT ClckURL (ServerPartT IO) Response) (ClckT ClckURL IO ()) ClckwrksConfig ClckPluginsSt
- data ClckPluginsSt
- initialClckPluginsSt :: Acid -> ClckPluginsSt
- newtype ClckT url m a = ClckT {}
- type ClckForm url = Form (ClckT url (ServerPartT IO)) [Input] ClckFormError [XMLGenT (ClckT url (ServerPartT IO)) XML] ()
- type ClckFormT error m = Form m [Input] error [XMLGenT m XML] ()
- data ClckFormError
- = ClckCFE (CommonFormError [Input])
- | EmptyUsername
- data family ChildType (m :: Type -> Type) :: Type
- data ClckwrksConfig = ClckwrksConfig {
- clckHostname :: String
- clckPort :: Int
- clckTLS :: Maybe TLSSettings
- clckHidePort :: Bool
- clckJQueryPath :: FilePath
- clckJQueryUIPath :: FilePath
- clckJSTreePath :: FilePath
- clckJSON2Path :: FilePath
- clckTopDir :: Maybe FilePath
- clckEnableAnalytics :: Bool
- clckInitHook :: Text -> ClckState -> ClckwrksConfig -> IO (ClckState, ClckwrksConfig)
- data TLSSettings = TLSSettings {}
- data family AttributeType (m :: Type -> Type) :: Type
- data Theme = Theme {}
- data ThemeStyle = ThemeStyle {
- themeStyleName :: Text
- themeStyleDescription :: Text
- themeStylePreview :: Maybe FilePath
- themeStyleTemplate :: forall headers body. (EmbedAsChild (ClckT ClckURL (ServerPartT IO)) headers, EmbedAsChild (ClckT ClckURL (ServerPartT IO)) body) => Text -> headers -> body -> XMLGenT (ClckT ClckURL (ServerPartT IO)) XML
- newtype ThemeStyleId = ThemeStyleId {}
- type ThemeName = Text
- getThemeStyles :: MonadIO m => ClckPlugins -> m [(ThemeStyleId, ThemeStyle)]
- themeTemplate :: (EmbedAsChild (ClckT ClckURL (ServerPartT IO)) headers, EmbedAsChild (ClckT ClckURL (ServerPartT IO)) body) => ClckPlugins -> ThemeStyleId -> Text -> headers -> body -> ClckT ClckURL (ServerPartT IO) Response
- calcBaseURI :: ClckwrksConfig -> Text
- calcTLSBaseURI :: ClckwrksConfig -> Maybe Text
- evalClckT :: Monad m => (url -> [(Text, Maybe Text)] -> Text) -> ClckState -> ClckT url m a -> m a
- execClckT :: Monad m => (url -> [(Text, Maybe Text)] -> Text) -> ClckState -> ClckT url m a -> m ClckState
- runClckT :: Monad m => (url -> [(Text, Maybe Text)] -> Text) -> ClckState -> ClckT url m a -> m (a, ClckState)
- mapClckT :: (m (a, ClckState) -> n (b, ClckState)) -> ClckT url m a -> ClckT url n b
- withRouteClckT :: ((url' -> [(Text, Maybe Text)] -> Text) -> url -> [(Text, Maybe Text)] -> Text) -> ClckT url m a -> ClckT url' m a
- data ClckState = ClckState {
- acidState :: Acid
- uniqueId :: TVar Integer
- adminMenus :: [(Text, [(Set Role, Text, Text)])]
- enableAnalytics :: Bool
- plugins :: ClckPlugins
- requestInit :: ServerPart ()
- data Content
- addAdminMenu :: Monad m => (Text, [(Set Role, Text, Text)]) -> ClckT url m ()
- appendRequestInit :: Monad m => ServerPart () -> ClckT url m ()
- getNavBarLinks :: MonadIO m => Plugins theme n hook config ClckPluginsSt -> ClckT ClckURL m NavBarLinks
- addPreProc :: MonadIO m => Plugins theme n hook config ClckPluginsSt -> (forall mm. (Functor mm, MonadIO mm, Happstack mm) => Text -> ClckT ClckURL mm Text) -> m ()
- addNavBarCallback :: MonadIO m => Plugins theme n hook config ClckPluginsSt -> ClckT ClckURL IO (String, [NamedLink]) -> m ()
- getPreProcessors :: MonadIO m => Plugins theme n hook config ClckPluginsSt -> forall mm. (Functor mm, MonadIO mm, Happstack mm) => ClckT url m [Text -> ClckT ClckURL mm Text]
- getEnableAnalytics :: (Functor m, MonadState ClckState m) => m Bool
- googleAnalytics :: XMLGenT (Clck url) XML
- getUnique :: (Functor m, MonadIO m) => ClckT url m Integer
- setUnique :: (Functor m, MonadIO m) => Integer -> ClckT url m ()
- setRedirectCookie :: Happstack m => String -> m ()
- getRedirectCookie :: Happstack m => m (Maybe String)
- query :: forall event m. (QueryEvent event, GetAcidState m (EventState event), Functor m, MonadIO m, MonadState ClckState m) => event -> m (EventResult event)
- update :: forall event m. (UpdateEvent event, GetAcidState m (EventState event), Functor m, MonadIO m, MonadState ClckState m) => event -> m (EventResult event)
- nestURL :: (url1 -> url2) -> ClckT url1 m a -> ClckT url2 m a
- withAbs :: Happstack m => ClckT url m a -> ClckT url m a
- withAbs' :: Text -> ClckT url m a -> ClckT url m a
- segments :: Text -> Parser a -> Parser [Segment a]
- transform :: Monad m => (cmd -> m Builder) -> [Segment cmd] -> m Builder
- module HSP.XML
- module HSP.XMLGenerator
Documentation
type ClckPlugins = Plugins Theme (ClckT ClckURL (ServerPartT IO) Response) (ClckT ClckURL IO ()) ClckwrksConfig ClckPluginsSt Source #
ClckPlugins
newtype Plugins theme m hook config st
data ClckPluginsSt Source #
newtype ClckT url m a Source #
Instances
type ClckForm url = Form (ClckT url (ServerPartT IO)) [Input] ClckFormError [XMLGenT (ClckT url (ServerPartT IO)) XML] () Source #
type ClckFormT error m = Form m [Input] error [XMLGenT m XML] () Source #
ClckForm - type for reform forms
data ClckFormError Source #
error returned when a reform Form
fails to validate
Instances
Show ClckFormError Source # | |
Defined in Clckwrks.Monad showsPrec :: Int -> ClckFormError -> ShowS # show :: ClckFormError -> String # showList :: [ClckFormError] -> ShowS # | |
FormError ClckFormError Source # | |
Defined in Clckwrks.Monad type ErrorInputType ClckFormError :: Type # | |
(Functor m, MonadIO m, Happstack m) => EmbedAsChild (ClckT url m) ClckFormError Source # | |
Defined in Clckwrks.Monad asChild :: ClckFormError -> GenChildList (ClckT url m) # | |
type ErrorInputType ClckFormError Source # | |
Defined in Clckwrks.Monad |
data family ChildType (m :: Type -> Type) :: Type #
Instances
XMLGen m => EmbedAsChild m (ChildType m) | |
Defined in HSP.XMLGenerator asChild :: ChildType m -> GenChildList m # | |
newtype ChildType (HSPT XML m) | |
newtype ChildType (RouteT url m) | |
newtype ChildType (ClckT url m) Source # | |
Defined in Clckwrks.Monad |
data ClckwrksConfig Source #
ClckwrksConfig | |
|
data TLSSettings Source #
TLSSettings | |
|
data family AttributeType (m :: Type -> Type) :: Type #
Instances
XMLGen m => EmbedAsAttr m (AttributeType m) | |
Defined in HSP.XMLGenerator asAttr :: AttributeType m -> GenAttributeList m # | |
newtype AttributeType (HSPT XML m) | |
newtype AttributeType (RouteT url m) | |
Defined in Web.Routes.XMLGenT | |
newtype AttributeType (ClckT url m) Source # | |
Defined in Clckwrks.Monad |
Theme | |
|
data ThemeStyle Source #
ThemeStyle | |
|
newtype ThemeStyleId Source #
Instances
getThemeStyles :: MonadIO m => ClckPlugins -> m [(ThemeStyleId, ThemeStyle)] Source #
themeTemplate :: (EmbedAsChild (ClckT ClckURL (ServerPartT IO)) headers, EmbedAsChild (ClckT ClckURL (ServerPartT IO)) body) => ClckPlugins -> ThemeStyleId -> Text -> headers -> body -> ClckT ClckURL (ServerPartT IO) Response Source #
calcBaseURI :: ClckwrksConfig -> Text Source #
calculate the baseURI from the clckHostname
, clckPort
and clckHidePort
options
calcTLSBaseURI :: ClckwrksConfig -> Maybe Text Source #
:: Monad m | |
=> (url -> [(Text, Maybe Text)] -> Text) | function to act as |
-> ClckState | initial |
-> ClckT url m a |
|
-> m a |
evaluate a ClckT
returning the inner monad
similar to evalStateT
.
:: Monad m | |
=> (url -> [(Text, Maybe Text)] -> Text) | function to act as |
-> ClckState | initial |
-> ClckT url m a |
|
-> m ClckState |
execute a ClckT
returning the final ClckState
similar to execStateT
.
:: (m (a, ClckState) -> n (b, ClckState)) | transformation function |
-> ClckT url m a | initial monad |
-> ClckT url n b |
map a transformation function over the inner monad
similar to mapStateT
withRouteClckT :: ((url' -> [(Text, Maybe Text)] -> Text) -> url -> [(Text, Maybe Text)] -> Text) -> ClckT url m a -> ClckT url' m a Source #
change the route url
ClckState | |
|
a wrapper which identifies how to treat different Text
values when attempting to embed them.
In general Content
values have already been
flattenpreprocessedetc and are now basic formats like
text/plain
, text/html
, etc
Instances
Eq Content Source # | |
Data Content Source # | |
Defined in Clckwrks.Monad gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Content -> c Content # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Content # toConstr :: Content -> Constr # dataTypeOf :: Content -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Content) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Content) # gmapT :: (forall b. Data b => b -> b) -> Content -> Content # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Content -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Content -> r # gmapQ :: (forall d. Data d => d -> u) -> Content -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Content -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Content -> m Content # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Content -> m Content # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Content -> m Content # | |
Ord Content Source # | |
Read Content Source # | |
Show Content Source # | |
(Functor m, Monad m) => EmbedAsChild (ClckT url m) Content Source # | |
Defined in Clckwrks.Monad asChild :: Content -> GenChildList (ClckT url m) # |
addAdminMenu :: Monad m => (Text, [(Set Role, Text, Text)]) -> ClckT url m () Source #
add an Admin menu
appendRequestInit :: Monad m => ServerPart () -> ClckT url m () Source #
append an action to the request init
getNavBarLinks :: MonadIO m => Plugins theme n hook config ClckPluginsSt -> ClckT ClckURL m NavBarLinks Source #
addPreProc :: MonadIO m => Plugins theme n hook config ClckPluginsSt -> (forall mm. (Functor mm, MonadIO mm, Happstack mm) => Text -> ClckT ClckURL mm Text) -> m () Source #
addNavBarCallback :: MonadIO m => Plugins theme n hook config ClckPluginsSt -> ClckT ClckURL IO (String, [NamedLink]) -> m () Source #
getPreProcessors :: MonadIO m => Plugins theme n hook config ClckPluginsSt -> forall mm. (Functor mm, MonadIO mm, Happstack mm) => ClckT url m [Text -> ClckT ClckURL mm Text] Source #
getEnableAnalytics :: (Functor m, MonadState ClckState m) => m Bool Source #
get the Bool
value indicating if Google Analytics should be enabled or not
googleAnalytics :: XMLGenT (Clck url) XML Source #
create a google analytics tracking code block
This will under two different conditions:
- the
enableAnalytics
field inClckState
isFalse
- the
uacct
field inPageState
isNothing
getUnique :: (Functor m, MonadIO m) => ClckT url m Integer Source #
get a unique Integer
.
Only unique for the current request
setRedirectCookie :: Happstack m => String -> m () Source #
query :: forall event m. (QueryEvent event, GetAcidState m (EventState event), Functor m, MonadIO m, MonadState ClckState m) => event -> m (EventResult event) Source #
update :: forall event m. (UpdateEvent event, GetAcidState m (EventState event), Functor m, MonadIO m, MonadState ClckState m) => event -> m (EventResult event) Source #
module HSP.XML
module HSP.XMLGenerator
Orphan instances
GetAcidState m st => GetAcidState (XMLGenT m) st Source # | |
getAcidState :: XMLGenT m (AcidState st) Source # |