{-# LANGUAGE NoImplicitPrelude          #-}
{-# LANGUAGE ConstraintKinds            #-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE RankNTypes                 #-}

-- | The facility for retrieving all files from the main Stack

-- 'Stack.Types.Package' type. This was moved into its own module to allow

-- component-level file-gathering without circular dependency at the Package

-- level.

module Stack.Types.PackageFile
  ( GetPackageFileContext (..)
  , DotCabalPath (..)
  , DotCabalDescriptor (..)
  , GetPackageFiles (..)
  , PackageWarning (..)
  ) where

import           Distribution.ModuleName ( ModuleName )
import           RIO.Process ( HasProcessContext (processContextL) )
import           Stack.Prelude
import           Stack.Types.Config
                   ( BuildConfig, HasBuildConfig (..), HasConfig (..)
                   , HasEnvConfig, HasGHCVariant, HasPlatform, HasRunner (..)
                   )
import           Stack.Types.NamedComponent ( NamedComponent )

data GetPackageFileContext = GetPackageFileContext
  { GetPackageFileContext -> Path Abs File
ctxFile :: !(Path Abs File)
  , GetPackageFileContext -> Path Abs Dir
ctxDistDir :: !(Path Abs Dir)
  , GetPackageFileContext -> BuildConfig
ctxBuildConfig :: !BuildConfig
  , GetPackageFileContext -> Version
ctxCabalVer :: !Version
  }

instance HasPlatform GetPackageFileContext
instance HasGHCVariant GetPackageFileContext
instance HasLogFunc GetPackageFileContext where
  logFuncL :: Lens' GetPackageFileContext LogFunc
logFuncL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasLogFunc env => Lens' env LogFunc
logFuncL
instance HasRunner GetPackageFileContext where
  runnerL :: Lens' GetPackageFileContext Runner
runnerL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasRunner env => Lens' env Runner
runnerL
instance HasStylesUpdate GetPackageFileContext where
  stylesUpdateL :: Lens' GetPackageFileContext StylesUpdate
stylesUpdateL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasStylesUpdate env => Lens' env StylesUpdate
stylesUpdateL
instance HasTerm GetPackageFileContext where
  useColorL :: Lens' GetPackageFileContext Bool
useColorL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasTerm env => Lens' env Bool
useColorL
  termWidthL :: Lens' GetPackageFileContext Int
termWidthL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasTerm env => Lens' env Int
termWidthL
instance HasConfig GetPackageFileContext
instance HasPantryConfig GetPackageFileContext where
  pantryConfigL :: Lens' GetPackageFileContext PantryConfig
pantryConfigL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasPantryConfig env => Lens' env PantryConfig
pantryConfigL
instance HasProcessContext GetPackageFileContext where
  processContextL :: Lens' GetPackageFileContext ProcessContext
processContextL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasProcessContext env => Lens' env ProcessContext
processContextL
instance HasBuildConfig GetPackageFileContext where
  buildConfigL :: Lens' GetPackageFileContext BuildConfig
buildConfigL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens GetPackageFileContext -> BuildConfig
ctxBuildConfig (\GetPackageFileContext
x BuildConfig
y -> GetPackageFileContext
x { ctxBuildConfig :: BuildConfig
ctxBuildConfig = BuildConfig
y })

-- | A path resolved from the Cabal file, which is either main-is or

-- an exposed/internal/referenced module.

data DotCabalPath
  = DotCabalModulePath !(Path Abs File)
  | DotCabalMainPath !(Path Abs File)
  | DotCabalFilePath !(Path Abs File)
  | DotCabalCFilePath !(Path Abs File)
  deriving (DotCabalPath -> DotCabalPath -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DotCabalPath -> DotCabalPath -> Bool
$c/= :: DotCabalPath -> DotCabalPath -> Bool
== :: DotCabalPath -> DotCabalPath -> Bool
$c== :: DotCabalPath -> DotCabalPath -> Bool
Eq, Eq DotCabalPath
DotCabalPath -> DotCabalPath -> Bool
DotCabalPath -> DotCabalPath -> Ordering
DotCabalPath -> DotCabalPath -> DotCabalPath
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DotCabalPath -> DotCabalPath -> DotCabalPath
$cmin :: DotCabalPath -> DotCabalPath -> DotCabalPath
max :: DotCabalPath -> DotCabalPath -> DotCabalPath
$cmax :: DotCabalPath -> DotCabalPath -> DotCabalPath
>= :: DotCabalPath -> DotCabalPath -> Bool
$c>= :: DotCabalPath -> DotCabalPath -> Bool
> :: DotCabalPath -> DotCabalPath -> Bool
$c> :: DotCabalPath -> DotCabalPath -> Bool
<= :: DotCabalPath -> DotCabalPath -> Bool
$c<= :: DotCabalPath -> DotCabalPath -> Bool
< :: DotCabalPath -> DotCabalPath -> Bool
$c< :: DotCabalPath -> DotCabalPath -> Bool
compare :: DotCabalPath -> DotCabalPath -> Ordering
$ccompare :: DotCabalPath -> DotCabalPath -> Ordering
Ord, Int -> DotCabalPath -> ShowS
[DotCabalPath] -> ShowS
DotCabalPath -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DotCabalPath] -> ShowS
$cshowList :: [DotCabalPath] -> ShowS
show :: DotCabalPath -> String
$cshow :: DotCabalPath -> String
showsPrec :: Int -> DotCabalPath -> ShowS
$cshowsPrec :: Int -> DotCabalPath -> ShowS
Show)

-- | A descriptor from a Cabal file indicating one of the following:

--

-- exposed-modules: Foo

-- other-modules: Foo

-- or

-- main-is: Foo.hs

--

data DotCabalDescriptor
  = DotCabalModule !ModuleName
  | DotCabalMain !FilePath
  | DotCabalFile !FilePath
  | DotCabalCFile !FilePath
  deriving (DotCabalDescriptor -> DotCabalDescriptor -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DotCabalDescriptor -> DotCabalDescriptor -> Bool
$c/= :: DotCabalDescriptor -> DotCabalDescriptor -> Bool
== :: DotCabalDescriptor -> DotCabalDescriptor -> Bool
$c== :: DotCabalDescriptor -> DotCabalDescriptor -> Bool
Eq, Eq DotCabalDescriptor
DotCabalDescriptor -> DotCabalDescriptor -> Bool
DotCabalDescriptor -> DotCabalDescriptor -> Ordering
DotCabalDescriptor -> DotCabalDescriptor -> DotCabalDescriptor
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DotCabalDescriptor -> DotCabalDescriptor -> DotCabalDescriptor
$cmin :: DotCabalDescriptor -> DotCabalDescriptor -> DotCabalDescriptor
max :: DotCabalDescriptor -> DotCabalDescriptor -> DotCabalDescriptor
$cmax :: DotCabalDescriptor -> DotCabalDescriptor -> DotCabalDescriptor
>= :: DotCabalDescriptor -> DotCabalDescriptor -> Bool
$c>= :: DotCabalDescriptor -> DotCabalDescriptor -> Bool
> :: DotCabalDescriptor -> DotCabalDescriptor -> Bool
$c> :: DotCabalDescriptor -> DotCabalDescriptor -> Bool
<= :: DotCabalDescriptor -> DotCabalDescriptor -> Bool
$c<= :: DotCabalDescriptor -> DotCabalDescriptor -> Bool
< :: DotCabalDescriptor -> DotCabalDescriptor -> Bool
$c< :: DotCabalDescriptor -> DotCabalDescriptor -> Bool
compare :: DotCabalDescriptor -> DotCabalDescriptor -> Ordering
$ccompare :: DotCabalDescriptor -> DotCabalDescriptor -> Ordering
Ord, Int -> DotCabalDescriptor -> ShowS
[DotCabalDescriptor] -> ShowS
DotCabalDescriptor -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DotCabalDescriptor] -> ShowS
$cshowList :: [DotCabalDescriptor] -> ShowS
show :: DotCabalDescriptor -> String
$cshow :: DotCabalDescriptor -> String
showsPrec :: Int -> DotCabalDescriptor -> ShowS
$cshowsPrec :: Int -> DotCabalDescriptor -> ShowS
Show)

