Skip to content

Commit

Permalink
Use GHC.Path for running ghc and handle flag change in GHC 7.6 (refs #…
Browse files Browse the repository at this point in the history
  • Loading branch information
chrisdone committed Dec 2, 2012
1 parent e7aab14 commit 4c0dbc9
Show file tree
Hide file tree
Showing 2 changed files with 23 additions and 10 deletions.
4 changes: 4 additions & 0 deletions fay.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -129,6 +129,7 @@ library
other-modules: Language.Fay.Print, Control.Monad.IO, Language.Fay.Stdlib, System.Process.Extra, Data.List.Extra, Paths_fay
ghc-options: -O2 -Wall
build-depends: base >= 4 && < 5,
ghc-paths,
mtl,
haskell-src-exts,
aeson,
Expand Down Expand Up @@ -171,6 +172,7 @@ executable fay
ghc-prof-options: -fprof-auto
main-is: Main.hs
build-depends: base >= 4 && < 5,
ghc-paths,
mtl,
haskell-src-exts,
aeson,
Expand Down Expand Up @@ -204,6 +206,7 @@ executable fay-tests
main-is: Tests.hs
other-modules: Language.Fay.Compiler Test.Convert Test.Api Test.CommandLine Test.Util
build-depends: base >= 4 && < 5,
ghc-paths,
mtl,
haskell-src-exts,
aeson,
Expand Down Expand Up @@ -237,6 +240,7 @@ executable fay-docs
main-is: Docs.hs
other-modules: Text.Blaze.Extra
build-depends: base >= 4 && < 5,
ghc-paths,
mtl,
haskell-src-exts,
aeson,
Expand Down
29 changes: 19 additions & 10 deletions src/Language/Fay/Compiler.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
Expand All @@ -22,6 +23,14 @@ module Language.Fay.Compiler
,compileToplevelModule)
where

import Language.Fay.Compiler.FFI
import Language.Fay.Compiler.Misc
import Language.Fay.Compiler.Optimizer
import Language.Fay.Print (printJSString)
import qualified Language.Fay.Stdlib as Stdlib (enumFromThenTo,enumFromTo)
import Language.Fay.Types


import Control.Applicative
import Control.Monad.Error
import Control.Monad.IO
Expand All @@ -32,17 +41,10 @@ import Data.List.Extra
import Data.Map (Map)
import qualified Data.Map as M
import Data.Maybe
import Language.Fay.Compiler.FFI
import Language.Fay.Compiler.Misc
import Language.Fay.Compiler.Optimizer
import Language.Fay.Print (printJSString)
import qualified Language.Fay.Stdlib as Stdlib (enumFromThenTo,
enumFromTo)
import Language.Fay.Types
import qualified GHC.Paths as GHCPaths
import Language.Haskell.Exts
import System.Directory (doesFileExist)
import System.FilePath ((</>))

import System.Process.Extra

--------------------------------------------------------------------------------
Expand Down Expand Up @@ -206,20 +208,27 @@ initialPass_dataDecl _ _decl constructors =

typecheck :: Maybe FilePath -> [FilePath] -> [String] -> Bool -> String -> Compile ()
typecheck packageConf includeDirs ghcFlags wall fp = do
res <- liftIO $ readAllFromProcess' "ghc" (
res <- liftIO $ readAllFromProcess' GHCPaths.ghc (
["-fno-code"
,"-package fay"
,"-XNoImplicitPrelude"
,"-main-is"
,"Language.Fay.DummyMain"
,fp]
++ [ "-package-conf=" ++ pk | Just pk <- [packageConf] ]
++ [ ghcPackageDbFlag ++ "=" ++ pk | Just pk <- [packageConf] ]
++ map ("-i" ++) includeDirs ++ ghcFlags ++ wallF) ""
either error (warn . fst) res
where
wallF | wall = ["-Wall"]
| otherwise = []

ghcPackageDbFlag :: String
#if __GLASGOW_HASKELL__ >= 706
ghcPackageDbFlag = "-package-db"
#else
ghcPackageDbFlag = "-package-conf"
#endif

--------------------------------------------------------------------------------
-- Compilers

Expand Down

0 comments on commit 4c0dbc9

Please sign in to comment.