module Distribution.Simple (
        module Distribution.Package,
        module Distribution.Version,
        module Distribution.License,
        module Distribution.Simple.Compiler,
        module Language.Haskell.Extension,
        
        defaultMain, defaultMainNoRead, defaultMainArgs,
        
        UserHooks(..), Args,
        defaultMainWithHooks, defaultMainWithHooksArgs,
        
        simpleUserHooks,
        autoconfUserHooks,
        defaultUserHooks, emptyUserHooks,
        
        defaultHookedPackageDesc
  ) where
import Distribution.Simple.Compiler hiding (Flag)
import Distribution.Simple.UserHooks
import Distribution.Package 
import Distribution.PackageDescription
         ( PackageDescription(..), GenericPackageDescription
         , updatePackageDescription, hasLibs
         , HookedBuildInfo, emptyHookedBuildInfo )
import Distribution.PackageDescription.Parse
         ( readPackageDescription, readHookedBuildInfo )
import Distribution.PackageDescription.Configuration
         ( flattenPackageDescription )
import Distribution.Simple.Program
         ( defaultProgramConfiguration, addKnownPrograms, builtinPrograms
         , restoreProgramConfiguration, reconfigurePrograms )
import Distribution.Simple.PreProcess (knownSuffixHandlers, PPSuffixHandler)
import Distribution.Simple.Setup
import Distribution.Simple.Command
import Distribution.Simple.Build        ( build, makefile )
import Distribution.Simple.SrcDist      ( sdist )
import Distribution.Simple.Register     ( register, unregister,
                                          writeInstalledConfig,
                                          removeRegScripts
                                        )
import Distribution.Simple.Configure
         ( getPersistBuildConfig, maybeGetPersistBuildConfig
         , writePersistBuildConfig, checkPersistBuildConfig
         , configure, checkForeignDeps )
import Distribution.Simple.LocalBuildInfo ( LocalBuildInfo(..) )
import Distribution.Simple.BuildPaths ( srcPref)
import Distribution.Simple.Install (install)
import Distribution.Simple.Haddock (haddock, hscolour)
import Distribution.Simple.Utils
         (die, notice, info, warn, setupMessage, chattyTry,
          defaultPackageDesc, defaultHookedPackageDesc,
          rawSystemExit, cabalVersion )
import Distribution.Verbosity
import Language.Haskell.Extension
import Distribution.Version
import Distribution.License
import Distribution.Text
         ( display )
import System.Environment(getArgs,getProgName)
import System.Directory(removeFile, doesFileExist,
                        doesDirectoryExist, removeDirectoryRecursive)
import System.Exit
import Control.Monad   (when)
import Data.List       (intersperse, unionBy)
defaultMain :: IO ()
defaultMain = getArgs >>= defaultMainHelper simpleUserHooks
defaultMainArgs :: [String] -> IO ()
defaultMainArgs = defaultMainHelper simpleUserHooks
defaultMainWithHooks :: UserHooks -> IO ()
defaultMainWithHooks hooks = getArgs >>= defaultMainHelper hooks
defaultMainWithHooksArgs :: UserHooks -> [String] -> IO ()
defaultMainWithHooksArgs = defaultMainHelper
defaultMainNoRead :: PackageDescription -> IO ()
defaultMainNoRead pkg_descr =
  getArgs >>=
  defaultMainHelper simpleUserHooks { readDesc = return (Just pkg_descr) }
