module Distribution.Client.Reconfigure ( Check(..), reconfigure ) where

import Distribution.Client.Compat.Prelude

import Data.Monoid ( Any(..) )
import System.Directory ( doesFileExist )

import Distribution.Simple.Configure ( localBuildInfoFile )
import Distribution.Simple.Setup ( Flag, flagToMaybe, toFlag )
import Distribution.Simple.Utils
       ( existsAndIsMoreRecentThan, defaultPackageDesc, info )

import Distribution.Client.Config ( SavedConfig(..) )
import Distribution.Client.Configure ( readConfigFlags )
import Distribution.Client.Nix ( findNixExpr, inNixShell, nixInstantiate )
import Distribution.Client.Sandbox ( findSavedDistPref, updateInstallDirs )
import Distribution.Client.Sandbox.PackageEnvironment
       ( userPackageEnvironmentFile )
import Distribution.Client.Setup
       ( ConfigFlags(..), ConfigExFlags, GlobalFlags(..) )

-- | @Check@ represents a function to check some condition on type @a@. The
-- returned 'Any' is 'True' if any part of the condition failed.
newtype Check a = Check {
  forall a. Check a -> Any -> a -> IO (Any, a)
runCheck :: Any          -- Did any previous check fail?
           -> a            -- value returned by previous checks
           -> IO (Any, a)  -- Did this check fail? What value is returned?
}

instance Semigroup (Check a) where
  <> :: Check a -> Check a -> Check a
(<>) Check a
c Check a
d = forall a. (Any -> a -> IO (Any, a)) -> Check a
Check forall a b. (a -> b) -> a -> b
$ \Any
any0 a
a0 -> do
    (Any
any1, a
a1) <- forall a. Check a -> Any -> a -> IO (Any, a)
runCheck Check a
c Any
any0 a
a0
    (Any
any2, a
a2) <- forall a. Check a -> Any -> a -> IO (Any, a)
runCheck Check a
d (Any
any0 forall a. Semigroup a => a -> a -> a
<> Any
any1) a
a1
    forall (m :: * -> *) a. Monad m => a -> m a
return (Any
any0 forall a. Semigroup a => a -> a -> a
<> Any
any1 forall a. Semigroup a => a -> a -> a
<> Any
any2, a
a2)

instance Monoid (Check a) where
  mempty :: Check a
mempty = forall a. (Any -> a -> IO (Any, a)) -> Check a
Check forall a b. (a -> b) -> a -> b
$ \Any
_ a
a -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. Monoid a => a
mempty, a
a)
  mappend :: Check a -> Check a -> Check a
mappend = forall a. Semigroup a => a -> a -> a
(<>)


-- | Re-configure the package in the current directory if needed. Deciding
-- when to reconfigure and with which options is convoluted:
--
-- If we are reconfiguring, we must always run @configure@ with the
-- verbosity option we are given; however, that a previous configuration
-- uses a different verbosity setting is not reason enough to reconfigure.
--
-- The package should be configured to use the same \"dist\" prefix as
-- given to the @build@ command, otherwise the build will probably
-- fail. Not only does this determine the \"dist\" prefix setting if we
-- need to reconfigure anyway, but an existing configuration should be
-- invalidated if its \"dist\" prefix differs.
--
-- If the package has never been configured (i.e., there is no
-- LocalBuildInfo), we must configure first, using the default options.
--
-- If the package has been configured, there will be a 'LocalBuildInfo'.
-- If there no package description file, we assume that the
-- 'PackageDescription' is up to date, though the configuration may need
-- to be updated for other reasons (see above). If there is a package
-- description file, and it has been modified since the 'LocalBuildInfo'
-- was generated, then we need to reconfigure.
--
-- The caller of this function may also have specific requirements
-- regarding the flags the last configuration used. For example,
-- 'testAction' requires that the package be configured with test suites
-- enabled. The caller may pass the required settings to this function
-- along with a function to check the validity of the saved 'ConfigFlags';
-- these required settings will be checked first upon determining that
-- a previous configuration exists.
reconfigure
  :: ((ConfigFlags, ConfigExFlags) -> [String] -> GlobalFlags -> IO ())
     -- ^ configure action
  -> Verbosity
     -- ^ Verbosity setting
  -> FilePath
     -- ^ \"dist\" prefix
  -> Flag (Maybe Int)
     -- ^ -j flag for reinstalling add-source deps.
  -> Check (ConfigFlags, ConfigExFlags)
     -- ^ Check that the required flags are set.
     -- If they are not set, provide a message explaining the
     -- reason for reconfiguration.
  -> [String]     -- ^ Extra arguments
  -> GlobalFlags  -- ^ Global flags
  -> SavedConfig
  -> IO SavedConfig
