b9-1.1.0: A tool and library for building virtual machine images.

Safe HaskellNone
LanguageHaskell2010

System.IO.B9Extras

Description

Some utilities to deal with IO in B9.

Synopsis

Documentation

data SystemPath Source #

A data type encapsulating different kinds of relative or absolute paths.

Constructors

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 b9 sub of the users application configuration directory getAppUserDataDirectory

InTempDir FilePath

A path relative to the systems temporary directory.

Instances
Eq SystemPath Source # 
Instance details

Defined in System.IO.B9Extras

Data SystemPath Source # 
Instance details

Defined in System.IO.B9Extras

Methods

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 # 
Instance details

Defined in System.IO.B9Extras

Show SystemPath Source # 
Instance details

Defined in System.IO.B9Extras

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

prettyPrintToFile :: (MonadIO m, Show a) => FilePath -> a -> m () Source #

Write a value of a type that is an instance of Show to file. This function uses ppShow instead of the given Show instance.

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.

randomUUID :: MonadIO m => m UUID Source #

Generate a random UUID.

data UUID Source #

A bunch of numbers, enough to make globally unique IDs. Create one of these using randomUUID.

Instances
Eq UUID Source # 
Instance details

Defined in System.IO.B9Extras

Methods

(==) :: UUID -> UUID -> Bool #

(/=) :: UUID -> UUID -> Bool #

Ord UUID Source # 
Instance details

Defined in System.IO.B9Extras

Methods

compare :: UUID -> UUID -> Ordering #

(<) :: UUID -> UUID -> Bool #

(<=) :: UUID -> UUID -> Bool #

(>) :: UUID -> UUID -> Bool #

(>=) :: UUID -> UUID -> Bool #

max :: UUID -> UUID -> UUID #

min :: UUID -> UUID -> UUID #

Read UUID Source # 
Instance details

Defined in System.IO.B9Extras

Show UUID Source # 
Instance details

Defined in System.IO.B9Extras

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

PrintfArg UUID Source # 
Instance details

Defined in System.IO.B9Extras