{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# OPTIONS -fno-warn-unused-do-bind #-}
module Stack.GhcPkg
  (getGlobalDB
  ,findGhcPkgField
  ,createDatabase
  ,unregisterGhcPkgId
  ,getCabalPkgVer
  ,ghcPkgExeName
  ,ghcPkgPathEnvVar
  ,mkGhcPackagePath)
  where
import           Stack.Prelude
import qualified Data.ByteString.Char8 as S8
import qualified Data.ByteString.Lazy as BL
import           Data.List
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import           Path (parent, mkRelFile, (</>))
import           Path.Extra (toFilePathNoTrailingSep)
import           Path.IO
import           Stack.Constants
import           Stack.Types.Build
import           Stack.Types.GhcPkgId
import           Stack.Types.PackageIdentifier
import           Stack.Types.Compiler
import           Stack.Types.PackageName
import           Stack.Types.Version
import           System.FilePath (searchPathSeparator)
import           RIO.Process
getGlobalDB :: (HasProcessContext env, HasLogFunc env)
            => WhichCompiler -> RIO env (Path Abs Dir)
getGlobalDB wc = do
    logDebug "Getting global package database location"
    
    
    bs <- ghcPkg wc [] ["list", "--global"] >>= either throwIO return
    let fp = S8.unpack $ stripTrailingColon $ firstLine bs
    liftIO $ resolveDir' fp
  where
    stripTrailingColon bs
        | S8.null bs = bs
        | S8.last bs == ':' = S8.init bs
        | otherwise = bs
    firstLine = S8.takeWhile (\c -> c /= '\r' && c /= '\n')
ghcPkg :: (HasProcessContext env, HasLogFunc env)
       => WhichCompiler
       -> [Path Abs Dir]
       -> [String]
       -> RIO env (Either SomeException S8.ByteString)
ghcPkg wc pkgDbs args = do
    eres <- go
    case eres of
      Left _ -> do
        mapM_ (createDatabase wc) pkgDbs
        go
      Right _ -> return eres
  where
    go = tryAny
       $ BL.toStrict . fst
     <$> proc (ghcPkgExeName wc) args' readProcess_
    args' = packageDbFlags pkgDbs ++ args
createDatabase
  :: (HasProcessContext env, HasLogFunc env)
  => WhichCompiler -> Path Abs Dir -> RIO env ()
createDatabase wc db = do
    exists <- doesFileExist (db </> $(mkRelFile "package.cache"))
    unless exists $ do
        
        
        
        dirExists <- doesDirExist db
        args <- if dirExists
            then do
                logWarn $
                    "The package database located at " <>
                    fromString (toFilePath db) <>
                    " is corrupted (missing its package.cache file)."
                logWarn "Proceeding with a recache"
                return ["--package-db", toFilePath db, "recache"]
            else do
                
                
                
                ensureDir (parent db)
                return ["init", toFilePath db]
        void $ proc (ghcPkgExeName wc) args $ \pc ->
          readProcess_ pc `onException`
          logError ("Unable to create package database at " <> fromString (toFilePath db))
ghcPkgExeName :: WhichCompiler -> String
ghcPkgExeName Ghc = "ghc-pkg"
ghcPkgExeName Ghcjs = "ghcjs-pkg"
ghcPkgPathEnvVar :: WhichCompiler -> Text
ghcPkgPathEnvVar Ghc = "GHC_PACKAGE_PATH"
ghcPkgPathEnvVar Ghcjs = "GHCJS_PACKAGE_PATH"
packageDbFlags :: [Path Abs Dir] -> [String]
packageDbFlags pkgDbs =
          "--no-user-package-db"
        : map (\x -> "--package-db=" ++ toFilePath x) pkgDbs
findGhcPkgField
    :: (HasProcessContext env, HasLogFunc env)
    => WhichCompiler
    -> [Path Abs Dir] 
    -> String 
    -> Text
    -> RIO env (Maybe Text)
findGhcPkgField wc pkgDbs name field = do
    result <-
        ghcPkg
            wc
            pkgDbs
            ["field", "--simple-output", name, T.unpack field]
    return $
        case result of
            Left{} -> Nothing
            Right bs ->
                fmap (stripCR . T.decodeUtf8) $ listToMaybe $ S8.lines bs
findGhcPkgVersion :: (HasProcessContext env, HasLogFunc env)
                  => WhichCompiler
                  -> [Path Abs Dir] 
                  -> PackageName
                  -> RIO env (Maybe Version)
findGhcPkgVersion wc pkgDbs name = do
    mv <- findGhcPkgField wc pkgDbs (packageNameString name) "version"
    case mv of
        Just !v -> return (parseVersion v)
        _ -> return Nothing
unregisterGhcPkgId :: (HasProcessContext env, HasLogFunc env)
                    => WhichCompiler
                    -> CompilerVersion 'CVActual
                    -> Path Abs Dir 
                    -> GhcPkgId
                    -> PackageIdentifier
                    -> RIO env ()
unregisterGhcPkgId wc cv pkgDb gid ident = do
    eres <- ghcPkg wc [pkgDb] args
    case eres of
        Left e -> logWarn $ displayShow e
        Right _ -> return ()
  where
    
    args = "unregister" : "--user" : "--force" :
        (case cv of
            GhcVersion v | v < $(mkVersion "7.9") ->
                [packageIdentifierString ident]
            _ -> ["--ipid", ghcPkgIdString gid])
getCabalPkgVer :: (HasProcessContext env, HasLogFunc env)
               => WhichCompiler -> RIO env Version
getCabalPkgVer wc = do
    logDebug "Getting Cabal package version"
    mres <- findGhcPkgVersion
        wc
        [] 
        cabalPackageName
    maybe (throwIO $ Couldn'tFindPkgId cabalPackageName) return mres
mkGhcPackagePath :: Bool -> Path Abs Dir -> Path Abs Dir -> [Path Abs Dir] -> Path Abs Dir -> Text
mkGhcPackagePath locals localdb deps extras globaldb =
  T.pack $ intercalate [searchPathSeparator] $ concat
    [ [toFilePathNoTrailingSep localdb | locals]
    , [toFilePathNoTrailingSep deps]
    , [toFilePathNoTrailingSep db | db <- reverse extras]
    , [toFilePathNoTrailingSep globaldb]
    ]