{-# LANGUAGE CPP #-}
module DriverPhases (
HscSource(..), isHsBootOrSig, isHsigFile, hscSourceString,
Phase(..),
happensBefore, eqPhase, anyHsc, isStopLn,
startPhase,
phaseInputExt,
isHaskellishSuffix,
isHaskellSrcSuffix,
isBackpackishSuffix,
isObjectSuffix,
isCishSuffix,
isDynLibSuffix,
isHaskellUserSrcSuffix,
isHaskellSigSuffix,
isSourceSuffix,
isHaskellishTarget,
isHaskellishFilename,
isHaskellSrcFilename,
isHaskellSigFilename,
isObjectFilename,
isCishFilename,
isDynLibFilename,
isHaskellUserSrcFilename,
isSourceFilename
) where
#include "HsVersions.h"
import GhcPrelude
import {-# SOURCE #-} DynFlags
import Outputable
import Platform
import System.FilePath
import Binary
import Util
data HscSource
= HsSrcFile | HsBootFile | HsigFile
deriving( HscSource -> HscSource -> Bool
(HscSource -> HscSource -> Bool)
-> (HscSource -> HscSource -> Bool) -> Eq HscSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HscSource -> HscSource -> Bool
$c/= :: HscSource -> HscSource -> Bool
== :: HscSource -> HscSource -> Bool
$c== :: HscSource -> HscSource -> Bool
Eq, Eq HscSource
Eq HscSource =>
(HscSource -> HscSource -> Ordering)
-> (HscSource -> HscSource -> Bool)
-> (HscSource -> HscSource -> Bool)
-> (HscSource -> HscSource -> Bool)
-> (HscSource -> HscSource -> Bool)
-> (HscSource -> HscSource -> HscSource)
-> (HscSource -> HscSource -> HscSource)
-> Ord HscSource
HscSource -> HscSource -> Bool
HscSource -> HscSource -> Ordering
HscSource -> HscSource -> HscSource
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: HscSource -> HscSource -> HscSource
$cmin :: HscSource -> HscSource -> HscSource
max :: HscSource -> HscSource -> HscSource
$cmax :: HscSource -> HscSource -> HscSource
>= :: HscSource -> HscSource -> Bool
$c>= :: HscSource -> HscSource -> Bool
> :: HscSource -> HscSource -> Bool
$c> :: HscSource -> HscSource -> Bool
<= :: HscSource -> HscSource -> Bool
$c<= :: HscSource -> HscSource -> Bool
< :: HscSource -> HscSource -> Bool
$c< :: HscSource -> HscSource -> Bool
compare :: HscSource -> HscSource -> Ordering
$ccompare :: HscSource -> HscSource -> Ordering
$cp1Ord :: Eq HscSource
Ord, Int -> HscSource -> ShowS
[HscSource] -> ShowS
HscSource -> String
(Int -> HscSource -> ShowS)
-> (HscSource -> String)
-> ([HscSource] -> ShowS)
-> Show HscSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HscSource] -> ShowS
$cshowList :: [HscSource] -> ShowS
show :: HscSource -> String
$cshow :: HscSource -> String
showsPrec :: Int -> HscSource -> ShowS
$cshowsPrec :: Int -> HscSource -> ShowS
Show )
instance Binary HscSource where
put_ :: BinHandle -> HscSource -> IO ()
put_ bh :: BinHandle
bh HsSrcFile = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 0
put_ bh :: BinHandle
bh HsBootFile = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 1
put_ bh :: BinHandle
bh HsigFile = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 2
get :: BinHandle -> IO HscSource
get bh :: BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
0 -> HscSource -> IO HscSource
forall (m :: * -> *) a. Monad m => a -> m a
return HscSource
HsSrcFile
1 -> HscSource -> IO HscSource
forall (m :: * -> *) a. Monad m => a -> m a
return HscSource
HsBootFile
_ -> HscSource -> IO HscSource
forall (m :: * -> *) a. Monad m => a -> m a
return HscSource
HsigFile
hscSourceString :: HscSource -> String
hscSourceString :: HscSource -> String
hscSourceString HsSrcFile = ""
hscSourceString HsBootFile = "[boot]"
hscSourceString HsigFile = "[sig]"
isHsBootOrSig :: HscSource -> Bool
isHsBootOrSig :: HscSource -> Bool
isHsBootOrSig HsBootFile = Bool
True
isHsBootOrSig HsigFile = Bool
True
isHsBootOrSig _ = Bool
False
isHsigFile :: HscSource -> Bool
isHsigFile :: HscSource -> Bool
isHsigFile HsigFile = Bool
True
isHsigFile _ = Bool
False
data Phase
= Unlit HscSource
| Cpp HscSource
| HsPp HscSource
| Hsc HscSource
| Ccxx
| Cc
| Cobjc
| Cobjcxx
| HCc
| Splitter
| SplitAs
| As Bool
| LlvmOpt
| LlvmLlc
| LlvmMangle
| CmmCpp
| Cmm
| MergeForeign
| StopLn
deriving (Phase -> Phase -> Bool
(Phase -> Phase -> Bool) -> (Phase -> Phase -> Bool) -> Eq Phase
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Phase -> Phase -> Bool
$c/= :: Phase -> Phase -> Bool
== :: Phase -> Phase -> Bool
$c== :: Phase -> Phase -> Bool
Eq, Int -> Phase -> ShowS
[Phase] -> ShowS
Phase -> String
(Int -> Phase -> ShowS)
-> (Phase -> String) -> ([Phase] -> ShowS) -> Show Phase
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Phase] -> ShowS
$cshowList :: [Phase] -> ShowS
show :: Phase -> String
$cshow :: Phase -> String
showsPrec :: Int -> Phase -> ShowS
$cshowsPrec :: Int -> Phase -> ShowS
Show)
instance Outputable Phase where
ppr :: Phase -> SDoc
ppr p :: Phase
p = String -> SDoc
text (Phase -> String
forall a. Show a => a -> String
show Phase
p)
anyHsc :: Phase
anyHsc :: Phase
anyHsc = HscSource -> Phase
Hsc (String -> HscSource
forall a. String -> a
panic "anyHsc")
isStopLn :: Phase -> Bool
isStopLn :: Phase -> Bool
isStopLn StopLn = Bool
True
isStopLn _ = Bool
False
eqPhase :: Phase -> Phase -> Bool
eqPhase :: Phase -> Phase -> Bool
eqPhase (Unlit _) (Unlit _) = Bool
True
eqPhase (Cpp _) (Cpp _) = Bool
True
eqPhase (HsPp _) (HsPp _) = Bool
True
eqPhase (Hsc _) (Hsc _) = Bool
True
eqPhase Cc Cc = Bool
True
eqPhase Cobjc Cobjc = Bool
True
eqPhase HCc HCc = Bool
True
eqPhase Splitter Splitter = Bool
True
eqPhase SplitAs SplitAs = Bool
True
eqPhase (As x :: Bool
x) (As y :: Bool
y) = Bool
x Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool
y
eqPhase LlvmOpt LlvmOpt = Bool
True
eqPhase LlvmLlc LlvmLlc = Bool
True
eqPhase LlvmMangle LlvmMangle = Bool
True
eqPhase CmmCpp CmmCpp = Bool
True
eqPhase Cmm Cmm = Bool
True
eqPhase MergeForeign MergeForeign = Bool
True
eqPhase StopLn StopLn = Bool
True
eqPhase Ccxx Ccxx = Bool
True
eqPhase Cobjcxx Cobjcxx = Bool
True
eqPhase _ _ = Bool
False
happensBefore :: DynFlags -> Phase -> Phase -> Bool
happensBefore :: DynFlags -> Phase -> Phase -> Bool
happensBefore dflags :: DynFlags
dflags p1 :: Phase
p1 p2 :: Phase
p2 = Phase
p1 Phase -> Phase -> Bool
`happensBefore'` Phase
p2
where StopLn happensBefore' :: Phase -> Phase -> Bool
`happensBefore'` _ = Bool
False
x :: Phase
x `happensBefore'` y :: Phase
y = Phase
after_x Phase -> Phase -> Bool
`eqPhase` Phase
y
Bool -> Bool -> Bool
|| Phase
after_x Phase -> Phase -> Bool
`happensBefore'` Phase
y
where after_x :: Phase
after_x = DynFlags -> Phase -> Phase
nextPhase DynFlags
dflags Phase
x
nextPhase :: DynFlags -> Phase -> Phase
nextPhase :: DynFlags -> Phase -> Phase
nextPhase dflags :: DynFlags
dflags p :: Phase
p
= case Phase
p of
Unlit sf :: HscSource
sf -> HscSource -> Phase
Cpp HscSource
sf
Cpp sf :: HscSource
sf -> HscSource -> Phase
HsPp HscSource
sf
HsPp sf :: HscSource
sf -> HscSource -> Phase
Hsc HscSource
sf
Hsc _ -> Phase
maybeHCc
Splitter -> Phase
SplitAs
LlvmOpt -> Phase
LlvmLlc
LlvmLlc -> Phase
LlvmMangle
LlvmMangle -> Bool -> Phase
As Bool
False
SplitAs -> Phase
MergeForeign
As _ -> Phase
MergeForeign
Ccxx -> Bool -> Phase
As Bool
False
Cc -> Bool -> Phase
As Bool
False
Cobjc -> Bool -> Phase
As Bool
False
Cobjcxx -> Bool -> Phase
As Bool
False
CmmCpp -> Phase
Cmm
Cmm -> Phase
maybeHCc
HCc -> Bool -> Phase
As Bool
False
MergeForeign -> Phase
StopLn
StopLn -> String -> Phase
forall a. String -> a
panic "nextPhase: nothing after StopLn"
where maybeHCc :: Phase
maybeHCc = if Platform -> Bool
platformUnregisterised (DynFlags -> Platform
targetPlatform DynFlags
dflags)
then Phase
HCc
else Bool -> Phase
As Bool
False
startPhase :: String -> Phase
startPhase :: String -> Phase
startPhase "lhs" = HscSource -> Phase
Unlit HscSource
HsSrcFile
startPhase "lhs-boot" = HscSource -> Phase
Unlit HscSource
HsBootFile
startPhase "lhsig" = HscSource -> Phase
Unlit HscSource
HsigFile
startPhase "hs" = HscSource -> Phase
Cpp HscSource
HsSrcFile
startPhase "hs-boot" = HscSource -> Phase
Cpp HscSource
HsBootFile
startPhase "hsig" = HscSource -> Phase
Cpp HscSource
HsigFile
startPhase "hscpp" = HscSource -> Phase
HsPp HscSource
HsSrcFile
startPhase "hspp" = HscSource -> Phase
Hsc HscSource
HsSrcFile
startPhase "hc" = Phase
HCc
startPhase "c" = Phase
Cc
startPhase "cpp" = Phase
Ccxx
startPhase "C" = Phase
Cc
startPhase "m" = Phase
Cobjc
startPhase "M" = Phase
Cobjcxx
startPhase "mm" = Phase
Cobjcxx
startPhase "cc" = Phase
Ccxx
startPhase "cxx" = Phase
Ccxx
startPhase "split_s" = Phase
Splitter
startPhase "s" = Bool -> Phase
As Bool
False
startPhase "S" = Bool -> Phase
As Bool
True
startPhase "ll" = Phase
LlvmOpt
startPhase "bc" = Phase
LlvmLlc
startPhase "lm_s" = Phase
LlvmMangle
startPhase "o" = Phase
StopLn
startPhase "cmm" = Phase
CmmCpp
startPhase "cmmcpp" = Phase
Cmm
startPhase _ = Phase
StopLn
phaseInputExt :: Phase -> String
phaseInputExt :: Phase -> String
phaseInputExt (Unlit HsSrcFile) = "lhs"
phaseInputExt (Unlit HsBootFile) = "lhs-boot"
phaseInputExt (Unlit HsigFile) = "lhsig"
phaseInputExt (Cpp _) = "lpp"
phaseInputExt (HsPp _) = "hscpp"
phaseInputExt (Hsc _) = "hspp"
phaseInputExt HCc = "hc"
phaseInputExt Ccxx = "cpp"
phaseInputExt Cobjc = "m"
phaseInputExt Cobjcxx = "mm"
phaseInputExt Cc = "c"
phaseInputExt Splitter = "split_s"
phaseInputExt (As True) = "S"
phaseInputExt (As False) = "s"
phaseInputExt LlvmOpt = "ll"
phaseInputExt LlvmLlc = "bc"
phaseInputExt LlvmMangle = "lm_s"
phaseInputExt SplitAs = "split_s"
phaseInputExt CmmCpp = "cmmcpp"
phaseInputExt Cmm = "cmm"
phaseInputExt MergeForeign = "o"
phaseInputExt StopLn = "o"
haskellish_src_suffixes, backpackish_suffixes, haskellish_suffixes, cish_suffixes,
haskellish_user_src_suffixes, haskellish_sig_suffixes
:: [String]
haskellish_src_suffixes :: [String]
haskellish_src_suffixes = [String]
haskellish_user_src_suffixes [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[ "hspp", "hscpp" ]
haskellish_suffixes :: [String]
haskellish_suffixes = [String]
haskellish_src_suffixes [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[ "hc", "cmm", "cmmcpp" ]
cish_suffixes :: [String]
cish_suffixes = [ "c", "cpp", "C", "cc", "cxx", "s", "S", "ll", "bc", "lm_s", "m", "M", "mm" ]
haskellish_user_src_suffixes :: [String]
haskellish_user_src_suffixes =
[String]
haskellish_sig_suffixes [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ "hs", "lhs", "hs-boot", "lhs-boot" ]
haskellish_sig_suffixes :: [String]
haskellish_sig_suffixes = [ "hsig", "lhsig" ]
backpackish_suffixes :: [String]
backpackish_suffixes = [ "bkp" ]
objish_suffixes :: Platform -> [String]
objish_suffixes :: Platform -> [String]
objish_suffixes platform :: Platform
platform = case Platform -> OS
platformOS Platform
platform of
OSMinGW32 -> [ "o", "O", "obj", "OBJ" ]
_ -> [ "o" ]
dynlib_suffixes :: Platform -> [String]
dynlib_suffixes :: Platform -> [String]
dynlib_suffixes platform :: Platform
platform = case Platform -> OS
platformOS Platform
platform of
OSMinGW32 -> ["dll", "DLL"]
OSDarwin -> ["dylib", "so"]
_ -> ["so"]
isHaskellishSuffix, isBackpackishSuffix, isHaskellSrcSuffix, isCishSuffix,
isHaskellUserSrcSuffix, isHaskellSigSuffix
:: String -> Bool
isHaskellishSuffix :: String -> Bool
isHaskellishSuffix s :: String
s = String
s String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
haskellish_suffixes
isBackpackishSuffix :: String -> Bool
isBackpackishSuffix s :: String
s = String
s String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
backpackish_suffixes
isHaskellSigSuffix :: String -> Bool
isHaskellSigSuffix s :: String
s = String
s String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
haskellish_sig_suffixes
isHaskellSrcSuffix :: String -> Bool
isHaskellSrcSuffix s :: String
s = String
s String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
haskellish_src_suffixes
isCishSuffix :: String -> Bool
isCishSuffix s :: String
s = String
s String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
cish_suffixes
isHaskellUserSrcSuffix :: String -> Bool
isHaskellUserSrcSuffix s :: String
s = String
s String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
haskellish_user_src_suffixes
isObjectSuffix, isDynLibSuffix :: Platform -> String -> Bool
isObjectSuffix :: Platform -> String -> Bool
isObjectSuffix platform :: Platform
platform s :: String
s = String
s String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Platform -> [String]
objish_suffixes Platform
platform
isDynLibSuffix :: Platform -> String -> Bool
isDynLibSuffix platform :: Platform
platform s :: String
s = String
s String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Platform -> [String]
dynlib_suffixes Platform
platform
isSourceSuffix :: String -> Bool
isSourceSuffix :: String -> Bool
isSourceSuffix suff :: String
suff = String -> Bool
isHaskellishSuffix String
suff
Bool -> Bool -> Bool
|| String -> Bool
isCishSuffix String
suff
Bool -> Bool -> Bool
|| String -> Bool
isBackpackishSuffix String
suff
isHaskellishTarget :: (String, Maybe Phase) -> Bool
isHaskellishTarget :: (String, Maybe Phase) -> Bool
isHaskellishTarget (f :: String
f,Nothing) =
String -> Bool
looksLikeModuleName String
f Bool -> Bool -> Bool
|| String -> Bool
isHaskellSrcFilename String
f Bool -> Bool -> Bool
|| Bool -> Bool
not (String -> Bool
hasExtension String
f)
isHaskellishTarget (_,Just phase :: Phase
phase) =
Phase
phase Phase -> [Phase] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [ Bool -> Phase
As Bool
True, Bool -> Phase
As Bool
False, Phase
Cc, Phase
Cobjc, Phase
Cobjcxx, Phase
CmmCpp, Phase
Cmm
, Phase
StopLn]
isHaskellishFilename, isHaskellSrcFilename, isCishFilename,
isHaskellUserSrcFilename, isSourceFilename, isHaskellSigFilename
:: FilePath -> Bool
isHaskellishFilename :: String -> Bool
isHaskellishFilename f :: String
f = String -> Bool
isHaskellishSuffix (Int -> ShowS
forall a. Int -> [a] -> [a]
drop 1 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ ShowS
takeExtension String
f)
isHaskellSrcFilename :: String -> Bool
isHaskellSrcFilename f :: String
f = String -> Bool
isHaskellSrcSuffix (Int -> ShowS
forall a. Int -> [a] -> [a]
drop 1 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ ShowS
takeExtension String
f)
isCishFilename :: String -> Bool
isCishFilename f :: String
f = String -> Bool
isCishSuffix (Int -> ShowS
forall a. Int -> [a] -> [a]
drop 1 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ ShowS
takeExtension String
f)
isHaskellUserSrcFilename :: String -> Bool
isHaskellUserSrcFilename f :: String
f = String -> Bool
isHaskellUserSrcSuffix (Int -> ShowS
forall a. Int -> [a] -> [a]
drop 1 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ ShowS
takeExtension String
f)
isSourceFilename :: String -> Bool
isSourceFilename f :: String
f = String -> Bool
isSourceSuffix (Int -> ShowS
forall a. Int -> [a] -> [a]
drop 1 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ ShowS
takeExtension String
f)
isHaskellSigFilename :: String -> Bool
isHaskellSigFilename f :: String
f = String -> Bool
isHaskellSigSuffix (Int -> ShowS
forall a. Int -> [a] -> [a]
drop 1 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ ShowS
takeExtension String
f)
isObjectFilename, isDynLibFilename :: Platform -> FilePath -> Bool
isObjectFilename :: Platform -> String -> Bool
isObjectFilename platform :: Platform
platform f :: String
f = Platform -> String -> Bool
isObjectSuffix Platform
platform (Int -> ShowS
forall a. Int -> [a] -> [a]
drop 1 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ ShowS
takeExtension String
f)
isDynLibFilename :: Platform -> String -> Bool
isDynLibFilename platform :: Platform
platform f :: String
f = Platform -> String -> Bool
isDynLibSuffix Platform
platform (Int -> ShowS
forall a. Int -> [a] -> [a]
drop 1 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ ShowS
takeExtension String
f)