-- | A module for documenting Java source files using @javadoc@. module Lastik.Java.Javadoc( SourceRelease(..), Javadoc, overview, public, protected, package, private, help, doclet, docletpath, sourcepath, classpath, exclude, subpackages, breakiterator, bootclasspath, source, extdirs, verbose, locale, encoding, quiet, flags, directory, use, version, author, docfilessubdirs, splitindex, windowtitle, doctitle, header, footer, top, bottom, link, linkoffline, excludedocfilessubdir, group, nocomment, nodeprecated, noqualifier, nosince, notimestamp, nodeprecatedlist, notree, noindex, nohelp, nonavbar, serialwarn, tag, taglet, tagletpath, charset, helpfile, linksource, sourcetab, keywords, stylesheetfile, docencoding, javadoc, javadoc' ) where import Lastik.Util import Lastik.Compile import Lastik.Output import Lastik.Extension import Data.List hiding (group) -- | Provide source compatibility with specified release data SourceRelease = S15 -- ^ @1.5@ | S14 -- ^ @1.4@ | S13 -- ^ @1.3@ deriving Eq instance Show SourceRelease where show S15 = "1.5" show S14 = "1.4" show S13 = "1.3" -- | Javadoc is the compiler for Java API documentation. data Javadoc = Javadoc { overview :: Maybe FilePath, -- ^ @-overview@ public :: Bool, -- ^ @-public@ protected :: Bool, -- ^ @-protected@ package :: Bool, -- ^ @-package@ private :: Bool, -- ^ @-private@ help :: Bool, -- ^ @-help@ doclet :: Maybe String, -- ^ @-doclet@ docletpath :: Maybe FilePath, -- ^ @-docletpath@ sourcepath :: [FilePath], -- ^ @-sourcepath@ classpath :: [FilePath], -- ^ @-classpath@ exclude :: [String], -- ^ @-exclude@ subpackages :: [String], -- ^ @-subpackages@ breakiterator :: Bool, -- ^ @-breakiterator@ bootclasspath :: [FilePath], -- ^ @-bootclasspath@ source :: Maybe SourceRelease, -- ^ @-source@ extdirs :: [FilePath], -- ^ @-extdirs@ verbose :: Bool, -- ^ @-verbose@ locale :: Maybe String, -- ^ @-locale@ encoding :: Maybe String, -- ^ @-encoding@ quiet :: Bool, -- ^ @-quiet@ flags :: [String], -- ^ @-flags@ directory :: Maybe FilePath, -- ^ @-d@ use :: Bool, -- ^ @-use@ version :: Bool, -- ^ @-version@ author :: Bool, -- ^ @-author@ docfilessubdirs :: Bool, -- ^ @-docfilessubdirs@ splitindex :: Bool, -- ^ @-splitindex@ windowtitle :: Maybe String, -- ^ @-windowtitle@ doctitle :: Maybe String, -- ^ @-doctitle@ header :: Maybe String, -- ^ @-header@ footer :: Maybe String, -- ^ @-footer@ top :: Maybe String, -- ^ @-top@ bottom :: Maybe String, -- ^ @-bottom@ link :: [String], -- ^ @-link@ linkoffline :: [(String, String)], -- ^ @-linkoffline@ excludedocfilessubdir :: [String], -- ^ @-excludedocfilessubdir@ group :: [(String, [String])], -- ^ @-group@ nocomment :: Bool, -- ^ @-nocomment@ nodeprecated :: Bool, -- ^ @-nodeprecated@ noqualifier :: [String], -- ^ @-noqualifier@ nosince :: Bool, -- ^ @-nosince@ notimestamp :: Bool, -- ^ @-notimestamp@ nodeprecatedlist :: Bool, -- ^ @-nodeprecatedlist@ notree :: Bool, -- ^ @-notree@ noindex :: Bool, -- ^ @-noindex@ nohelp :: Bool, -- ^ @-nohelp@ nonavbar :: Bool, -- ^ @-nonavbar@ serialwarn :: Bool, -- ^ @-serialwarn@ tag :: [(String, String, String)], -- ^ @-tag@ taglet :: Bool, -- ^ @-taglet@ tagletpath :: Bool, -- ^ @-tagletpath@ charset :: Maybe String, -- ^ @-charset@ helpfile :: Maybe FilePath, -- ^ @-helpfile@ linksource :: Bool, -- ^ @-linksource@ sourcetab :: Maybe Int, -- ^ @-sourcetab@ keywords :: Bool, -- ^ @-keywords@ stylesheetfile :: Maybe FilePath, -- ^ @-stylesheetfile@ docencoding :: Maybe String -- ^ @-docencoding@ } -- | A @Javadoc@ with nothing set. javadoc :: Javadoc javadoc = Javadoc Nothing False False False False False Nothing Nothing [] [] [] [] False [] Nothing [] False Nothing Nothing False [] Nothing False False False False False Nothing Nothing Nothing Nothing Nothing Nothing [] [] [] [] False False [] False False False False False False False False [] False False Nothing Nothing False Nothing False Nothing Nothing -- | Construct a @Javadoc@. javadoc' :: Maybe FilePath -> Bool -> Bool -> Bool -> Bool -> Bool -> Maybe String -> Maybe FilePath -> [FilePath] -> [FilePath] -> [String] -> [String] -> Bool -> [FilePath] -> Maybe SourceRelease -> [FilePath] -> Bool -> Maybe String -> Maybe String -> Bool -> [String] -> Maybe FilePath -> Bool -> Bool -> Bool -> Bool -> Bool -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> [String] -> [(String, String)] -> [String] -> [(String, [String])] -> Bool -> Bool -> [String] -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> [(String, String, String)] -> Bool -> Bool -> Maybe String -> Maybe FilePath -> Bool -> Maybe Int -> Bool -> Maybe FilePath -> Maybe String -> Javadoc javadoc' = Javadoc instance Show Javadoc where show (Javadoc overview public protected package private help doclet docletpath sourcepath classpath exclude subpackages breakiterator bootclasspath source extdirs verbose locale encoding quiet flags directory use version author docfilessubdirs splitindex windowtitle doctitle header footer top bottom link linkoffline excludedocfilessubdir group nocomment nodeprecated noqualifier nosince notimestamp nodeprecatedlist notree noindex nohelp nonavbar serialwarn tag taglet tagletpath charset helpfile linksource sourcetab keywords stylesheetfile docencoding) = ["overview" ~~~> overview, "public" ~~ public, "protected" ~~ protected, "package" ~~ package, "private" ~~ private, "help" ~~ help, "doclet" ~~~> doclet, "docletpath" ~~~> docletpath, "sourcepath" ~?? sourcepath, "classpath" ~?? classpath, c exclude, c subpackages, "breakiterator" ~~ breakiterator, "bootclasspath" ~?? bootclasspath, "source" ~~> show $ source, "extdirs" ~?? extdirs, "verbose" ~~ verbose, "locale" ~~~> locale, "encoding" ~~~> encoding, "quiet" ~~ quiet, intercalate " " $ map ("-J" ++) flags, "d" ~~~> directory, "use" ~~ use, "version" ~~ version, "author" ~~ author, "docfilessubdirs" ~~ docfilessubdirs, "splitindex" ~~ splitindex, "windowtitle" ~~~> windowtitle, "doctitle" ~~~> doctitle, "header" ~~~> header, "footer" ~~~> footer, "top" ~~~> top, "bottom" ~~~> bottom, "link" `many` link, manys (\(x, y) -> x ++ "\" \"" ++ y) "linkoffline" linkoffline, intercalate ":" excludedocfilessubdir, manys (\(x, y) -> x ++ "\" \"" ++ c y) "group" group, "nocomment" ~~ nocomment, "nodeprecated" ~~ nodeprecated, intercalate ":" noqualifier, "nosince" ~~ nosince, "notimestamp" ~~ notimestamp, "nodeprecatedlist" ~~ nodeprecatedlist, "notree" ~~ notree, "noindex" ~~ noindex, "nohelp" ~~ nohelp, "nonavbar" ~~ nonavbar, "serialwarn" ~~ serialwarn, manys (\(x, y, z) -> c [x, y, z]) "tag" tag, "taglet" ~~ taglet, "tagletpath" ~~ tagletpath, "charset" ~~~> charset, "helpfile" ~~~> helpfile, "linksource" ~~ linksource, "sourcetab" ~~> show $ sourcetab, "keywords" ~~ keywords, "stylesheetfile" ~~~> stylesheetfile, "docencoding" ~~~> docencoding ] ^^^ " " where c = intercalate ":" instance Compile Javadoc where compile s ps = "javadoc " ++ show s ++ ' ' : space ps instance Output Javadoc where output = directory instance Extension Javadoc where ext _ = "java" instance OutputReference Javadoc where reference p j = j { classpath = p } reference' = classpath