-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.Make
-- Copyright   :  Martin Sjögren 2004
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- This is an alternative build system that delegates everything to the @make@
-- program. All the commands just end up calling @make@ with appropriate
-- arguments. The intention was to allow preexisting packages that used
-- makefiles to be wrapped into Cabal packages. In practice essentially all
-- such packages were converted over to the \"Simple\" build system instead.
-- Consequently this module is not used much and it certainly only sees cursory
-- maintenance and no testing. Perhaps at some point we should stop pretending
-- that it works.
--
-- Uses the parsed command-line from "Distribution.Simple.Setup" in order to build
-- Haskell tools using a backend build system based on make. Obviously we
-- assume that there is a configure script, and that after the ConfigCmd has
-- been run, there is a Makefile. Further assumptions:
--
-- [ConfigCmd] We assume the configure script accepts
--              @--with-hc@,
--              @--with-hc-pkg@,
--              @--prefix@,
--              @--bindir@,
--              @--libdir@,
--              @--libexecdir@,
--              @--datadir@.
--
-- [BuildCmd] We assume that the default Makefile target will build everything.
--
-- [InstallCmd] We assume there is an @install@ target. Note that we assume that
-- this does *not* register the package!
--
-- [CopyCmd]    We assume there is a @copy@ target, and a variable @$(destdir)@.
--              The @copy@ target should probably just invoke @make install@
--              recursively (e.g. @$(MAKE) install prefix=$(destdir)\/$(prefix)
--              bindir=$(destdir)\/$(bindir)@. The reason we can\'t invoke @make
--              install@ directly here is that we don\'t know the value of @$(prefix)@.
--
-- [SDistCmd] We assume there is a @dist@ target.
--
-- [RegisterCmd] We assume there is a @register@ target and a variable @$(user)@.
--
-- [UnregisterCmd] We assume there is an @unregister@ target.
--
-- [HaddockCmd] We assume there is a @docs@ or @doc@ target.


--                      copy :
--                              $(MAKE) install prefix=$(destdir)/$(prefix) \
--                                              bindir=$(destdir)/$(bindir) \

{- All rights reserved.

Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are
met:

    * Redistributions of source code must retain the above copyright
      notice, this list of conditions and the following disclaimer.

    * Redistributions in binary form must reproduce the above
      copyright notice, this list of conditions and the following
      disclaimer in the documentation and/or other materials provided
      with the distribution.

    * Neither the name of Isaac Jones nor the names of other
      contributors may be used to endorse or promote products derived
      from this software without specific prior written permission.

THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}

module Distribution.Make (
        module Distribution.Package,
        License(..), Version(..),
        defaultMain, defaultMainArgs, defaultMainNoRead
  ) where

-- local
import Distribution.Compat.Exception
import Distribution.Package --must not specify imports, since we're exporting moule.
import Distribution.Simple.Program(defaultProgramConfiguration)
import Distribution.PackageDescription
import Distribution.Simple.Setup
import Distribution.Simple.Command

import Distribution.Simple.Utils (rawSystemExit, cabalVersion)

import Distribution.License (License(..))
import Distribution.Version
         ( Version(..) )
import Distribution.Text
         ( display )

import System.Environment (getArgs, getProgName)
import Data.List  (intersperse)
import System.Exit

defaultMain :: IO ()
defaultMain = getArgs :: IO [String]getArgs (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= defaultMainArgs :: [String] -> IO ()defaultMainArgs

defaultMainArgs :: [String] -> IO ()
defaultMainArgs = defaultMainHelper :: [String] -> IO ()defaultMainHelper

{-# DEPRECATED defaultMainNoRead "it ignores its PackageDescription arg" #-}
defaultMainNoRead :: PackageDescription -> IO ()
defaultMainNoRead = const :: a -> b -> aconst defaultMain :: IO ()defaultMain

defaultMainHelper :: [String] -> IO ()
defaultMainHelper args =
  case commandsRun ::
  CommandUI a
  -> [Command action]
  -> [String]
  -> CommandParse (a, CommandParse action)commandsRun globalCommand :: CommandUI GlobalFlagsglobalCommand commands :: [Command (IO ())]commands args :: [String]args of
    CommandHelp   help                 -> printHelp :: (String -> String) -> IO ()printHelp help :: String -> Stringhelp
    CommandList   opts                 -> printOptionsList :: [String] -> IO ()printOptionsList opts :: [String]opts
    CommandErrors errs                 -> printErrors :: [[Char]] -> IO bprintErrors errs :: [[Char]]errs
    CommandReadyToGo (flags, commandParse)  ->
      case commandParse :: CommandParse (IO ())commandParse of
        _ | fromFlag :: Flag a -> afromFlag (globalVersion :: GlobalFlags -> Flag BoolglobalVersion flags :: GlobalFlagsflags)        -> printVersion :: IO ()printVersion
          | fromFlag :: Flag a -> afromFlag (globalNumericVersion :: GlobalFlags -> Flag BoolglobalNumericVersion flags :: GlobalFlagsflags) -> printNumericVersion :: IO ()printNumericVersion
        CommandHelp     help           -> printHelp :: (String -> String) -> IO ()printHelp help :: String -> Stringhelp
        CommandList     opts           -> printOptionsList :: [String] -> IO ()printOptionsList opts :: [String]opts
        CommandErrors   errs           -> printErrors :: [[Char]] -> IO bprintErrors errs :: [[Char]]errs
        CommandReadyToGo action        -> action :: IO ()action

  where
    printHelp help = getProgName :: IO StringgetProgName (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= putStr :: String -> IO ()putStr (.) :: (b -> c) -> (a -> b) -> a -> c. help :: String -> Stringhelp
    printOptionsList = putStr :: String -> IO ()putStr (.) :: (b -> c) -> (a -> b) -> a -> c. unlines :: [String] -> Stringunlines
    printErrors errs = do
      putStr :: String -> IO ()putStr (concat :: [[a]] -> [a]concat (intersperse :: a -> [a] -> [a]intersperse "\n" errs :: [[Char]]errs))
      exitWith :: ExitCode -> IO aexitWith (ExitFailure :: Int -> ExitCodeExitFailure 1)
    printNumericVersion = putStrLn :: String -> IO ()putStrLn ($) :: (a -> b) -> a -> b$ display :: Text a => a -> Stringdisplay cabalVersion :: VersioncabalVersion
    printVersion        = putStrLn :: String -> IO ()putStrLn ($) :: (a -> b) -> a -> b$ "Cabal library version "
                                  (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay cabalVersion :: VersioncabalVersion

    progs = defaultProgramConfiguration :: ProgramConfigurationdefaultProgramConfiguration
    commands =
      [configureCommand :: ProgramConfiguration -> CommandUI ConfigFlagsconfigureCommand progs :: ProgramConfigurationprogs commandAddAction ::
  CommandUI flags -> (flags -> [String] -> action) -> Command action`commandAddAction` configureAction :: ConfigFlags -> [String] -> IO ()configureAction
      ,buildCommand :: ProgramConfiguration -> CommandUI BuildFlagsbuildCommand     progs :: ProgramConfigurationprogs commandAddAction ::
  CommandUI flags -> (flags -> [String] -> action) -> Command action`commandAddAction` buildAction :: BuildFlags -> [String] -> IO ()buildAction
      ,installCommand :: CommandUI InstallFlagsinstallCommand         commandAddAction ::
  CommandUI flags -> (flags -> [String] -> action) -> Command action`commandAddAction` installAction :: InstallFlags -> [String] -> IO ()installAction
      ,copyCommand :: CommandUI CopyFlagscopyCommand            commandAddAction ::
  CommandUI flags -> (flags -> [String] -> action) -> Command action`commandAddAction` copyAction :: CopyFlags -> [String] -> IO ()copyAction
      ,haddockCommand :: CommandUI HaddockFlagshaddockCommand         commandAddAction ::
  CommandUI flags -> (flags -> [String] -> action) -> Command action`commandAddAction` haddockAction :: HaddockFlags -> [String] -> IO ()haddockAction
      ,cleanCommand :: CommandUI CleanFlagscleanCommand           commandAddAction ::
  CommandUI flags -> (flags -> [String] -> action) -> Command action`commandAddAction` cleanAction :: CleanFlags -> [String] -> IO ()cleanAction
      ,sdistCommand :: CommandUI SDistFlagssdistCommand           commandAddAction ::
  CommandUI flags -> (flags -> [String] -> action) -> Command action`commandAddAction` sdistAction :: SDistFlags -> [String] -> IO ()sdistAction
      ,registerCommand :: CommandUI RegisterFlagsregisterCommand        commandAddAction ::
  CommandUI flags -> (flags -> [String] -> action) -> Command action`commandAddAction` registerAction :: RegisterFlags -> [String] -> IO ()registerAction
      ,unregisterCommand :: CommandUI RegisterFlagsunregisterCommand      commandAddAction ::
  CommandUI flags -> (flags -> [String] -> action) -> Command action`commandAddAction` unregisterAction :: RegisterFlags -> [String] -> IO ()unregisterAction
      ]

configureAction :: ConfigFlags -> [String] -> IO ()
configureAction flags args = do
  noExtraFlags :: [String] -> IO ()noExtraFlags args :: [String]args
  let verbosity = fromFlag :: Flag a -> afromFlag (configVerbosity :: ConfigFlags -> Flag VerbosityconfigVerbosity flags :: GlobalFlagsflags)
  rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()rawSystemExit verbosity :: Verbosityverbosity "sh" ($) :: (a -> b) -> a -> b$
    "configure"
    (:) :: a -> [a] -> [a]: configureArgs :: Bool -> ConfigFlags -> [String]configureArgs backwardsCompatHack :: BoolbackwardsCompatHack flags :: GlobalFlagsflags
  where backwardsCompatHack = True :: BoolTrue

copyAction :: CopyFlags -> [String] -> IO ()
copyAction flags args = do
  noExtraFlags :: [String] -> IO ()noExtraFlags args :: [String]args
  let destArgs = case fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ copyDest :: CopyFlags -> Flag CopyDestcopyDest flags :: GlobalFlagsflags of
        NoCopyDest      -> ["install"]
        CopyTo path     -> ["copy", "destdir=" (++) :: [a] -> [a] -> [a]++ path :: FilePathpath]
  rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()rawSystemExit (fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ copyVerbosity :: CopyFlags -> Flag VerbositycopyVerbosity flags :: GlobalFlagsflags) "make" destArgs :: [[Char]]destArgs

installAction :: InstallFlags -> [String] -> IO ()
installAction flags args = do
  noExtraFlags :: [String] -> IO ()noExtraFlags args :: [String]args
  rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()rawSystemExit (fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ installVerbosity :: InstallFlags -> Flag VerbosityinstallVerbosity flags :: GlobalFlagsflags) "make" ["install"]
  rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()rawSystemExit (fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ installVerbosity :: InstallFlags -> Flag VerbosityinstallVerbosity flags :: GlobalFlagsflags) "make" ["register"]

haddockAction :: HaddockFlags -> [String] -> IO ()
haddockAction flags args = do
  noExtraFlags :: [String] -> IO ()noExtraFlags args :: [String]args
  rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()rawSystemExit (fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ haddockVerbosity :: HaddockFlags -> Flag VerbosityhaddockVerbosity flags :: GlobalFlagsflags) "make" ["docs"]
    catchIO :: IO a -> (IOException -> IO a) -> IO a`catchIO` \_ ->
    rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()rawSystemExit (fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ haddockVerbosity :: HaddockFlags -> Flag VerbosityhaddockVerbosity flags :: GlobalFlagsflags) "make" ["doc"]

buildAction :: BuildFlags -> [String] -> IO ()
buildAction flags args = do
  noExtraFlags :: [String] -> IO ()noExtraFlags args :: [String]args
  rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()rawSystemExit (fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ buildVerbosity :: BuildFlags -> Flag VerbositybuildVerbosity flags :: GlobalFlagsflags) "make" [] :: [a][]

cleanAction :: CleanFlags -> [String] -> IO ()
cleanAction flags args = do
  noExtraFlags :: [String] -> IO ()noExtraFlags args :: [String]args
  rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()rawSystemExit (fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ cleanVerbosity :: CleanFlags -> Flag VerbositycleanVerbosity flags :: GlobalFlagsflags) "make" ["clean"]

sdistAction :: SDistFlags -> [String] -> IO ()
sdistAction flags args = do
  noExtraFlags :: [String] -> IO ()noExtraFlags args :: [String]args
  rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()rawSystemExit (fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ sDistVerbosity :: SDistFlags -> Flag VerbositysDistVerbosity flags :: GlobalFlagsflags) "make" ["dist"]

registerAction :: RegisterFlags -> [String] -> IO ()
registerAction  flags args = do
  noExtraFlags :: [String] -> IO ()noExtraFlags args :: [String]args
  rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()rawSystemExit (fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ regVerbosity :: RegisterFlags -> Flag VerbosityregVerbosity flags :: GlobalFlagsflags) "make" ["register"]

unregisterAction :: RegisterFlags -> [String] -> IO ()
unregisterAction flags args = do
  noExtraFlags :: [String] -> IO ()noExtraFlags args :: [String]args
  rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()rawSystemExit (fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ regVerbosity :: RegisterFlags -> Flag VerbosityregVerbosity flags :: GlobalFlagsflags) "make" ["unregister"]