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.Utils.Path                       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 :: CompilerRange
doctestJobVersionRange = CompilerRange
RangeGHC forall a. Lattice a => a -> a -> a
/\ VersionRange -> CompilerRange
Range (Version -> VersionRange
C.orLaterVersion forall a b. (a -> b) -> a -> b
$ [Int] -> Version
C.mkVersion [Int
8,Int
0])
doctestArgs :: C.GenericPackageDescription -> [[String]]
doctestArgs :: GenericPackageDescription -> [[String]]
doctestArgs GenericPackageDescription
gpd = forall a. Eq a => [a] -> [a]
nub forall a b. (a -> b) -> a -> b
$
    [ Library -> [String]
libraryModuleArgs Library
c
    | Library
c <- forall a s. Getting (DList a) s a -> s -> [a]
toListOf (Lens' PackageDescription (Maybe Library)
L.library forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse) (GenericPackageDescription -> PackageDescription
C.flattenPackageDescription GenericPackageDescription
gpd)
    ] forall a. [a] -> [a] -> [a]
++
    [ Library -> [String]
libraryModuleArgs Library
c
    | Library
c <- forall a s. Getting (DList a) s a -> s -> [a]
toListOf (Lens' PackageDescription [Library]
L.subLibraries forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse) (GenericPackageDescription -> PackageDescription
C.flattenPackageDescription GenericPackageDescription
gpd)
    ]
libraryModuleArgs :: C.Library -> [String]
libraryModuleArgs :: Library -> [String]
libraryModuleArgs Library
l
    | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
dirsOrMods = []
    | Bool
otherwise       = [String]
lang forall a. [a] -> [a] -> [a]
++ [String]
exts forall a. [a] -> [a] -> [a]
++ [String]
dirsOrMods
  where
    bi :: BuildInfo
bi = Library
l forall s a. s -> Getting a s a -> a
^. forall a. HasBuildInfo a => Lens' a BuildInfo
L.buildInfo
    dirsOrMods :: [String]
dirsOrMods
        | forall (t :: * -> *) a. Foldable t => t a -> Bool
null (BuildInfo -> [SymbolicPath PackageDir SourceDir]
C.hsSourceDirs BuildInfo
bi) = forall a b. (a -> b) -> [a] -> [b]
map forall a. Pretty a => a -> String
C.prettyShow (Library -> [ModuleName]
C.exposedModules Library
l)
        | Bool
otherwise                = forall a b. (a -> b) -> [a] -> [b]
map forall from to. SymbolicPath from to -> String
C.getSymbolicPath forall a b. (a -> b) -> a -> b
$ BuildInfo -> [SymbolicPath PackageDir SourceDir]
C.hsSourceDirs BuildInfo
bi
    lang :: [String]
lang = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
"-X" forall a. [a] -> [a] -> [a]
++) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Pretty a => a -> String
C.prettyShow) (BuildInfo -> Maybe Language
C.defaultLanguage BuildInfo
bi)
    exts :: [String]
exts = forall a b. (a -> b) -> [a] -> [b]
map ((String
"-X" forall a. [a] -> [a] -> [a]
++) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Pretty a => a -> String
C.prettyShow) (BuildInfo -> [Extension]
C.defaultExtensions BuildInfo
bi)
executableModuleArgs :: C.Executable -> [String]
executableModuleArgs :: Executable -> [String]
executableModuleArgs Executable
e
    | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
dirsOrMods = []
    | Bool
otherwise       = [String]
lang forall a. [a] -> [a] -> [a]
++ [String]
exts forall a. [a] -> [a] -> [a]
++ [String]
dirsOrMods
  where
    bi :: BuildInfo
bi = Executable
e forall s a. s -> Getting a s a -> a
^. forall a. HasBuildInfo a => Lens' a BuildInfo
L.buildInfo
    dirsOrMods :: [String]
dirsOrMods
        
        | forall (t :: * -> *) a. Foldable t => t a -> Bool
