-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.Client.Init
-- Copyright   :  (c) Brent Yorgey 2009
-- License     :  BSD-like
--
-- Maintainer  :  cabal-devel@haskell.org
-- Stability   :  provisional
-- Portability :  portable
--
-- Implementation of the 'cabal init' command, which creates an initial .cabal
-- file for a project.
--
-----------------------------------------------------------------------------

module Distribution.Client.Init
( -- * Commands
  initCmd
) where

import qualified Distribution.Client.Init.Interactive.Command as Interactive
import qualified Distribution.Client.Init.NonInteractive.Command as NonInteractive
import qualified Distribution.Client.Init.Simple as Simple
import Distribution.Verbosity
import Distribution.Client.Setup (RepoContext)
import Distribution.Simple.Compiler
import Distribution.Simple.Program (ProgramDb)
import Distribution.Client.Init.Types
import Distribution.Simple.Setup
import Distribution.Client.IndexUtils
import System.IO (hSetBuffering, stdout, BufferMode (NoBuffering))
import Distribution.Client.Init.FileCreators

-- | This is the main driver for the init script.
--
initCmd
    :: Verbosity
    -> PackageDBStack
    -> RepoContext
    -> Compiler
    -> ProgramDb
    -> InitFlags
    -> IO ()
initCmd :: Verbosity
-> PackageDBStack
-> RepoContext
-> Compiler
-> ProgramDb
-> InitFlags
-> IO ()
initCmd Verbosity
v PackageDBStack
packageDBs RepoContext
repoCtxt Compiler
comp ProgramDb
progdb InitFlags
initFlags = do
    InstalledPackageIndex
installedPkgIndex <- Verbosity
-> Compiler
-> PackageDBStack
-> ProgramDb
-> IO InstalledPackageIndex
getInstalledPackages Verbosity
v Compiler
comp PackageDBStack
packageDBs ProgramDb
progdb
    SourcePackageDb
sourcePkgDb <- Verbosity -> RepoContext -> IO SourcePackageDb
getSourcePackages Verbosity
v RepoContext
repoCtxt
    Handle -> BufferMode -> IO ()
hSetBuffering Handle
stdout BufferMode
NoBuffering
    ProjectSettings
settings <- Verbosity
-> InstalledPackageIndex
-> SourcePackageDb
-> InitFlags
-> IO ProjectSettings
createProject Verbosity
v InstalledPackageIndex
installedPkgIndex SourcePackageDb
sourcePkgDb InitFlags
initFlags
    forall (m :: * -> *). Interactive m => ProjectSettings -> m ()
writeProject ProjectSettings
settings
  where
    -- When no flag is set, default to interactive.
    --
    -- When `--interactive` is set, if we also set `--simple`,
    -- then we interactive generate a simple project with sensible defaults.
    --
    -- If `--simple` is not set, default to interactive. When the flag
    -- is explicitly set to `--non-interactive`, then we choose non-interactive.
    --
    createProject :: Verbosity
-> InstalledPackageIndex
-> SourcePackageDb
-> InitFlags
-> IO ProjectSettings
createProject
      | forall a. a -> Flag a -> a
fromFlagOrDefault Bool
False (InitFlags -> Flag Bool
simpleProject InitFlags
initFlags) =
          forall (m :: * -> *).
Interactive m =>
Verbosity
-> InstalledPackageIndex
-> SourcePackageDb
-> InitFlags
-> m ProjectSettings
Simple.createProject
      | Bool
otherwise = case InitFlags -> Flag Bool
interactive InitFlags
initFlags of
        Flag Bool
False -> forall (m :: * -> *).
Interactive m =>
Compiler
-> Verbosity
-> InstalledPackageIndex
-> SourcePackageDb
-> InitFlags
-> m ProjectSettings
NonInteractive.createProject Compiler
comp
        Flag Bool
_ -> forall (m :: * -> *).
Interactive m =>
Verbosity
-> InstalledPackageIndex
-> SourcePackageDb
-> InitFlags
-> m ProjectSettings
Interactive.createProject