module Distribution.Simple.SrcDist (
  
  sdist,
  
  printPackageProblems,
  prepareTree,
  createArchive,
  
  prepareSnapshotTree,
  snapshotPackage,
  snapshotVersion,
  dateToSnapshotNumber,
  
  listPackageSources
  )  where
import Distribution.PackageDescription
         ( PackageDescription(..), BuildInfo(..), Executable(..), Library(..)
         , TestSuite(..), TestSuiteInterface(..), Benchmark(..)
         , BenchmarkInterface(..) )
import Distribution.PackageDescription.Check
         ( PackageCheck(..), checkConfiguredPackage, checkPackageFiles )
import Distribution.Package
         ( PackageIdentifier(pkgVersion), Package(..), packageVersion )
import Distribution.ModuleName (ModuleName)
import qualified Distribution.ModuleName as ModuleName
import Distribution.Version
         ( Version(versionBranch) )
import Distribution.Simple.Utils
         ( createDirectoryIfMissingVerbose, withUTF8FileContents, writeUTF8File
         , installOrdinaryFiles, installMaybeExecutableFiles
         , findFile, findFileWithExtension, matchFileGlob
         , withTempDirectory, defaultPackageDesc
         , die, warn, notice, setupMessage )
import Distribution.Simple.Setup ( Flag(..), SDistFlags(..)
                                 , fromFlag, flagToMaybe)
import Distribution.Simple.PreProcess ( PPSuffixHandler, ppSuffixes
                                      , preprocessComponent )
import Distribution.Simple.LocalBuildInfo
         ( LocalBuildInfo(..), withAllComponentsInBuildOrder )
import Distribution.Simple.BuildPaths ( autogenModuleName )
import Distribution.Simple.Program ( defaultProgramConfiguration, requireProgram,
                              rawSystemProgram, tarProgram )
import Distribution.Text
         ( display )
import Control.Monad(when, unless, forM)
import Data.Char (toLower)
import Data.List (partition, isPrefixOf)
import Data.Maybe (isNothing, catMaybes)
import Data.Time (UTCTime, getCurrentTime, toGregorian, utctDay)
import System.Directory ( doesFileExist )
import System.IO (IOMode(WriteMode), hPutStrLn, withFile)
import Distribution.Verbosity (Verbosity)
import System.FilePath
         ( (</>), (<.>), dropExtension, isAbsolute )
sdist :: PackageDescription     
      -> Maybe LocalBuildInfo   
      -> SDistFlags             
      -> (FilePath -> FilePath) 
      -> [PPSuffixHandler]      
      -> IO ()
