jbi-0.1.0.0: Just Build It - a "do what I mean" abstraction for Haskell build tools

Copyright(c) Ivan Lazar Miljenovic
LicenseMIT
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone
LanguageHaskell2010

System.JBI.Commands.BuildTool

Description

 

Synopsis

Documentation

class Tool bt => BuildTool bt where Source #

Methods

canUseCommand :: GlobalEnv -> Installed bt -> IO Bool Source #

Make sure there's nothing in the environment preventing us from using this tool.

For example, a minimum version, need another tool installed, etc.

commandProjectRoot :: Tagged bt CommandPath -> IO (Maybe (Tagged bt ProjectRoot)) Source #

Try and determine the root directory for this project.

hasBuildArtifacts :: Tagged bt ProjectRoot -> IO Bool Source #

commandPrepare :: GlobalEnv -> Tagged bt CommandPath -> IO ExitCode Source #

Ensure's that hasBuildArtifacts is True afterwards; i.e. forces this build tool.

The intent for this is "No build tool is currently being used (i.e. hasBuildArtifacts is False for all) so start using the one chosen." This will not do the equivalent of stack init and create project configuration.

Some manual fiddling is allowed after this.

Assumes canUseBuildTool. Should be run within ProjectRoot.

commandTargets :: Tagged bt CommandPath -> IO [Tagged bt ProjectTarget] Source #

Assumes canUseBuildTool. Should be run within ProjectRoot.

commandBuild :: GlobalEnv -> Tagged bt CommandPath -> Maybe (Tagged bt ProjectTarget) -> IO ExitCode Source #

Assumes canUseBuildTool. Should be run within ProjectRoot.

commandRepl :: GlobalEnv -> Tagged bt CommandPath -> Maybe (Tagged bt ProjectTarget) -> IO ExitCode Source #

Launch a ghci session within the current project. Should pass through the -ferror-spans argument to the underlying ghci process.

Assumes canUseBuildTool. Should be run within ProjectRoot.

commandClean :: GlobalEnv -> Tagged bt CommandPath -> IO ExitCode Source #

Remove all build artifacts of using this build tool (that is, afterwards hasBuildArtifacts should return False).

Assumes canUseBuildTool. Should be run within ProjectRoot.

commandTest :: GlobalEnv -> Tagged bt CommandPath -> IO ExitCode Source #

Assumes canUseBuildTool. Should be run within ProjectRoot.

commandBench :: GlobalEnv -> Tagged bt CommandPath -> IO ExitCode Source #

Assumes canUseBuildTool. Should be run within ProjectRoot.

commandExec :: GlobalEnv -> Tagged bt CommandPath -> String -> Args -> IO ExitCode Source #

Run an external command within this environment.

Assumes canUseBuildTool. Should be run within ProjectRoot.

commandRun :: GlobalEnv -> Tagged bt CommandPath -> Tagged bt ProjectTarget -> Args -> IO ExitCode Source #

Run an executable component within this environment (building it first if required).

Assumes canUseBuildTool. Should be run within ProjectRoot.

commandUpdate :: GlobalEnv -> Tagged bt CommandPath -> IO ExitCode Source #

Update index of available packages.

Instances

BuildTool Stack Source # 
CabalMode mode => BuildTool (Cabal mode) Source # 

class BuildTool bt => NamedTool bt where Source #

This class exists because of:

a) Distinguish the different Cabal variants

b) Be able to use a wrapper GADT that takes a proxy bt and can be an instance of BuildTool but not this.

Methods

prettyName :: proxy bt -> String Source #

Instances

NamedTool Stack Source # 

Methods

prettyName :: proxy Stack -> String Source #

CabalMode mode => NamedTool (Cabal mode) Source # 

Methods

prettyName :: proxy (Cabal mode) -> String Source #

data ToolInformation bt Source #

Constructors

ToolInformation 

Fields

Instances

Eq (ToolInformation bt) Source # 
Read (ToolInformation bt) Source # 
Show (ToolInformation bt) Source # 
Show (WrappedTool ToolInformation) # 
Generic (ToolInformation bt) Source # 

Associated Types

type Rep (ToolInformation bt) :: * -> * #

ToJSON (ToolInformation bt) Source # 
ToJSON (WrappedTool ToolInformation) # 
type Rep (ToolInformation bt) Source # 
type Rep (ToolInformation bt) = D1 (MetaData "ToolInformation" "System.JBI.Commands.BuildTool" "jbi-0.1.0.0-H3lqhY7ZSRMEKM0XTQQkPr" False) (C1 (MetaCons "ToolInformation" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "tool") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)) (S1 (MetaSel (Just Symbol "information") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (BuildUsage bt))))))

data BuildUsage bt Source #

Constructors

BuildUsage 

Fields

Instances

Eq (BuildUsage bt) Source # 

Methods

(==) :: BuildUsage bt -> BuildUsage bt -> Bool #

(/=) :: BuildUsage bt -> BuildUsage bt -> Bool #

Read (BuildUsage bt) Source # 
Show (BuildUsage bt) Source # 

Methods

showsPrec :: Int -> BuildUsage bt -> ShowS #

show :: BuildUsage bt -> String #

showList :: [BuildUsage bt] -> ShowS #

Generic (BuildUsage bt) Source # 

Associated Types

type Rep (BuildUsage bt) :: * -> * #

Methods

from :: BuildUsage bt -> Rep (BuildUsage bt) x #

to :: Rep (BuildUsage bt) x -> BuildUsage bt #

ToJSON (BuildUsage bt) Source # 
type Rep (BuildUsage bt) Source # 
type Rep (BuildUsage bt) = D1 (MetaData "BuildUsage" "System.JBI.Commands.BuildTool" "jbi-0.1.0.0-H3lqhY7ZSRMEKM0XTQQkPr" False) (C1 (MetaCons "BuildUsage" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "installation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Installed bt))) ((:*:) (S1 (MetaSel (Just Symbol "usable") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "project") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (BuildProject bt)))))))

data BuildProject bt Source #

Constructors

BuildProject 

Instances

Eq (BuildProject bt) Source # 

Methods

(==) :: BuildProject bt -> BuildProject bt -> Bool #

(/=) :: BuildProject bt -> BuildProject bt -> Bool #

Read (BuildProject bt) Source # 
Show (BuildProject bt) Source # 
Generic (BuildProject bt) Source # 

Associated Types

type Rep (BuildProject bt) :: * -> * #

Methods

from :: BuildProject bt -> Rep (BuildProject bt) x #

to :: Rep (BuildProject bt) x -> BuildProject bt #

ToJSON (BuildProject bt) Source # 
type Rep (BuildProject bt) Source # 
type Rep (BuildProject bt) = D1 (MetaData "BuildProject" "System.JBI.Commands.BuildTool" "jbi-0.1.0.0-H3lqhY7ZSRMEKM0XTQQkPr" False) (C1 (MetaCons "BuildProject" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "projectRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Tagged * bt ProjectRoot))) (S1 (MetaSel (Just Symbol "artifactsPresent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))))

commandBuildUsage :: BuildTool bt => GlobalEnv -> IO (Maybe (BuildUsage bt)) Source #

A Nothing indicates that this tool cannot be used for this project (i.e. needs configuration).

safeLast :: [[a]] -> [a] Source #

splitOn :: Eq a => a -> [a] -> [[a]] Source #

tryIO :: IO (Maybe a) -> IO (Maybe a) Source #

If an exception occurs, return Nothing

recurseUpFindFile :: (FilePath -> Bool) -> IO (Maybe FilePath) Source #

Recurse up until you find a directory containing a file that matches the predicate, returning that directory.