| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Hakyll.Core.Metadata
Synopsis
- type Metadata = Object
- lookupString :: String -> Metadata -> Maybe String
- lookupStringList :: String -> Metadata -> Maybe [String]
- class Monad m => MonadMetadata m where- getMetadata :: Identifier -> m Metadata
- getMatches :: Pattern -> m [Identifier]
- getAllMetadata :: Pattern -> m [(Identifier, Metadata)]
 
- getMetadataField :: MonadMetadata m => Identifier -> String -> m (Maybe String)
- getMetadataField' :: (MonadFail m, MonadMetadata m) => Identifier -> String -> m String
- makePatternDependency :: MonadMetadata m => Pattern -> m Dependency
- newtype BinaryMetadata = BinaryMetadata {}
Documentation
class Monad m => MonadMetadata m where Source #
Minimal complete definition
Methods
getMetadata :: Identifier -> m Metadata Source #
getMatches :: Pattern -> m [Identifier] Source #
getAllMetadata :: Pattern -> m [(Identifier, Metadata)] Source #
Instances
| MonadMetadata Compiler Source # | Access provided metadata from anywhere | 
| Defined in Hakyll.Core.Compiler.Internal Methods getMetadata :: Identifier -> Compiler Metadata Source # getMatches :: Pattern -> Compiler [Identifier] Source # getAllMetadata :: Pattern -> Compiler [(Identifier, Metadata)] Source # | |
| MonadMetadata Rules Source # | |
| Defined in Hakyll.Core.Rules.Internal Methods getMetadata :: Identifier -> Rules Metadata Source # getMatches :: Pattern -> Rules [Identifier] Source # getAllMetadata :: Pattern -> Rules [(Identifier, Metadata)] Source # | |
getMetadataField :: MonadMetadata m => Identifier -> String -> m (Maybe String) Source #
getMetadataField' :: (MonadFail m, MonadMetadata m) => Identifier -> String -> m String Source #
Version of getMetadataField which throws an error if the field does not
 exist.
makePatternDependency :: MonadMetadata m => Pattern -> m Dependency Source #
newtype BinaryMetadata Source #
Newtype wrapper for serialization.
Constructors
| BinaryMetadata | |
| Fields | |
Instances
| Binary BinaryMetadata Source # | |
| Defined in Hakyll.Core.Metadata Methods put :: BinaryMetadata -> Put # get :: Get BinaryMetadata # putList :: [BinaryMetadata] -> Put # | |