-- | Files that the package depends on, relative to package directory.

-- Argument is the location of the Cabal file

newtype GetPackageFiles = GetPackageFiles
  { GetPackageFiles
-> forall env.
   HasEnvConfig env =>
   Path Abs File
   -> RIO
        env
        (Map NamedComponent (Map ModuleName (Path Abs File)),
         Map NamedComponent [DotCabalPath], Set (Path Abs File),
         [PackageWarning])
getPackageFiles :: forall env. HasEnvConfig env
                    => Path Abs File
                    -> RIO env
                         ( Map NamedComponent (Map ModuleName (Path Abs File))
                         , Map NamedComponent [DotCabalPath]
                         , Set (Path Abs File)
                         , [PackageWarning]
                         )
  }
instance Show GetPackageFiles where
  show :: GetPackageFiles -> String
show GetPackageFiles
_ = String
"<GetPackageFiles>"

-- | Warning generated when reading a package

data PackageWarning
  = UnlistedModulesWarning NamedComponent [ModuleName]
    -- ^ Modules found that are not listed in Cabal file

  -- TODO: bring this back - see

  -- https://github.com/commercialhaskell/stack/issues/2649

  {-
  | MissingModulesWarning (Path Abs File) (Maybe String) [ModuleName]
    -- ^ Modules not found in file system, which are listed in Cabal file
  -}