null (BuildInfo -> [SymbolicPath PackageDir SourceDir]
C.hsSourceDirs BuildInfo
bi) = forall a b. (a -> b) -> [a] -> [b]
map forall a. Pretty a => a -> String
C.prettyShow (BuildInfo -> [ModuleName]
C.otherModules BuildInfo
bi)
        | Bool
otherwise                = forall a b. (a -> b) -> [a] -> [b]
map forall from to. SymbolicPath from to -> String
C.getSymbolicPath forall a b. (a -> b) -> a -> b
$ BuildInfo -> [SymbolicPath PackageDir SourceDir]
C.hsSourceDirs BuildInfo
bi
    lang :: [String]
lang = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
"-X" forall a. [a] -> [a] -> [a]
++) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Pretty a => a -> String
C.prettyShow) (BuildInfo -> Maybe Language
C.defaultLanguage BuildInfo
bi)
    exts :: [String]
exts = forall a b. (a -> b) -> [a] -> [b]
map ((String
"-X" forall a. [a] -> [a] -> [a]
++) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Pretty a => a -> String
C.prettyShow) (BuildInfo -> [Extension]
C.defaultExtensions BuildInfo
bi)
hlintJobVersionRange
    :: Set CompilerVersion  
    -> VersionRange         
    -> HLintJob             
    -> CompilerRange
hlintJobVersionRange :: Set CompilerVersion -> VersionRange -> HLintJob -> CompilerRange
hlintJobVersionRange Set CompilerVersion
vs VersionRange
headHackage HLintJob
HLintJobLatest = case forall a. Set a -> Maybe (a, Set a)
S.maxView Set Version
vs' of
    Just (Version
v, Set Version
_) -> Set CompilerVersion -> CompilerRange
RangePoints (forall a. a -> Set a
S.singleton (Version -> CompilerVersion
GHC Version
v))
    Maybe (Version, Set Version)
_           -> Set CompilerVersion -> CompilerRange
RangePoints forall a. Set a
S.empty
  where
    
    vs' :: Set Version
vs' = forall a. Ord a => [a] -> Set a
S.fromList
        forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (\Version
v -> Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ Version -> VersionRange -> Bool
C.withinRange Version
v VersionRange
headHackage)
        forall a b. (a -> b) -> a -> b
$ forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (forall a. a -> (Version -> a) -> CompilerVersion -> a
maybeGHC forall a. Maybe a
Nothing forall a. a -> Maybe a
Just)
        forall a b. (a -> b) -> a -> b
$ forall a. Set a -> [a]
S.toList Set CompilerVersion
vs
hlintJobVersionRange Set CompilerVersion
_ VersionRange
_ (HLintJob Version
v)   = Set CompilerVersion -> CompilerRange
RangePoints (forall a. a -> Set a
S.singleton (Version -> CompilerVersion
GHC Version
v))
hlintArgs :: C.GenericPackageDescription -> [[String]]
hlintArgs :: GenericPackageDescription -> [[String]]
hlintArgs GenericPackageDescription
gpd = forall a. Eq a => [a] -> [a]
nub forall a b. (a -> b) -> a -> b
$
    [ Library -> [String]
libraryModuleArgs Library
c
    | Library
c <- forall a s. Getting (DList a) s a -> s -> [a]
toListOf (Lens' PackageDescription (Maybe Library)
L.library forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse) (GenericPackageDescription -> PackageDescription
C.flattenPackageDescription GenericPackageDescription
gpd)
    ] forall a. [a] -> [a] -> [a]
++
    [ Library -> [String]
libraryModuleArgs Library
c
    | Library
c <- forall a s. Getting (DList a) s a -> s -> [a]
toListOf (Lens' PackageDescription [Library]
L.subLibraries forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse) (GenericPackageDescription -> PackageDescription
C.flattenPackageDescription GenericPackageDescription
gpd)
    ] forall a. [a] -> [a] -> [a]
++
    [ Executable -> [String]
executableModuleArgs Executable
c
    | Executable
c <- forall a s. Getting (DList a) s a -> s -> [a]
toListOf (Lens' PackageDescription [Executable]
L.executables forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse) (GenericPackageDescription -> PackageDescription
C.flattenPackageDescription GenericPackageDescription
gpd)
    ]