reconfigure :: ((ConfigFlags, ConfigExFlags) -> [String] -> GlobalFlags -> IO ())
-> Verbosity
-> String
-> Flag (Maybe Int)
-> Check (ConfigFlags, ConfigExFlags)
-> [String]
-> GlobalFlags
-> SavedConfig
-> IO SavedConfig
reconfigure
  (ConfigFlags, ConfigExFlags) -> [String] -> GlobalFlags -> IO ()
configureAction
  Verbosity
verbosity
  String
dist
  Flag (Maybe Int)
_numJobsFlag
  Check (ConfigFlags, ConfigExFlags)
check
  [String]
extraArgs
  GlobalFlags
globalFlags
  SavedConfig
config
  = do

  savedFlags :: (ConfigFlags, ConfigExFlags)
savedFlags@(ConfigFlags
_, ConfigExFlags
_) <- String -> IO (ConfigFlags, ConfigExFlags)
readConfigFlags String
dist

  Bool
useNix <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Maybe a -> Bool
isJust (GlobalFlags -> SavedConfig -> IO (Maybe String)
findNixExpr GlobalFlags
globalFlags SavedConfig
config)
  Bool
alreadyInNixShell <- IO Bool
inNixShell

  if Bool
useNix Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
alreadyInNixShell
    then do

      -- If we are using Nix, we must reinstantiate the derivation outside
      -- the shell. Eventually, the caller will invoke 'nixShell' which will
      -- rerun cabal inside the shell. That will bring us back to 'reconfigure',
      -- but inside the shell we'll take the second branch, below.

      -- This seems to have a problem: won't 'configureAction' call 'nixShell'
      -- yet again, spawning an infinite tree of subprocesses?
      -- No, because 'nixShell' doesn't spawn a new process if it is already
      -- running in a Nix shell.

      Verbosity -> String -> Bool -> GlobalFlags -> SavedConfig -> IO ()
nixInstantiate Verbosity
verbosity String
dist Bool
False GlobalFlags
globalFlags SavedConfig
config
      forall (m :: * -> *) a. Monad m => a -> m a
return SavedConfig
config

    else do

      let checks :: Check (ConfigFlags, ConfigExFlags)
          checks :: Check (ConfigFlags, ConfigExFlags)
checks =
            forall b. Check (ConfigFlags, b)
checkVerb
            forall a. Semigroup a => a -> a -> a
<> forall b. Check (ConfigFlags, b)
checkDist
            forall a. Semigroup a => a -> a -> a
<> forall b. Check (ConfigFlags, b)
checkOutdated
            forall a. Semigroup a => a -> a -> a
<> Check (ConfigFlags, ConfigExFlags)
check
      (Any Bool
frc, flags :: (ConfigFlags, ConfigExFlags)
flags@(ConfigFlags
configFlags, ConfigExFlags
_)) <- forall a. Check a -> Any -> a -> IO (Any, a)
runCheck Check (ConfigFlags, ConfigExFlags)
checks forall a. Monoid a => a
mempty (ConfigFlags, ConfigExFlags)
savedFlags

      let config' :: SavedConfig
          config' :: SavedConfig
config' = Flag Bool -> SavedConfig -> SavedConfig
updateInstallDirs (ConfigFlags -> Flag Bool
configUserInstall ConfigFlags
configFlags) SavedConfig
config

      forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
frc forall a b. (a -> b) -> a -> b
$ (ConfigFlags, ConfigExFlags) -> [String] -> GlobalFlags -> IO ()
configureAction (ConfigFlags, ConfigExFlags)
flags [String]
extraArgs GlobalFlags
globalFlags
      forall (m :: * -> *) a. Monad m => a -> m a
return SavedConfig
config'

  where

    -- Changing the verbosity does not require reconfiguration, but the new
    -- verbosity should be used if reconfiguring.
    checkVerb :: Check (ConfigFlags, b)
    checkVerb :: forall b. Check (ConfigFlags, b)
checkVerb = forall a. (Any -> a -> IO (Any, a)) -> Check a
Check forall a b. (a -> b) -> a -> b
$ \Any
_ (ConfigFlags
configFlags, b
configExFlags) -> do
      let configFlags' :: ConfigFlags
          configFlags' :: ConfigFlags