defaultMainHelper :: UserHooks -> Args -> IO ()
defaultMainHelper hooks args =
  case commandsRun globalCommand commands args of
    CommandHelp   help                 -> printHelp help
    CommandList   opts                 -> printOptionsList opts
    CommandErrors errs                 -> printErrors errs
    CommandReadyToGo (flags, commandParse)  ->
      case commandParse of
        _ | fromFlag (globalVersion flags)        -> printVersion
          | fromFlag (globalNumericVersion flags) -> printNumericVersion
        CommandHelp     help           -> printHelp help
        CommandList     opts           -> printOptionsList opts
        CommandErrors   errs           -> printErrors errs
        CommandReadyToGo action        -> action
  where
    printHelp help = getProgName >>= putStr . help
    printOptionsList = putStr . unlines
    printErrors errs = do
      putStr (concat (intersperse "\n" errs))
      exitWith (ExitFailure 1)
    printNumericVersion = putStrLn $ display cabalVersion
    printVersion        = putStrLn $ "Cabal library version "
                                  ++ display cabalVersion
    progs = addKnownPrograms (hookedPrograms hooks) defaultProgramConfiguration
    commands =
      [configureCommand progs `commandAddAction` configureAction    hooks
      ,buildCommand     progs `commandAddAction` buildAction        hooks
      ,installCommand         `commandAddAction` installAction      hooks
      ,copyCommand            `commandAddAction` copyAction         hooks
      ,haddockCommand         `commandAddAction` haddockAction      hooks
      ,cleanCommand           `commandAddAction` cleanAction        hooks
      ,sdistCommand           `commandAddAction` sdistAction        hooks
      ,hscolourCommand        `commandAddAction` hscolourAction     hooks
      ,registerCommand        `commandAddAction` registerAction     hooks
      ,unregisterCommand      `commandAddAction` unregisterAction   hooks
      ,testCommand            `commandAddAction` testAction         hooks
      ,makefileCommand        `commandAddAction` makefileAction     hooks
      ]
allSuffixHandlers :: UserHooks
                  -> [PPSuffixHandler]
allSuffixHandlers hooks
    = overridesPP (hookedPreProcessors hooks) knownSuffixHandlers
    where
      overridesPP :: [PPSuffixHandler] -> [PPSuffixHandler] -> [PPSuffixHandler]
      overridesPP = unionBy (\x y -> fst x == fst y)
configureAction :: UserHooks -> ConfigFlags -> Args -> IO ()
configureAction hooks flags args = do
                let distPref = fromFlag $ configDistPref flags
                pbi <- preConf hooks args flags
                (mb_pd_file, pkg_descr0) <- confPkgDescr
                
                
                let epkg_descr = (pkg_descr0, pbi)
                
                
                localbuildinfo0 <- confHook hooks epkg_descr flags
                
                let localbuildinfo = localbuildinfo0{ pkgDescrFile = mb_pd_file }
                writePersistBuildConfig distPref localbuildinfo
                let pkg_descr = localPkgDescr localbuildinfo
                postConf hooks args flags pkg_descr localbuildinfo
              where
                verbosity = fromFlag (configVerbosity flags)
                confPkgDescr :: IO (Maybe FilePath,
                                    Either GenericPackageDescription
                                           PackageDescription)
                confPkgDescr = do
                  mdescr <- readDesc hooks
                  case mdescr of
                    Just descr -> return (Nothing, Right descr)
                    Nothing -> do
                      pdfile <- defaultPackageDesc verbosity
                      ppd <- readPackageDescription verbosity pdfile
                      return (Just pdfile, Left ppd)
buildAction :: UserHooks -> BuildFlags -> Args -> IO ()
buildAction hooks flags args = do
  let distPref  = fromFlag $ buildDistPref flags
      verbosity = fromFlag $ buildVerbosity flags
  lbi <- getBuildConfig hooks distPref
  progs <- reconfigurePrograms verbosity
             (buildProgramPaths flags)
             (buildProgramArgs flags)
             (withPrograms lbi)
  hookedAction preBuild buildHook postBuild
               (return lbi { withPrograms = progs })
               hooks flags args
makefileAction :: UserHooks -> MakefileFlags -> Args -> IO ()
makefileAction hooks flags args
    = do let distPref = fromFlag $ makefileDistPref flags
         hookedAction preMakefile makefileHook postMakefile
                      (getBuildConfig hooks distPref)
                      hooks flags args
hscolourAction :: UserHooks -> HscolourFlags -> Args -> IO ()
hscolourAction hooks flags args
    = do let distPref = fromFlag $ hscolourDistPref flags
         hookedAction preHscolour hscolourHook postHscolour
                      (getBuildConfig hooks distPref)
                      hooks flags args
