module Devel.Compile 
( initCompile
, compile
, finishCompile
) where
import IdeSession
import Distribution.PackageDescription
import Distribution.ModuleName
import Distribution.PackageDescription.Parse
import Distribution.PackageDescription.Configuration
import Language.Haskell.Extension
import Data.Text (unpack)
import Data.Monoid ((<>))
import Devel.Paths
import Devel.Types
import System.FilePath.Posix (takeExtension, pathSeparator)
import System.Directory (doesFileExist)
import Data.List (union, delete, isInfixOf, nub)
import Data.Maybe (fromMaybe)
import Control.Monad (filterM)
initCompile :: SessionConfig -> Maybe IdeSession -> IO (IdeSession, [GhcExtension], [FilePath])
initCompile sessionConfig mSession = do
  
  session <- case mSession of
               Just session -> return session
               Nothing -> initSession
                            defaultSessionInitParams
                            sessionConfig
  
  (extensionList, srcDir, cabalSrcList) <- getExtensions
  sourceList <- getSourceList srcDir cabalSrcList
  return (session, extensionList, sourceList)
getSourceList :: [FilePath] -> [FilePath] -> IO [FilePath]
getSourceList srcDir cabalSrcList = do
  fileList' <- mapM getRecursiveContents srcDir
  let 
      fileList = foldr union [] fileList'
      
      fileListNoTests = filter (not.(\x -> isInfixOf "test/" x || isInfixOf "cabal-sandbox/" x || isInfixOf "stack-work/" x)) fileList
      
      fileListCombined = fileListNoTests ++ cabalSrcList
      
      
      sourceList' = filter 
                      (\f -> let ext = takeExtension f in ext == ".lhs" || ext == ".hs") 
                      fileListCombined
      
      sourceList = nub $ delete "app/DevelMain.hs" $ delete "app/devel.hs" sourceList'
  return sourceList
compile :: IdeSession -> FilePath -> [GhcExtension] -> [FilePath] -> IO (IdeSession, IdeSessionUpdate)
compile session buildFile extensionList sourceList = do
  
  let targetList = TargetsInclude (if buildFile `elem` sourceList
                                      then sourceList
                                      else buildFile : sourceList) :: Targets
      update = updateTargets targetList
               <> updateCodeGeneration True
               <> updateGhcOpts (["-Wall", "-ddump-hi", "-ddump-to-file"] ++ extensionList)
  return (session, update)
finishCompile :: (IdeSession, IdeSessionUpdate) -> IO (Either [SourceError'] IdeSession)
finishCompile (session, update) = do
  _ <- updateSession session update print
  
  errorList' <- getSourceErrors session
  let errorList = case filterErrors errorList' of
                    [] -> []
                    _  -> prettyPrintErrors errorList'
  
  mapM_ putStrLn $ prettyPrintErrors errorList'
  return $ case errorList of
    [] -> Right session
    _  -> Left  errorList
getExtensions :: IO ([GhcExtension], [FilePath], [FilePath])
getExtensions = do               
  cabalFilePath <- getCabalFile
  cabalFile <- readFile cabalFilePath
  let unsafePackageDescription = parsePackageDescription cabalFile
      genericPackageDescription = case unsafePackageDescription of
                                ParseOk _ a -> a
                                _           -> error "failed package description."
      packDescription = flattenPackageDescription genericPackageDescription
      rawExt = usedExtensions $ head $ allBuildInfo packDescription
      lib = fromMaybe emptyLibrary $ library packDescription
      
      srcDir  = hsSourceDirs $ libBuildInfo lib
      srcList = extraSrcFiles packDescription
      parseExtension :: Extension -> String
      parseExtension (EnableExtension extension) =  "-X" ++ show extension
      parseExtension (DisableExtension extension) = "-XNo" ++ show extension
      parseExtension (UnknownExtension extension) = "-X" ++ show extension
      extensions = map parseExtension rawExt
      
      execList = executables packDescription
  
  paths <- mapM getPathList execList 
  return (extensions, srcDir, (srcList ++ (concat paths)))
  where 
    getPathList :: Executable -> IO [FilePath]
    getPathList exec =
      let mainModule' = modulePath exec
          bInfo = buildInfo exec
          execModuleList = otherModules bInfo
          srcDirsList = hsSourceDirs bInfo
          execSrcFileList = map toFilePath execModuleList
          nonPaths = [dir ++ (pathSeparator : fp) | fp <- execSrcFileList, dir <- srcDirsList]
          paths' = map (++ (pathSeparator : mainModule') ) srcDirsList 
                   ++ [x++y | x <- nonPaths, y <- [".hs", ".lhs"]]
      in filterM doesFileExist paths'
filterErrors :: [SourceError] -> [SourceError]
filterErrors [] = []
filterErrors (x:xs) = 
  case errorKind x  of
    KindWarning -> filterErrors xs
    _ -> x : filterErrors xs
prettyPrintErrors :: [SourceError] -> [SourceError']
prettyPrintErrors [] = []
prettyPrintErrors (x: xs) = 
  case errorKind x  of
    KindWarning -> ("Warning: " ++ show (errorSpan x) ++ " " ++ unpack (errorMsg x)) : prettyPrintErrors xs
    KindError   -> ("Error: " ++ show (errorSpan x) ++ " " ++ unpack (errorMsg x))  : prettyPrintErrors xs
    KindServerDied -> show (errorKind x) : prettyPrintErrors xs