sdist pkg mb_lbi flags mkTmpDir pps =
  
  case (sDistListSources flags) of
    Flag path -> withFile path WriteMode $ \outHandle -> do
      (ordinary, maybeExecutable) <- listPackageSources verbosity pkg pps
      mapM_ (hPutStrLn outHandle) ordinary
      mapM_ (hPutStrLn outHandle) maybeExecutable
      notice verbosity $ "List of package sources written to file '"
                         ++ path ++ "'"
    NoFlag    -> do
      
      printPackageProblems verbosity pkg
      when (isNothing mb_lbi) $
        warn verbosity "Cannot run preprocessors. Run 'configure' command first."
      date <- getCurrentTime
      let pkg' | snapshot  = snapshotPackage date pkg
               | otherwise = pkg
      case flagToMaybe (sDistDirectory flags) of
        Just targetDir -> do
          generateSourceDir targetDir pkg'
          notice verbosity $ "Source directory created: " ++ targetDir
        Nothing -> do
          createDirectoryIfMissingVerbose verbosity True tmpTargetDir
          withTempDirectory verbosity tmpTargetDir "sdist." $ \tmpDir -> do
            let targetDir = tmpDir </> tarBallName pkg'
            generateSourceDir targetDir pkg'
            targzFile <- createArchive verbosity pkg' mb_lbi tmpDir targetPref
            notice verbosity $ "Source tarball created: " ++ targzFile
  where
    generateSourceDir targetDir pkg' = do
      setupMessage verbosity "Building source dist for" (packageId pkg')
      prepareTree verbosity pkg' mb_lbi targetDir pps
      when snapshot $
        overwriteSnapshotPackageDesc verbosity pkg' targetDir
    verbosity = fromFlag (sDistVerbosity flags)
    snapshot  = fromFlag (sDistSnapshot flags)
    distPref     = fromFlag $ sDistDistPref flags
    targetPref   = distPref
    tmpTargetDir = mkTmpDir distPref
listPackageSources :: Verbosity          
                   -> PackageDescription 
                   -> [PPSuffixHandler]  
                                         
                   -> IO ([FilePath], [FilePath])
listPackageSources verbosity pkg_descr0 pps = do
  
  ordinary        <- listPackageSourcesOrdinary        verbosity pkg_descr pps
  maybeExecutable <- listPackageSourcesMaybeExecutable pkg_descr
  return (ordinary, maybeExecutable)
  where
    pkg_descr = filterAutogenModule pkg_descr0
listPackageSourcesMaybeExecutable :: PackageDescription -> IO [FilePath]
listPackageSourcesMaybeExecutable pkg_descr =
  
  fmap concat . forM (extraSrcFiles pkg_descr) $ \fpath -> matchFileGlob fpath
listPackageSourcesOrdinary :: Verbosity
                           -> PackageDescription
                           -> [PPSuffixHandler]
                           -> IO [FilePath]
listPackageSourcesOrdinary verbosity pkg_descr pps =
  fmap concat . sequence $
  [
    
    withLib $ \Library { exposedModules = modules, libBuildInfo = libBi } ->
     allSourcesBuildInfo libBi pps modules
    
  , fmap concat
    . withExe $ \Executable { modulePath = mainPath, buildInfo = exeBi } -> do
       biSrcs  <- allSourcesBuildInfo exeBi pps []
       mainSrc <- findMainExeFile exeBi pps mainPath
       return (mainSrc:biSrcs)
    
  , fmap concat
    . withTest $ \t -> do
       let bi  = testBuildInfo t
       case testInterface t of
         TestSuiteExeV10 _ mainPath -> do
           biSrcs <- allSourcesBuildInfo bi pps []
           srcMainFile <- do
             ppFile <- findFileWithExtension (ppSuffixes pps)
                       (hsSourceDirs bi) (dropExtension mainPath)
             case ppFile of
               Nothing -> findFile (hsSourceDirs bi) mainPath
               Just pp -> return pp
           return (srcMainFile:biSrcs)
         TestSuiteLibV09 _ m ->
           allSourcesBuildInfo bi pps [m]
         TestSuiteUnsupported tp -> die $ "Unsupported test suite type: "
                                   ++ show tp
    
  , fmap concat
    . withBenchmark $ \bm -> do
       let  bi = benchmarkBuildInfo bm
       case benchmarkInterface bm of
         BenchmarkExeV10 _ mainPath -> do
           biSrcs <- allSourcesBuildInfo bi pps []
           srcMainFile <- do
             ppFile <- findFileWithExtension (ppSuffixes pps)
                       (hsSourceDirs bi) (dropExtension mainPath)
             case ppFile of
               Nothing -> findFile (hsSourceDirs bi) mainPath
               Just pp -> return pp
           return (srcMainFile:biSrcs)
         BenchmarkUnsupported tp -> die $ "Unsupported benchmark type: "
                                    ++ show tp
    
  , fmap concat
    . forM (dataFiles pkg_descr) $ \filename ->
       matchFileGlob (dataDir pkg_descr </> filename)
    
  , fmap concat
    . forM (extraDocFiles pkg_descr) $ \ filename ->
      matchFileGlob filename
    
  , return $ case [licenseFile pkg_descr]
             of [[]] -> []
                l    -> l
    
  , withLib $ \ l -> do
       let lbi = libBuildInfo l
           relincdirs = "." : filter (not.isAbsolute) (includeDirs lbi)
       mapM (fmap snd . findIncludeFile relincdirs) (installIncludes lbi)
    
  , fmap (maybe [] (\f -> [f])) $ findSetupFile ""
    
  , fmap (\d -> [d]) (defaultPackageDesc verbosity)
  ]
  where
    
    
    withLib       action = maybe (return []) action (library pkg_descr)
    withExe       action = mapM action (executables pkg_descr)
    withTest      action = mapM action (testSuites pkg_descr)
    withBenchmark action = mapM action (benchmarks pkg_descr)
prepareTree :: Verbosity          
            -> PackageDescription 
            -> Maybe LocalBuildInfo
            -> FilePath           
            -> [PPSuffixHandler]  
            -> IO ()
prepareTree verbosity pkg_descr0 mb_lbi targetDir pps = do
  
  
  case mb_lbi of
    Just lbi | not (null pps) -> do
      let lbi' = lbi{ buildDir = targetDir </> buildDir lbi }
      withAllComponentsInBuildOrder pkg_descr lbi' $ \c _ ->
        preprocessComponent pkg_descr c lbi' True verbosity pps
    _ -> return ()
  (ordinary, mExecutable)  <- listPackageSources verbosity pkg_descr0 pps
  installOrdinaryFiles        verbosity targetDir (zip (repeat []) ordinary)
  installMaybeExecutableFiles verbosity targetDir (zip (repeat []) mExecutable)
  maybeCreateDefaultSetupScript targetDir
  where
    pkg_descr = filterAutogenModule pkg_descr0
findSetupFile :: FilePath -> IO (Maybe FilePath)
findSetupFile targetDir = do
  hsExists  <- doesFileExist setupHs
  lhsExists <- doesFileExist setupLhs
  if hsExists
    then return (Just setupHs)
    else if lhsExists
         then return (Just setupLhs)
         else return Nothing
    where
      setupHs  = targetDir </> "Setup.hs"
      setupLhs = targetDir </> "Setup.lhs"
maybeCreateDefaultSetupScript :: FilePath -> IO ()
maybeCreateDefaultSetupScript targetDir = do
  mSetupFile <- findSetupFile targetDir
  case mSetupFile of
    Just _setupFile -> return ()
    Nothing         -> do
      writeUTF8File (targetDir </> "Setup.hs") $ unlines [
        "import Distribution.Simple",
        "main = defaultMain"]
findMainExeFile :: BuildInfo -> [PPSuffixHandler] -> FilePath -> IO FilePath
findMainExeFile exeBi pps mainPath = do
  ppFile <- findFileWithExtension (ppSuffixes pps) (hsSourceDirs exeBi)
            (dropExtension mainPath)
  case ppFile of
    Nothing -> findFile (hsSourceDirs exeBi) mainPath
    Just pp -> return pp
findIncludeFile :: [FilePath] -> String -> IO (String, FilePath)
findIncludeFile [] f = die ("can't find include file " ++ f)
findIncludeFile (d:ds) f = do
  let path = (d </> f)
  b <- doesFileExist path
  if b then return (f,path) else findIncludeFile ds f
filterAutogenModule :: PackageDescription -> PackageDescription
filterAutogenModule pkg_descr0 = mapLib filterAutogenModuleLib $
                                 mapAllBuildInfo filterAutogenModuleBI pkg_descr0
  where
    mapLib f pkg = pkg { library = fmap f (library pkg) }
    filterAutogenModuleLib lib = lib {
      exposedModules = filter (/=autogenModule) (exposedModules lib)
    }
    filterAutogenModuleBI bi = bi {
      otherModules   = filter (/=autogenModule) (otherModules bi)
    }
    autogenModule = autogenModuleName pkg_descr0
prepareSnapshotTree :: Verbosity          
                    -> PackageDescription 
                    -> Maybe LocalBuildInfo
                    -> FilePath           
                    -> [PPSuffixHandler]  
                                          
                    -> IO ()
prepareSnapshotTree verbosity pkg mb_lbi targetDir pps = do
  prepareTree verbosity pkg mb_lbi targetDir pps
  overwriteSnapshotPackageDesc verbosity pkg targetDir
overwriteSnapshotPackageDesc :: Verbosity          
                             -> PackageDescription 
                             -> FilePath           
                             -> IO ()
overwriteSnapshotPackageDesc verbosity pkg targetDir = do
    
    
    descFile <- defaultPackageDesc verbosity
    withUTF8FileContents descFile $
      writeUTF8File (targetDir </> descFile)
        . unlines . map (replaceVersion (packageVersion pkg)) . lines
  where
    replaceVersion :: Version -> String -> String
    replaceVersion version line
      | "version:" `isPrefixOf` map toLower line
                  = "version: " ++ display version
      | otherwise = line
snapshotPackage :: UTCTime -> PackageDescription -> PackageDescription
snapshotPackage date pkg =
  pkg {
    package = pkgid { pkgVersion = snapshotVersion date (pkgVersion pkgid) }
  }
  where pkgid = packageId pkg
snapshotVersion :: UTCTime -> Version -> Version
snapshotVersion date version = version {
    versionBranch = versionBranch version
                 ++ [dateToSnapshotNumber date]
  }
dateToSnapshotNumber :: UTCTime -> Int
dateToSnapshotNumber date = case toGregorian (utctDay date) of
                            (year, month, day) ->
                                fromIntegral year * 10000
                              + month             * 100
                              + day
type CreateArchiveFun = Verbosity               
                        -> PackageDescription   
                        -> Maybe LocalBuildInfo 
                        -> FilePath             
                        -> FilePath             
                        -> IO FilePath
createArchive :: CreateArchiveFun
createArchive verbosity pkg_descr mb_lbi tmpDir targetPref = do
  let tarBallFilePath = targetPref </> tarBallName pkg_descr <.> "tar.gz"
  (tarProg, _) <- requireProgram verbosity tarProgram
                    (maybe defaultProgramConfiguration withPrograms mb_lbi)
   
   
   
   
  rawSystemProgram verbosity tarProg
           ["-C", tmpDir, "-czf", tarBallFilePath, tarBallName pkg_descr]
  return tarBallFilePath
allSourcesBuildInfo :: BuildInfo
                       -> [PPSuffixHandler] 
                       -> [ModuleName]      
                       -> IO [FilePath]
allSourcesBuildInfo bi pps modules = do
  let searchDirs = hsSourceDirs bi
  sources <- sequence
    [ let file = ModuleName.toFilePath module_
      in findFileWithExtension suffixes searchDirs file
         >>= maybe (notFound module_) return
    | module_ <- modules ++ otherModules bi ]
  bootFiles <- sequence
    [ let file = ModuleName.toFilePath module_
          fileExts = ["hs-boot", "lhs-boot"]
      in findFileWithExtension fileExts (hsSourceDirs bi) file
    | module_ <- modules ++ otherModules bi ]
  return $ sources ++ catMaybes bootFiles ++ cSources bi
  where
    suffixes = ppSuffixes pps ++ ["hs", "lhs"]
    notFound m = die $ "Error: Could not find module: " ++ display m
                 ++ " with any suffix: " ++ show suffixes
printPackageProblems :: Verbosity -> PackageDescription -> IO ()
printPackageProblems verbosity pkg_descr = do
  ioChecks      <- checkPackageFiles pkg_descr "."
  let pureChecks = checkConfiguredPackage pkg_descr
      isDistError (PackageDistSuspicious _) = False
      isDistError _                         = True
      (errors, warnings) = partition isDistError (pureChecks ++ ioChecks)
  unless (null errors) $
      notice verbosity $ "Distribution quality errors:\n"
                      ++ unlines (map explanation errors)
  unless (null warnings) $
      notice verbosity $ "Distribution quality warnings:\n"
                      ++ unlines (map explanation warnings)
  unless (null errors) $
      notice verbosity
        "Note: the public hackage server would reject this package."
tarBallName :: PackageDescription -> String
tarBallName = display . packageId
mapAllBuildInfo :: (BuildInfo -> BuildInfo)
                -> (PackageDescription -> PackageDescription)
mapAllBuildInfo f pkg = pkg {
    library     = fmap mapLibBi (library pkg),
    executables = fmap mapExeBi (executables pkg),
    testSuites  = fmap mapTestBi (testSuites pkg),
    benchmarks  = fmap mapBenchBi (benchmarks pkg)
  }
  where
    mapLibBi lib  = lib { libBuildInfo       = f (libBuildInfo lib) }
    mapExeBi exe  = exe { buildInfo          = f (buildInfo exe) }
    mapTestBi t   = t   { testBuildInfo      = f (testBuildInfo t) }
    mapBenchBi bm = bm  { benchmarkBuildInfo = f (benchmarkBuildInfo bm) }