| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Shakebook.Data
Synopsis
- type ToC = Cofree [] String
- data SbConfig = SbConfig {}
- class HasSbConfig a where
- newtype Shakebook r a = Shakebook (ReaderT r Rules a)
- newtype ShakebookA r a = ShakebookA (ReaderT r Action a)
- runShakebook :: r -> Shakebook r a -> Rules a
- runShakebookA :: r -> ShakebookA r a -> Action a
- class MonadAction m where
- liftAction :: Action a -> m a
- class MonadRules m where
- data ShakebookEnv = ShakebookEnv {}
- type MonadShakebook r m = (MonadReader r m, HasSbConfig r, HasLogFunc r, MonadIO m)
- type MonadShakebookAction r m = (MonadShakebook r m, MonadAction m)
- type MonadShakebookRules r m = (MonadShakebook r m, MonadRules m)
- viewSrcPath :: Value -> Text
- withSrcPath :: Text -> Value -> Value
- withBaseUrl :: Text -> Value -> Value
- withFullUrl :: Text -> Value -> Value
- viewUrl :: Value -> Text
- withUrl :: Text -> Value -> Value
- enrichFullUrl :: Text -> Value -> Value
- enrichUrl :: (Text -> Text) -> Value -> Value
- typicalFullOutToSrcPath :: MonadShakebook r m => m (String -> String)
- typicalFullOutToFullSrcPath :: MonadShakebook r m => m (String -> String)
- typicalFullOutHTMLToMdSrcPath :: MonadShakebook r m => m (String -> String)
- typicalMdSrcPathToHTMLFullOut :: MonadShakebook r m => m (String -> String)
- typicalSrcPathToUrl :: Text -> Text
- typicalUrlEnricher :: Value -> Value
- readMarkdownFile' :: MonadShakebookAction r m => String -> m Value
- loadIfExists :: (FilePath -> Action Value) -> FilePath -> Action Value
- getMarkdown :: MonadShakebookAction r m => [FilePattern] -> m [Value]
- genBuildPageAction :: MonadShakebookAction r m => FilePath -> (FilePath -> m Value) -> (Value -> Value) -> FilePath -> m Value
- traverseToSnd :: Functor f => (a -> f b) -> a -> f (a, b)
- lower :: Cofree [] Value -> [Value]
- loadSortFilterEnrich :: (MonadShakebookAction r m, Ord b) => [FilePattern] -> (Value -> b) -> (Value -> Bool) -> (Value -> Value) -> m [(FilePath, Value)]
- loadSortEnrich :: (MonadShakebookAction r m, Ord b) => [FilePattern] -> (Value -> b) -> (Value -> Value) -> m [(String, Value)]
Documentation
Constructors
| SbConfig | |
class HasSbConfig a where Source #
Instances
| HasSbConfig ShakebookEnv Source # | |
Defined in Shakebook.Data | |
newtype ShakebookA r a Source #
Constructors
| ShakebookA (ReaderT r Action a) |
Instances
runShakebook :: r -> Shakebook r a -> Rules a Source #
runShakebookA :: r -> ShakebookA r a -> Action a Source #
class MonadAction m where Source #
Methods
liftAction :: Action a -> m a Source #
Instances
| MonadAction (ShakebookA r) Source # | |
Defined in Shakebook.Data Methods liftAction :: Action a -> ShakebookA r a Source # | |
class MonadRules m where Source #
Instances
| MonadRules (Shakebook r) Source # | |
data ShakebookEnv Source #
Constructors
| ShakebookEnv | |
Instances
| HasLogFunc ShakebookEnv Source # | |
Defined in Shakebook.Data Methods | |
| HasSbConfig ShakebookEnv Source # | |
Defined in Shakebook.Data | |
type MonadShakebook r m = (MonadReader r m, HasSbConfig r, HasLogFunc r, MonadIO m) Source #
type MonadShakebookAction r m = (MonadShakebook r m, MonadAction m) Source #
type MonadShakebookRules r m = (MonadShakebook r m, MonadRules m) Source #
viewSrcPath :: Value -> Text Source #
View the "srcPath" field of a JSON Value.
enrichUrl :: (Text -> Text) -> Value -> Value Source #
Assuming a srcPath field, enrich using withUrl using a Text -> Text transformation.
typicalFullOutToSrcPath :: MonadShakebook r m => m (String -> String) Source #
Filepath/URL calculators - these work but don't try to do the wrong thing or it will explode.
typicalFullOutToFullSrcPath :: MonadShakebook r m => m (String -> String) Source #
typicalFullOutHTMLToMdSrcPath :: MonadShakebook r m => m (String -> String) Source #
typicalMdSrcPathToHTMLFullOut :: MonadShakebook r m => m (String -> String) Source #
typicalSrcPathToUrl :: Text -> Text Source #
typicalUrlEnricher :: Value -> Value Source #
readMarkdownFile' :: MonadShakebookAction r m => String -> m Value Source #
Get a JSON Value of Markdown Data with markdown body as "contents" field and the srcPath as "srcPath" field.
getMarkdown :: MonadShakebookAction r m => [FilePattern] -> m [Value] Source #
Arguments
| :: MonadShakebookAction r m | |
| => FilePath | The HTML template |
| -> (FilePath -> m Value) | How to get from FilePath to Value, can use Actions. |
| -> (Value -> Value) | Additional modifiers for the value. |
| -> FilePath | The out filepath |
| -> m Value |
Build a single page straight from a template, a loaded Value, and a pure enrichment.
traverseToSnd :: Functor f => (a -> f b) -> a -> f (a, b) Source #
Arguments
| :: (MonadShakebookAction r m, Ord b) | |
| => [FilePattern] | A shake filepattern to load, relative to srcDir from SbConfig. |
| -> (Value -> b) | A value to sortOn e.g (Down . viewPostTime) |
| -> (Value -> Bool) | A filtering predicate e.g (elem tag . viewTags) |
| -> (Value -> Value) | An initial enrichment. This is pure so can only be data derived from the initial markdown. |
| -> m [(FilePath, Value)] | A list of Values indexed by their srcPath. |
Multi-markdown loader. Allows you to load a filepattern of markdown as a list of JSON values ready to pass to an HTML template. You will probably want to add additional data before you write. See the examples in Shakebook.Defaults
Arguments
| :: (MonadShakebookAction r m, Ord b) | |
| => [FilePattern] | A Shake filepattern to load. |
| -> (Value -> b) | A value to sortOn e.g (Down . viewPostTime). |
| -> (Value -> Value) | An initial pure enrichment. |
| -> m [(String, Value)] | A list of Values index by their srcPath. |
The same as loadSortFilterEnrich but without filtering.