aboutsummaryrefslogtreecommitdiff
path: root/CabalHelper/Wrapper.hs
blob: c0908dc9597a659ed110c104ce5416b91d9a4107 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
-- cabal-helper: Simple interface to Cabal's configuration state
-- Copyright (C) 2015  Daniel Gröber <dxld ÄT darkboxed DOT org>
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU Affero General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-- GNU Affero General Public License for more details.
--
-- You should have received a copy of the GNU Affero General Public License
-- along with this program.  If not, see <http://www.gnu.org/licenses/>.
{-# LANGUAGE RecordWildCards, FlexibleContexts #-}
module Main where

import Control.Applicative
import Control.Monad
import Data.Char
import Data.List
import Data.Maybe
import Data.String
import Data.Version
import Text.Printf
import System.Console.GetOpt
import System.Environment
import System.Directory
import System.FilePath
import System.Process
import System.Exit
import System.IO
import Prelude

import Distribution.System (buildPlatform)
import Distribution.Text (display)

import Paths_cabal_helper (version)
import CabalHelper.Common
import CabalHelper.GuessGhc
import CabalHelper.Compile
import CabalHelper.Types

usage :: IO ()
usage = do
  prog <- getProgName
  hPutStr stderr $ align "(" "|" ("Usage: " ++ prog ++ " " ++ usageMsg)
 where
   usageMsg = "\
\( print-appdatadir\n\
\| print-build-platform\n\
\| [--verbose]\n\
\  [--with-ghc=GHC_PATH]\n\
\  [--with-ghc-pkg=GHC_PKG_PATH]\n\
\  [--with-cabal=CABAL_PATH]\n\
\  PROJ_DIR DIST_DIR ( print-exe | [CABAL_HELPER_ARGS...] ) )\n"

globalArgSpec :: [OptDescr (Options -> Options)]
globalArgSpec =
      [ option "" ["verbose"] "Be more verbose" $
              NoArg $ \o -> o { verbose = True }

      , option "" ["with-ghc"] "GHC executable to use" $
              reqArg "PROG" $ \p o -> o { ghcProgram = p }

      , option "" ["with-ghc-pkg"] "ghc-pkg executable to use (only needed when guessing from GHC path fails)" $
              reqArg "PROG" $ \p o -> o { ghcPkgProgram = p }

      , option "" ["with-cabal"] "cabal-install executable to use" $
               reqArg "PROG" $ \p o -> o { cabalProgram = p }
      ]
 where
   option :: [Char] -> [String] -> String -> ArgDescr a -> OptDescr a
   option s l udsc dsc = Option s l dsc udsc

   reqArg :: String -> (String -> a) -> ArgDescr a
   reqArg udsc dsc = ReqArg dsc udsc

parseCommandArgs :: Options -> [String] -> (Options, [String])
parseCommandArgs opts argv
    = case getOpt RequireOrder globalArgSpec argv of
        (o,r,[])   -> (foldr id opts o, r)
        (_,_,errs) ->
            panic $ "Parsing command options failed:\n" ++ concat errs

guessProgramPaths :: Options -> IO Options
guessProgramPaths opts = do
    if not (same ghcProgram opts dopts) && same ghcPkgProgram opts dopts
       then do
         mghcPkg <- guessToolFromGhcPath "ghc-pkg" (ghcProgram opts)
         return opts {
           ghcPkgProgram = fromMaybe (ghcPkgProgram opts) mghcPkg
         }
       else return opts
 where
   same f o o'  = f o == f o'
   dopts = defaultOptions

main :: IO ()
main = handlePanic $ do
  (opts', args) <- parseCommandArgs defaultOptions <$> getArgs
  opts <- guessProgramPaths opts'
  case args of
    [] -> usage
    "help":[] -> usage
    "version":[] -> putStrLn $ showVersion version
    "print-appdatadir":[] -> putStrLn =<< appDataDir
    "print-build-platform":[] -> putStrLn $ display buildPlatform
    projdir:distdir:args' -> do
      cfgf <- canonicalizePath (distdir </> "setup-config")
      mhdr <- getCabalConfigHeader cfgf
      case mhdr of
        Nothing -> panic $ printf "\
\Could not read Cabal's persistent setup configuration header\n\
\- Check first line of: %s\n\
\- Maybe try: $ cabal configure" cfgf
        Just (hdrCabalVersion, _) -> do
          eexe <- compileHelper opts hdrCabalVersion projdir distdir
          case eexe of
              Left e -> exitWith e
              Right exe ->
                case args' of
                  "print-exe":_ -> putStrLn exe
                  _ -> do
                    (_,_,_,h) <- createProcess $ proc exe args
                    exitWith =<< waitForProcess h
    _ -> error "invalid command line"