cake3-0.6.4: Third cake the Makefile EDSL

Safe HaskellSafe
LanguageHaskell98

Development.Cake3.Types

Synopsis

Documentation

data Variable Source #

The representation of Makefile variable.

Constructors

Variable 

Fields

  • vname :: String

    The name of a variable

  • vval :: Maybe String

    Nothing means that variable is defined elsewhere (eg. borrowed from the environment)

Instances

Eq Variable Source # 
Data Variable Source # 

Methods

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

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

toConstr :: Variable -> Constr #

dataTypeOf :: Variable -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Variable Source # 
Show Variable Source # 
Monad m => RefInput (A' m) Variable Source # 

data Tool Source #

The representation a tool used by the Makefile's recipe. Typical example are gcc or bison

Constructors

Tool 

Fields

Instances

Eq Tool Source # 

Methods

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

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

Data Tool Source # 

Methods

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

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

toConstr :: Tool -> Constr #

dataTypeOf :: Tool -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Tool Source # 

Methods

compare :: Tool -> Tool -> Ordering #

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

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

(>) :: Tool -> Tool -> Bool #

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

max :: Tool -> Tool -> Tool #

min :: Tool -> Tool -> Tool #

Show Tool Source # 

Methods

showsPrec :: Int -> Tool -> ShowS #

show :: Tool -> String #

showList :: [Tool] -> ShowS #

Monad m => RefInput (A' m) Tool Source # 

Methods

refInput :: Tool -> A' m Command Source #

type Command = [CommandPiece] Source #

Command represents OS command line and consists of a list of fragments. Each fragment is either text (may contain spaces) or FilePath (spaces should be escaped)

data CommandPiece Source #

Constructors

CmdStr String 
CmdFile File 

Instances

Eq CommandPiece Source # 
Data CommandPiece Source # 

Methods

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

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

toConstr :: CommandPiece -> Constr #

dataTypeOf :: CommandPiece -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CommandPiece Source # 
Show CommandPiece Source # 

data Flag Source #

Constructors

Phony 
Intermediate 

Instances

Eq Flag Source # 

Methods

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

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

Data Flag Source # 

Methods

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

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

toConstr :: Flag -> Constr #

dataTypeOf :: Flag -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Flag Source # 

Methods

compare :: Flag -> Flag -> Ordering #

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

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

(>) :: Flag -> Flag -> Bool #

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

max :: Flag -> Flag -> Flag #

min :: Flag -> Flag -> Flag #

Show Flag Source # 

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

data Recipe Source #

Recipe answers to the question 'How to build the targets'. Internally, it contains sets of targets and prerequisites, as well as shell commands required to build former from latter

Constructors

Recipe 

Fields

Instances

Eq Recipe Source # 

Methods

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

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

Data Recipe Source # 

Methods

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

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

toConstr :: Recipe -> Constr #

dataTypeOf :: Recipe -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Recipe Source # 
Show Recipe Source # 
Monad m => MonadState Recipe (A' m) # 

Methods

get :: A' m Recipe #

put :: Recipe -> A' m () #

state :: (Recipe -> (a, Recipe)) -> A' m a #

Monad m => RefInput (A' m) Recipe Source # 

Methods

refInput :: Recipe -> A' m Command Source #

groupSet :: (Ord k, Ord x, Foldable t) => (x -> Set k) -> t x -> Map k (Set x) Source #

flattern :: [Set x] -> [x] Source #

applyPlacement' :: Eq x => [File] -> Map File x -> [x] Source #

transformRecipesM_ :: (Monad m, Foldable t) => (Recipe -> m ()) -> t Recipe -> m () Source #

makevar Source #

Arguments

:: String

Variable name

-> String

Default value

-> Variable 

Define the Makefile-level variable. Rules, referring to a variable, notice it's changes.

extvar :: String -> Variable Source #

Declare the variable defined elsewhere. Typycally, environment variables may be decalred with this functions. Variables are tracked by the cake3. Rules, referring to a variable, notice it's changes.

make :: Variable Source #

Reref to special variable $(MAKE)

data ModuleLocation Source #

Constructors

ModuleLocation 

Fields

Instances

Eq ModuleLocation Source # 
Data ModuleLocation Source # 

Methods

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

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

toConstr :: ModuleLocation -> Constr #

dataTypeOf :: ModuleLocation -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ModuleLocation Source # 
Show ModuleLocation Source # 
EmbedDecl File Source # 

Methods

embed :: MonadMake m => File -> UrpGen m () Source #

SrcDecl File Source # 

Methods

src :: MonadMake m => File -> UrpGen m () Source #

LinkDecl File Source # 

Methods

link :: MonadMake m => File -> UrpGen m () Source #

ModuleDecl File Source # 

Methods

ur :: Monad m => File -> UrpGen m () Source #

Monad m => RefOutput m File Source # 

Methods

refOutput :: File -> A' m Command Source #

Monad m => LibraryDecl m File Source # 

Methods

library :: File -> UrpGen m () Source #

RefOutput m File => RefOutput m (m File) Source # 

Methods

refOutput :: m File -> A' m Command Source #

Monad m => RefOutput m (Set File) Source # 
Monad m => RefOutput m [File] Source # 

Methods

refOutput :: [File] -> A' m Command Source #

Monad m => LibraryDecl m (m File) Source # 

Methods

library :: m File -> UrpGen m () Source #

Monad m => LibraryDecl m [File] Source # 

Methods

library :: [File] -> UrpGen m () Source #

Monad m => RefInput (A' m) File Source # 

Methods

refInput :: File -> A' m Command Source #

Monad m => RefInput (UrpGen m) File Source # 
LinkDecl (File, String) Source # 

Methods

link :: MonadMake m => (File, String) -> UrpGen m () Source #

ModuleDecl (File, File) Source # 

Methods

ur :: Monad m => (File, File) -> UrpGen m () Source #

SrcDecl (File, String, String) Source # 

Methods

src :: MonadMake m => (File, String, String) -> UrpGen m () Source #

type File = FileT ModuleLocation FilePath Source #

Simple wrapper for FilePath. The first type argument is a Hint, containing the path to the current module

file' :: ModuleLocation -> FilePath -> File Source #

Converts string representation of Path into type-safe File. Internally, files are stored in a form of offset from module root directory, plus the path from top-level dir to module root and back (see ModuleLocation)

TODO: rename to mkFile

fileModule :: File -> File Source #

Path to the module (a directory), which have originally declared the file

dottify :: FilePath -> FilePath Source #

Adds ./ before the path, marking it as relative

topRel :: File -> FilePath Source #

Returns the path to the file, relative to the top-level directory (the place, where the target Makefile is located)

wayback :: FilePath -> FilePath Source #

Converts path x to the back-path, consisting of '..' directories

route :: File -> File -> FilePath Source #

Returns path from file s to t, via the top-level directory

escapeFile :: File -> FilePath Source #

Convert File back to FilePath with escaped spaces