| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Emanote.Route.Ext
Documentation
Constructors
| SourceExt |
Instances
| ToJSON SourceExt Source # | |
Defined in Emanote.Route.Ext | |
| Data SourceExt Source # | |
Defined in Emanote.Route.Ext Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceExt -> c SourceExt # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceExt # toConstr :: SourceExt -> Constr # dataTypeOf :: SourceExt -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceExt) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceExt) # gmapT :: (forall b. Data b => b -> b) -> SourceExt -> SourceExt # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceExt -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceExt -> r # gmapQ :: (forall d. Data d => d -> u) -> SourceExt -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceExt -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceExt -> m SourceExt # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceExt -> m SourceExt # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceExt -> m SourceExt # | |
| Generic SourceExt Source # | |
| Read SourceExt Source # | |
| Show SourceExt Source # | |
| Eq SourceExt Source # | |
| Ord SourceExt Source # | |
| HasExt 'AnyExt Source # | The AnyExt instance ignores explicitly dealing with extensions, expecting the user to explicitly encode the extension in their value tpye. |
| HasExt 'HeistTpl Source # | |
| HasExt 'Yaml Source # | |
| Indexable SDataIxs SData Source # | |
| Indexable StaticFileIxs StaticFile Source # | |
Defined in Emanote.Model.StaticFile Methods | |
| HasExt ('LMLType 'Md) Source # | |
| HasExt ('LMLType 'Org) Source # | |
| type Rep SourceExt Source # | |
data FileType a where Source #
Constructors
| LMLType :: LML -> FileType SourceExt | |
| Yaml :: FileType SourceExt | |
| HeistTpl :: FileType SourceExt | |
| AnyExt :: FileType SourceExt |
|
| Html :: FileType () | |
| Folder :: FileType () |
Instances
| Eq a => Eq (FileType a) Source # | |
| Ord a => Ord (FileType a) Source # | |
A lightweight markup language
https://en.wikipedia.org/wiki/Lightweight_markup_language
This type exists simply because we may support more formats (eg: org-mode) in the future.
Instances
| ToJSON LML Source # | |
Defined in Emanote.Route.Ext | |
| Data LML Source # | |
Defined in Emanote.Route.Ext Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LML -> c LML # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LML # dataTypeOf :: LML -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LML) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LML) # gmapT :: (forall b. Data b => b -> b) -> LML -> LML # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LML -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LML -> r # gmapQ :: (forall d. Data d => d -> u) -> LML -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LML -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LML -> m LML # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LML -> m LML # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LML -> m LML # | |
| Bounded LML Source # | |
| Enum LML Source # | |
| Generic LML Source # | |
| Eq LML Source # | |
| Ord LML Source # | |
| type Rep LML Source # | |
class HasExt (ext :: FileType a) where Source #
The HasExt class's responsibility is to allow dealing with basepath sans
extension (and vice-versa).
Methods
fileType :: FileType a Source #
withExt :: FilePath -> FilePath Source #
Return the filepath with the known extension.
withoutKnownExt :: FilePath -> Maybe FilePath Source #
Return the filepath without the known extension.
Instances
| HasExt 'AnyExt Source # | The AnyExt instance ignores explicitly dealing with extensions, expecting the user to explicitly encode the extension in their value tpye. |
| HasExt 'HeistTpl Source # | |
| HasExt 'Yaml Source # | |
| HasExt 'Folder Source # | |
| HasExt 'Html Source # | |
| HasExt ('LMLType 'Md) Source # | |
| HasExt ('LMLType 'Org) Source # | |
fpWithoutExt :: (Monad m, Alternative m) => String -> FilePath -> m FilePath Source #