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

Safe HaskellNone
LanguageHaskell2010

B9.ShellScript

Description

Definition of Script and functions to convert Scripts to bash scripts.

Synopsis

Documentation

writeSh :: FilePath -> Script -> IO () Source #

Convert script to bash-shell-script written to file and make file executable.

emptyScript :: Script -> Bool Source #

Check if a script has the same effect as NoOP

data CmdVerbosity Source #

Constructors

Debug 
Verbose 
OnlyStdErr 
Quiet 

Instances

Eq CmdVerbosity Source # 
Data CmdVerbosity Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CmdVerbosity -> c CmdVerbosity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CmdVerbosity #

toConstr :: CmdVerbosity -> Constr #

dataTypeOf :: CmdVerbosity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CmdVerbosity) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CmdVerbosity) #

gmapT :: (forall b. Data b => b -> b) -> CmdVerbosity -> CmdVerbosity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CmdVerbosity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CmdVerbosity -> r #

gmapQ :: (forall d. Data d => d -> u) -> CmdVerbosity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CmdVerbosity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CmdVerbosity -> m CmdVerbosity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CmdVerbosity -> m CmdVerbosity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CmdVerbosity -> m CmdVerbosity #

Read CmdVerbosity Source # 
Show CmdVerbosity Source # 
Generic CmdVerbosity Source # 

Associated Types

type Rep CmdVerbosity :: * -> * #

Hashable CmdVerbosity Source # 
Binary CmdVerbosity Source # 
NFData CmdVerbosity Source # 

Methods

rnf :: CmdVerbosity -> () #

type Rep CmdVerbosity Source # 
type Rep CmdVerbosity = D1 * (MetaData "CmdVerbosity" "B9.ShellScript" "b9-0.5.48-J0n1eP3yIuK7a2bmFVpoGi" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Debug" PrefixI False) (U1 *)) (C1 * (MetaCons "Verbose" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "OnlyStdErr" PrefixI False) (U1 *)) (C1 * (MetaCons "Quiet" PrefixI False) (U1 *))))

data Cwd Source #

Constructors

Cwd FilePath 
NoCwd 

Instances

Eq Cwd Source # 

Methods

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

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

Data Cwd Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cwd -> c Cwd #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cwd #

toConstr :: Cwd -> Constr #

dataTypeOf :: Cwd -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Cwd) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cwd) #

gmapT :: (forall b. Data b => b -> b) -> Cwd -> Cwd #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cwd -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cwd -> r #

gmapQ :: (forall d. Data d => d -> u) -> Cwd -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Cwd -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cwd -> m Cwd #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cwd -> m Cwd #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cwd -> m Cwd #

Read Cwd Source # 
Show Cwd Source # 

Methods

showsPrec :: Int -> Cwd -> ShowS #

show :: Cwd -> String #

showList :: [Cwd] -> ShowS #

Generic Cwd Source # 

Associated Types

type Rep Cwd :: * -> * #

Methods

from :: Cwd -> Rep Cwd x #

to :: Rep Cwd x -> Cwd #

Hashable Cwd Source # 

Methods

hashWithSalt :: Int -> Cwd -> Int #

hash :: Cwd -> Int #

Binary Cwd Source # 

Methods

put :: Cwd -> Put #

get :: Get Cwd #

putList :: [Cwd] -> Put #

NFData Cwd Source # 

Methods

rnf :: Cwd -> () #

type Rep Cwd Source # 
type Rep Cwd = D1 * (MetaData "Cwd" "B9.ShellScript" "b9-0.5.48-J0n1eP3yIuK7a2bmFVpoGi" False) ((:+:) * (C1 * (MetaCons "Cwd" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath))) (C1 * (MetaCons "NoCwd" PrefixI False) (U1 *)))

data User Source #

Constructors

User String 
NoUser 

Instances

Eq User Source # 

Methods

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

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

Data User Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> User -> c User #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c User #

toConstr :: User -> Constr #

dataTypeOf :: User -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c User) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c User) #

gmapT :: (forall b. Data b => b -> b) -> User -> User #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> User -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> User -> r #

gmapQ :: (forall d. Data d => d -> u) -> User -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> User -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> User -> m User #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> User -> m User #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> User -> m User #

Read User Source # 
Show User Source # 

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

Generic User Source # 

Associated Types

type Rep User :: * -> * #

Methods

from :: User -> Rep User x #

to :: Rep User x -> User #

Hashable User Source # 

Methods

hashWithSalt :: Int -> User -> Int #

hash :: User -> Int #

Binary User Source # 

Methods

put :: User -> Put #

get :: Get User #

putList :: [User] -> Put #

NFData User Source # 

Methods

rnf :: User -> () #

type Rep User Source # 
type Rep User = D1 * (MetaData "User" "B9.ShellScript" "b9-0.5.48-J0n1eP3yIuK7a2bmFVpoGi" False) ((:+:) * (C1 * (MetaCons "User" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) (C1 * (MetaCons "NoUser" PrefixI False) (U1 *)))

data Script Source #

Instances

Eq Script Source # 

Methods

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

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

Data Script Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Script -> c Script #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Script #

toConstr :: Script -> Constr #

dataTypeOf :: Script -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Script) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Script) #

gmapT :: (forall b. Data b => b -> b) -> Script -> Script #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Script -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Script -> r #

gmapQ :: (forall d. Data d => d -> u) -> Script -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Script -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Script -> m Script #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Script -> m Script #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Script -> m Script #

Read Script Source # 
Show Script Source # 
Generic Script Source # 

Associated Types

type Rep Script :: * -> * #

Methods

from :: Script -> Rep Script x #

to :: Rep Script x -> Script #

Semigroup Script Source # 
Monoid Script Source # 
Hashable Script Source # 

Methods

hashWithSalt :: Int -> Script -> Int #

hash :: Script -> Int #

Binary Script Source # 

Methods

put :: Script -> Put #

get :: Get Script #

putList :: [Script] -> Put #

NFData Script Source # 

Methods

rnf :: Script -> () #

type Rep Script Source # 
type Rep Script = D1 * (MetaData "Script" "B9.ShellScript" "b9-0.5.48-J0n1eP3yIuK7a2bmFVpoGi" False) ((:+:) * ((:+:) * (C1 * (MetaCons "In" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Script])))) ((:+:) * (C1 * (MetaCons "As" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Script])))) (C1 * (MetaCons "IgnoreErrors" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Script])))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Verbosity" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CmdVerbosity)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Script])))) (C1 * (MetaCons "Begin" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Script])))) ((:+:) * (C1 * (MetaCons "Run" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])))) (C1 * (MetaCons "NoOP" PrefixI False) (U1 *)))))