Safe Haskell | None |
---|---|
Language | Haskell2010 |
Some utilities to deal with IO in B9.
Synopsis
- data SystemPath
- overSystemPath :: (FilePath -> FilePath) -> SystemPath -> SystemPath
- resolve :: MonadIO m => SystemPath -> m FilePath
- ensureSystemPath :: MonadIO m => SystemPath -> m ()
- ensureDir :: MonadIO m => FilePath -> m ()
- getDirectoryFiles :: MonadIO m => FilePath -> m [FilePath]
- prettyPrintToFile :: (MonadIO m, Show a) => FilePath -> a -> m ()
- consult :: (MonadIO m, Read a) => FilePath -> m a
- data ConsultException = ConsultException FilePath String
- randomUUID :: MonadIO m => m UUID
- data UUID
- removeIfExists :: FilePath -> IO ()
Documentation
data SystemPath Source #
A data type encapsulating different kinds of relative or absolute paths.
Path FilePath | A path that will just be passed through |
InHomeDir FilePath | A OS specific path relative to the home directory of a user. |
InB9UserDir FilePath | A path relative to the |
InTempDir FilePath | A path relative to the systems temporary directory. |
Instances
Eq SystemPath Source # | |
Defined in System.IO.B9Extras (==) :: SystemPath -> SystemPath -> Bool # (/=) :: SystemPath -> SystemPath -> Bool # | |
Data SystemPath Source # | |
Defined in System.IO.B9Extras gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SystemPath -> c SystemPath # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SystemPath # toConstr :: SystemPath -> Constr # dataTypeOf :: SystemPath -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SystemPath) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SystemPath) # gmapT :: (forall b. Data b => b -> b) -> SystemPath -> SystemPath # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SystemPath -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SystemPath -> r # gmapQ :: (forall d. Data d => d -> u) -> SystemPath -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SystemPath -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SystemPath -> m SystemPath # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SystemPath -> m SystemPath # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SystemPath -> m SystemPath # | |
Read SystemPath Source # | |
Defined in System.IO.B9Extras readsPrec :: Int -> ReadS SystemPath # readList :: ReadS [SystemPath] # readPrec :: ReadPrec SystemPath # readListPrec :: ReadPrec [SystemPath] # | |
Show SystemPath Source # | |
Defined in System.IO.B9Extras showsPrec :: Int -> SystemPath -> ShowS # show :: SystemPath -> String # showList :: [SystemPath] -> ShowS # |
overSystemPath :: (FilePath -> FilePath) -> SystemPath -> SystemPath Source #
Transform a SystemPath
resolve :: MonadIO m => SystemPath -> m FilePath Source #
Convert a SystemPath
to a FilePath
.
ensureSystemPath :: MonadIO m => SystemPath -> m () Source #
Create all missing parent directories of a file path.
Since: 1.1.0
ensureDir :: MonadIO m => FilePath -> m () Source #
Create all missing parent directories of a file path.
Note that the file path is assumed to be of a regular file, and
takeDirectory
is applied before creating the directory.
getDirectoryFiles :: MonadIO m => FilePath -> m [FilePath] Source #
Get all files from dir
that is get ONLY files not directories
consult :: (MonadIO m, Read a) => FilePath -> m a Source #
Read a value of a type that is an instance of Read
from a file.
This function throws a ConsultException
when the read the file failed.
data ConsultException Source #
Instances
Show ConsultException Source # | |
Defined in System.IO.B9Extras showsPrec :: Int -> ConsultException -> ShowS # show :: ConsultException -> String # showList :: [ConsultException] -> ShowS # | |
Exception ConsultException Source # | |
Defined in System.IO.B9Extras |
A bunch of numbers, enough to make globally unique IDs. Create one of these
using randomUUID
.
removeIfExists :: FilePath -> IO () Source #