-- | A module for compiling Java source files using @javac@. module System.Build.Java.Javac( Javac, -- * Data types referenced by @Javac@ Debug(..), Proc, Implicit, noneProc, only, proc', noneImplicit, class', implicit', -- * @Javac@ members debug, nowarn, verbose, deprecation, classpath, sourcepath, bootclasspath, extdirs, endorseddirs, proc, processor, processorpath, directory, src, implicit, encoding, source, target, version, help, akv, flags, etc, -- * @Javac@ values javac, javac' ) where import Data.List import Data.Maybe import Control.Arrow import System.FilePath import System.Build.CompilePaths import System.Build.Extensions import System.Build.OutputDirectory import System.Build.OutputReferenceSet import System.Build.OutputReferenceGet import System.Build.Command import System.Build.Args -- | The debug options that can be passed to @javac@. data Debug = Lines -- ^ Generate only some debugging info (@lines@). | Vars -- ^ Generate only some debugging info (@vars@). | Source -- ^ Generate only some debugging info (@source@). | None -- ^ Generate no debugging info. | All -- ^ Generate all debugging info. deriving Eq instance Show Debug where show Lines = "lines" show Vars = "vars" show Source = "source" show None = "none" show All = "all" instance ArgShow Debug where arg = show -- | Control whether annotation processing and/or compilation is done. newtype Proc = Proc Bool deriving Eq -- | No annotation processing (@none@). noneProc :: Proc noneProc = Proc False -- | Only annotation processing (@only@). only :: Proc only = Proc True -- | Returns the second argument if the given @Proc@ is @none@, otherwise the third argument. proc' :: Proc -> a -> a -> a proc' (Proc False) _ f = f proc' (Proc True) t _ = t instance Show Proc where show (Proc False) = "none" show (Proc True) = "only" instance ArgShow Proc where arg = show -- | Specify whether or not to generate class files for implicitly referenced files. newtype Implicit = Implicit Bool deriving Eq -- | No generate class files for implicitly referenced files (@none@). noneImplicit :: Implicit noneImplicit = Implicit False -- | Generate class files for implicitly referenced files (@class@). class' :: Implicit class' = Implicit True -- | Returns the second argument if the given @Implicit@ is @none@, otherwise the third argument. implicit' :: Implicit -> a -> a -> a implicit' (Implicit False) _ f = f implicit' (Implicit True) t _ = t instance Show Implicit where show (Implicit False) = "none" show (Implicit True) = "class" instance ArgShow Implicit where arg = show -- | Javac is the compiler for Java source files. data Javac = Javac { debug :: Maybe Debug, -- ^ @-g@ nowarn :: Bool, -- ^ @-nowarn@ verbose :: Bool, -- ^ @-verbose@ deprecation :: Bool, -- ^ @-deprecation@ classpath :: [FilePath], -- ^ @-classpath@ sourcepath :: [FilePath], -- ^ @-sourcepath@ bootclasspath :: [FilePath], -- ^ @-bootclasspath@ extdirs :: [FilePath], -- ^ @-extdirs@ endorseddirs :: [FilePath], -- ^ @-endorseddirs@ proc :: Maybe Proc, -- ^ @-proc@ processor :: [String], -- ^ @-processor@ processorpath :: Maybe FilePath, -- ^ @-processorpath@ directory :: Maybe FilePath, -- ^ @-d@ src :: Maybe FilePath, -- ^ @-s@ implicit :: Maybe Implicit, -- ^ @-implicit@ encoding :: Maybe String, -- ^ @-encoding@ source :: Maybe String, -- ^ @-source@ target :: Maybe String, -- ^ @-target@ version :: Bool, -- ^ @-version@ help :: Bool, -- ^ @-help@ akv :: Maybe ([String], Maybe String), -- ^ @-Akey[=value]@ flags :: [String], -- ^ @-J@ etc :: Maybe String } -- | A @Javac@ with nothing set. javac :: Javac javac = Javac Nothing False False False [] [] [] [] [] Nothing [] Nothing Nothing Nothing Nothing Nothing Nothing Nothing False False Nothing [] Nothing -- | Construct a @Javac@. javac' :: Maybe Debug -> Bool -> Bool -> Bool -> [FilePath] -> [FilePath] -> [FilePath] -> [FilePath] -> [FilePath] -> Maybe Proc -> [String] -> Maybe FilePath -> Maybe FilePath -> Maybe FilePath -> Maybe Implicit -> Maybe String -> Maybe String -> Maybe String -> Bool -> Bool -> Maybe ([String], Maybe String) -> [String] -> Maybe String -> Javac javac' = Javac instance Show Javac where show (Javac debug' nowarn' verbose' deprecation' classpath' sourcepath' bootclasspath' extdirs' endorseddirs' proc'' processor' processorpath' directory' src' implicit'' encoding' source' target' version' help' akv' flags' etc') = [d debug', "nowarn" ~~ nowarn', "verbose" ~~ verbose', "deprecation" ~~ deprecation', "classpath" ~: classpath', "sourcepath" ~: sourcepath', "bootclasspath" ~: bootclasspath', "extdirs" ~: extdirs', "endorseddirs" ~: endorseddirs', "proc" ~~> proc'', case processor' of [] -> [] _ -> intercalate "," processor', "processorpath" ~~> processorpath', "d" ~~> directory', "s" ~~> src', "implicit" ~~> implicit'', "encoding" ~~> encoding', "source" ~~> source', "target" ~~> target', "version" ~~ version', "help" ~~ help', (\z -> "-A" ++ case first (intercalate ".") z of (k, Just v) -> k ++ '=' : v (k, Nothing) -> k) ~? akv', intercalate " " $ map ("-J" ++) flags', fromMaybe [] etc'] ^^^ " " where d (Just All) = "g" ~~ True d k = "g" -~> k instance CompilePaths Javac where j =>> ps = show j ++ ' ' : space ps instance Extensions Javac where exts _ = ["java"] instance OutputDirectory Javac where outdir = directory instance OutputReferenceSet Javac where setReference p j = j { classpath = p } instance OutputReferenceGet Javac where getReference = classpath instance Command Javac where command _ = let envs = [ ("JAVA_HOME", ( "bin" "javac")), ("JDK_HOME", ( "bin" "javac")), ("JAVAC", id) ] in fromMaybe "javac" `fmap` tryEnvs envs