configFlags' = ConfigFlags
configFlags { configVerbosity :: Flag Verbosity
configVerbosity = forall a. a -> Flag a
toFlag Verbosity
verbosity}
      forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. Monoid a => a
mempty, (ConfigFlags
configFlags', b
configExFlags))

    -- Reconfiguration is required if @--build-dir@ changes.
    checkDist :: Check (ConfigFlags, b)
    checkDist :: forall b. Check (ConfigFlags, b)
checkDist = forall a. (Any -> a -> IO (Any, a)) -> Check a
Check forall a b. (a -> b) -> a -> b
$ \Any
_ (ConfigFlags
configFlags, b
configExFlags) -> do
      -- Always set the chosen @--build-dir@ before saving the flags,
      -- or bad things could happen.
      String
savedDist <- SavedConfig -> Flag String -> IO String
findSavedDistPref SavedConfig
config (ConfigFlags -> Flag String
configDistPref ConfigFlags
configFlags)
      let distChanged :: Bool
          distChanged :: Bool
distChanged = String
dist forall a. Eq a => a -> a -> Bool
/= String
savedDist
      forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
distChanged forall a b. (a -> b) -> a -> b
$ Verbosity -> String -> IO ()
info Verbosity
verbosity String
"build directory changed"
      let configFlags' :: ConfigFlags
          configFlags' :: ConfigFlags
configFlags' = ConfigFlags
configFlags { configDistPref :: Flag String
configDistPref = forall a. a -> Flag a
toFlag String
dist }
      forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Any
Any Bool
distChanged, (ConfigFlags
configFlags', b
configExFlags))

    checkOutdated :: Check (ConfigFlags, b)
    checkOutdated :: forall b. Check (ConfigFlags, b)
checkOutdated = forall a. (Any -> a -> IO (Any, a)) -> Check a
Check forall a b. (a -> b) -> a -> b
$ \Any
_ flags :: (ConfigFlags, b)
flags@(ConfigFlags
configFlags, b
_) -> do
      let buildConfig :: FilePath
          buildConfig :: String
buildConfig = String -> String
localBuildInfoFile String
dist

      -- Has the package ever been configured? If not, reconfiguration is
      -- required.
      Bool
configured <- String -> IO Bool
doesFileExist String
buildConfig
      forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
configured forall a b. (a -> b) -> a -> b
$ Verbosity -> String -> IO ()
info Verbosity
verbosity String
"package has never been configured"

      -- Is the @cabal.config@ file newer than @dist/setup.config@? Then we need
      -- to force reconfigure. Note that it's possible to use @cabal.config@
      -- even without sandboxes.
      Bool
userPackageEnvironmentFileModified <-
        String -> String -> IO Bool
existsAndIsMoreRecentThan String
userPackageEnvironmentFile String
buildConfig
      forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
userPackageEnvironmentFileModified forall a b. (a -> b) -> a -> b
$
        Verbosity -> String -> IO ()
info Verbosity
verbosity (String
"user package environment file ('"
        forall a. [a] -> [a] -> [a]
++ String
userPackageEnvironmentFile forall a. [a] -> [a] -> [a]
++ String
"') was modified")

      -- Is the configuration older than the package description?
      String
descrFile <- forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Verbosity -> IO String
defaultPackageDesc Verbosity
verbosity) forall (m :: * -> *) a. Monad m => a -> m a
return
                   (forall a. Flag a -> Maybe a
flagToMaybe (ConfigFlags -> Flag String
configCabalFilePath ConfigFlags
configFlags))
      Bool
outdated <- String -> String -> IO Bool
existsAndIsMoreRecentThan String
descrFile String
buildConfig
      forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
outdated forall a b. (a -> b) -> a -> b
$ Verbosity -> String -> IO ()
info Verbosity
verbosity (String
descrFile forall a. [a] -> [a] -> [a]
++ String
" was changed")

      let failed :: Any
          failed :: Any
failed =
            Bool -> Any
Any Bool
outdated
            forall a. Semigroup a => a -> a -> a
<> Bool -> Any
Any Bool
userPackageEnvironmentFileModified
            forall a. Semigroup a => a -> a -> a
<> Bool -> Any
Any (Bool -> Bool
not Bool
configured)
      forall (m :: * -> *) a. Monad m => a -> m a
return (Any
failed, (ConfigFlags, b)
flags)