module HaskellCI.Tools (
doctestJobVersionRange,
doctestArgs,
hlintJobVersionRange,
hlintArgs,
) where
import HaskellCI.Prelude
import qualified Data.Set as S
import qualified Distribution.PackageDescription as C
import qualified Distribution.PackageDescription.Configuration as C
import qualified Distribution.Pretty as C
import qualified Distribution.Types.VersionRange as C
import qualified Distribution.Version as C
import qualified Distribution.Types.BuildInfo.Lens as L
import qualified Distribution.Types.PackageDescription.Lens as L
import HaskellCI.Compiler
import HaskellCI.Config.HLint
doctestJobVersionRange :: CompilerRange
doctestJobVersionRange = RangeGHC /\ Range (C.orLaterVersion $ C.mkVersion [8,0])
doctestArgs :: C.GenericPackageDescription -> [[String]]
doctestArgs gpd = nub $
[ libraryModuleArgs c
| c <- toListOf (L.library . traverse) (C.flattenPackageDescription gpd)
] ++
[ libraryModuleArgs c
| c <- toListOf (L.subLibraries . traverse) (C.flattenPackageDescription gpd)
]
libraryModuleArgs :: C.Library -> [String]
libraryModuleArgs l
| null dirsOrMods = []
| otherwise = exts ++ dirsOrMods
where
bi = l ^. L.buildInfo
dirsOrMods
| null (C.hsSourceDirs bi) = map C.prettyShow (C.exposedModules l)
| otherwise = C.hsSourceDirs bi
exts = map (("-X" ++) . C.prettyShow) (C.defaultExtensions bi)
executableModuleArgs :: C.Executable -> [String]
executableModuleArgs e
| null dirsOrMods = []
| otherwise = exts ++ dirsOrMods
where
bi = e ^. L.buildInfo
dirsOrMods
| null (C.hsSourceDirs bi) = map C.prettyShow (C.otherModules bi)
| otherwise = C.hsSourceDirs bi
exts = map (("-X" ++) . C.prettyShow) (C.defaultExtensions bi)
hlintJobVersionRange
:: Set CompilerVersion
-> VersionRange
-> HLintJob
-> CompilerRange
hlintJobVersionRange vs headHackage HLintJobLatest = case S.maxView vs' of
Just (v, _) -> RangePoints (S.singleton (GHC v))
_ -> RangePoints S.empty
where
vs' = S.fromList
$ filter (\v -> not $ C.withinRange v headHackage)
$ mapMaybe (maybeGHC Nothing Just)
$ S.toList vs
hlintJobVersionRange _ _ (HLintJob v) = RangePoints (S.singleton (GHC v))
hlintArgs :: C.GenericPackageDescription -> [[String]]
hlintArgs gpd = nub $
[ libraryModuleArgs c
| c <- toListOf (L.library . traverse) (C.flattenPackageDescription gpd)
] ++
[ libraryModuleArgs c
| c <- toListOf (L.subLibraries . traverse) (C.flattenPackageDescription gpd)
] ++
[ executableModuleArgs c
| c <- toListOf (L.executables . traverse) (C.flattenPackageDescription gpd)
]