haddockAction :: UserHooks -> HaddockFlags -> Args -> IO ()
haddockAction hooks flags args = do
  let distPref  = fromFlag $ haddockDistPref flags
      verbosity = fromFlag $ haddockVerbosity flags
  lbi <- getBuildConfig hooks distPref
  progs <- reconfigurePrograms verbosity
             (haddockProgramPaths flags)
             (haddockProgramArgs flags)
             (withPrograms lbi)
  hookedAction preHaddock haddockHook postHaddock
               (return lbi { withPrograms = progs })
               hooks flags args
cleanAction :: UserHooks -> CleanFlags -> Args -> IO ()
cleanAction hooks flags args = do
                let distPref = fromFlag $ cleanDistPref flags
                pbi <- preClean hooks args flags
                mlbi <- maybeGetPersistBuildConfig distPref
                pdfile <- defaultPackageDesc verbosity
                ppd <- readPackageDescription verbosity pdfile
                let pkg_descr0 = flattenPackageDescription ppd
                let pkg_descr = updatePackageDescription pbi pkg_descr0
                cleanHook hooks pkg_descr mlbi hooks flags
                postClean hooks args flags pkg_descr mlbi
  where verbosity = fromFlag (cleanVerbosity flags)
copyAction :: UserHooks -> CopyFlags -> Args -> IO ()
copyAction hooks flags args
    = do let distPref = fromFlag $ copyDistPref flags
         hookedAction preCopy copyHook postCopy
                      (getBuildConfig hooks distPref)
                      hooks flags args
installAction :: UserHooks -> InstallFlags -> Args -> IO ()
installAction hooks flags args
    = do let distPref = fromFlag $ installDistPref flags
         hookedAction preInst instHook postInst
                      (getBuildConfig hooks distPref)
                      hooks flags args
sdistAction :: UserHooks -> SDistFlags -> Args -> IO ()
sdistAction hooks flags args = do
                let distPref = fromFlag $ sDistDistPref flags
                pbi <- preSDist hooks args flags
                mlbi <- maybeGetPersistBuildConfig distPref
                pdfile <- defaultPackageDesc verbosity
                ppd <- readPackageDescription verbosity pdfile
                let pkg_descr0 = flattenPackageDescription ppd
                let pkg_descr = updatePackageDescription pbi pkg_descr0
                sDistHook hooks pkg_descr mlbi hooks flags
                postSDist hooks args flags pkg_descr mlbi
  where verbosity = fromFlag (sDistVerbosity flags)
testAction :: UserHooks -> TestFlags -> Args -> IO ()
testAction hooks flags args = do
                let distPref = fromFlag $ testDistPref flags
                localbuildinfo <- getBuildConfig hooks distPref
                let pkg_descr = localPkgDescr localbuildinfo
                runTests hooks args False pkg_descr localbuildinfo
registerAction :: UserHooks -> RegisterFlags -> Args -> IO ()
registerAction hooks flags args
    = do let distPref = fromFlag $ regDistPref flags
         hookedAction preReg regHook postReg
                      (getBuildConfig hooks distPref)
                      hooks flags args
unregisterAction :: UserHooks -> RegisterFlags -> Args -> IO ()
unregisterAction hooks flags args
    = do let distPref = fromFlag $ regDistPref flags
         hookedAction preUnreg unregHook postUnreg
                      (getBuildConfig hooks distPref)
                      hooks flags args
hookedAction :: (UserHooks -> Args -> flags -> IO HookedBuildInfo)
        -> (UserHooks -> PackageDescription -> LocalBuildInfo
                      -> UserHooks -> flags -> IO ())
        -> (UserHooks -> Args -> flags -> PackageDescription
                      -> LocalBuildInfo -> IO ())
        -> IO LocalBuildInfo
        -> UserHooks -> flags -> Args -> IO ()
hookedAction pre_hook cmd_hook post_hook get_build_config hooks flags args = do
   pbi <- pre_hook hooks args flags
   localbuildinfo <- get_build_config
   let pkg_descr0 = localPkgDescr localbuildinfo
   
   let pkg_descr = updatePackageDescription pbi pkg_descr0
   
   
   cmd_hook hooks pkg_descr localbuildinfo hooks flags
   post_hook hooks args flags pkg_descr localbuildinfo
getBuildConfig :: UserHooks -> FilePath -> IO LocalBuildInfo
getBuildConfig hooks distPref = do
  lbi <- getPersistBuildConfig distPref
  case pkgDescrFile lbi of
    Nothing -> return ()
    Just pkg_descr_file -> checkPersistBuildConfig distPref pkg_descr_file
  return lbi {
    withPrograms = restoreProgramConfiguration
                     (builtinPrograms ++ hookedPrograms hooks)
                     (withPrograms lbi)
  }
clean :: PackageDescription -> CleanFlags -> IO ()
clean pkg_descr flags = do
    let distPref = fromFlag $ cleanDistPref flags
    notice verbosity "cleaning..."
    maybeConfig <- if fromFlag (cleanSaveConf flags)
                     then maybeGetPersistBuildConfig distPref
                     else return Nothing
    
    
    chattyTry "removing dist/" $ do
      exists <- doesDirectoryExist distPref
      when exists (removeDirectoryRecursive distPref)
    
    removeRegScripts
    
    mapM_ removeFileOrDirectory (extraTmpFiles pkg_descr)
    
    maybe (return ()) (writePersistBuildConfig distPref) maybeConfig
  where
        removeFileOrDirectory :: FilePath -> IO ()
        removeFileOrDirectory fname = do
            isDir <- doesDirectoryExist fname
            isFile <- doesFileExist fname
            if isDir then removeDirectoryRecursive fname
              else if isFile then removeFile fname
              else return ()
        verbosity = fromFlag (cleanVerbosity flags)
simpleUserHooks :: UserHooks
simpleUserHooks =
    emptyUserHooks {
       confHook  = configure,
       postConf  = finalChecks,
       buildHook = defaultBuildHook,
       makefileHook = defaultMakefileHook,
       copyHook  = \desc lbi _ f -> install desc lbi f, 
       instHook  = defaultInstallHook,
       sDistHook = \p l h f -> sdist p l f srcPref (allSuffixHandlers h),
       cleanHook = \p _ _ f -> clean p f,
       hscolourHook = \p l h f -> hscolour p l (allSuffixHandlers h) f,
       haddockHook  = \p l h f -> haddock  p l (allSuffixHandlers h) f,
       regHook   = defaultRegHook,
       unregHook = \p l _ f -> unregister p l f
      }
  where
    finalChecks _args flags pkg_descr lbi =
      checkForeignDeps pkg_descr lbi verbosity
      where
        verbosity = fromFlag (configVerbosity flags)
defaultUserHooks :: UserHooks
defaultUserHooks = autoconfUserHooks {
          confHook = \pkg flags -> do
                       let verbosity = fromFlag (configVerbosity flags)
                       warn verbosity $
                         "defaultUserHooks in Setup script is deprecated."
                       confHook autoconfUserHooks pkg flags,
          postConf = oldCompatPostConf
    }
    
    
    
    where oldCompatPostConf args flags pkg_descr lbi
              = do let verbosity = fromFlag (configVerbosity flags)
                   noExtraFlags args
                   confExists <- doesFileExist "configure"
                   when confExists $
                       rawSystemExit verbosity "sh" $
                       "configure" : configureArgs backwardsCompatHack flags
                   pbi <- getHookedBuildInfo verbosity
                   let pkg_descr' = updatePackageDescription pbi pkg_descr
                   postConf simpleUserHooks args flags pkg_descr' lbi
          backwardsCompatHack = True
autoconfUserHooks :: UserHooks
autoconfUserHooks
    = simpleUserHooks
      {
       postConf    = defaultPostConf,
       preBuild    = readHook buildVerbosity,
       preMakefile = readHook makefileVerbosity,
       preClean    = readHook cleanVerbosity,
       preCopy     = readHook copyVerbosity,
       preInst     = readHook installVerbosity,
       preHscolour = readHook hscolourVerbosity,
       preHaddock  = readHook haddockVerbosity,
       preReg      = readHook regVerbosity,
       preUnreg    = readHook regVerbosity
      }
    where defaultPostConf :: Args -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ()
          defaultPostConf args flags pkg_descr lbi
              = do let verbosity = fromFlag (configVerbosity flags)
                   noExtraFlags args
                   confExists <- doesFileExist "configure"
                   if confExists
                     then rawSystemExit verbosity "sh" $
                            "configure"
                          : configureArgs backwardsCompatHack flags
                     else die "configure script not found."
                   pbi <- getHookedBuildInfo verbosity
                   let pkg_descr' = updatePackageDescription pbi pkg_descr
                   postConf simpleUserHooks args flags pkg_descr' lbi
          backwardsCompatHack = False
          readHook :: (a -> Flag Verbosity) -> Args -> a -> IO HookedBuildInfo
          readHook get_verbosity a flags = do
              noExtraFlags a
              getHookedBuildInfo verbosity
            where
              verbosity = fromFlag (get_verbosity flags)
getHookedBuildInfo :: Verbosity -> IO HookedBuildInfo
getHookedBuildInfo verbosity = do
  maybe_infoFile <- defaultHookedPackageDesc
  case maybe_infoFile of
    Nothing       -> return emptyHookedBuildInfo
    Just infoFile -> do
      info verbosity $ "Reading parameters from " ++ infoFile
      readHookedBuildInfo verbosity infoFile
defaultInstallHook :: PackageDescription -> LocalBuildInfo
                   -> UserHooks -> InstallFlags -> IO ()
defaultInstallHook pkg_descr localbuildinfo _ flags = do
  let copyFlags = defaultCopyFlags {
                      copyDistPref   = installDistPref flags,
                      copyInPlace    = installInPlace flags,
                      copyUseWrapper = installUseWrapper flags,
                      copyDest       = toFlag NoCopyDest,
                      copyVerbosity  = installVerbosity flags
                  }
  install pkg_descr localbuildinfo copyFlags
  let registerFlags = defaultRegisterFlags {
                          regDistPref  = installDistPref flags,
                          regInPlace   = installInPlace flags,
                          regPackageDB = installPackageDB flags,
                          regVerbosity = installVerbosity flags
                      }
  when (hasLibs pkg_descr) $ register pkg_descr localbuildinfo registerFlags
defaultBuildHook :: PackageDescription -> LocalBuildInfo
        -> UserHooks -> BuildFlags -> IO ()
defaultBuildHook pkg_descr localbuildinfo hooks flags = do
  let distPref = fromFlag $ buildDistPref flags
  build pkg_descr localbuildinfo flags (allSuffixHandlers hooks)
  when (hasLibs pkg_descr) $
      writeInstalledConfig distPref pkg_descr localbuildinfo False Nothing
defaultMakefileHook :: PackageDescription -> LocalBuildInfo
        -> UserHooks -> MakefileFlags -> IO ()
defaultMakefileHook pkg_descr localbuildinfo hooks flags = do
  let distPref = fromFlag $ makefileDistPref flags
  makefile pkg_descr localbuildinfo flags (allSuffixHandlers hooks)
  when (hasLibs pkg_descr) $
      writeInstalledConfig distPref pkg_descr localbuildinfo False Nothing
defaultRegHook :: PackageDescription -> LocalBuildInfo
        -> UserHooks -> RegisterFlags -> IO ()
defaultRegHook pkg_descr localbuildinfo _ flags =
    if hasLibs pkg_descr
    then register pkg_descr localbuildinfo flags
    else setupMessage verbosity
           "Package contains no library to register:" (packageId pkg_descr)
  where verbosity = fromFlag (regVerbosity flags)