module GHC.Driver.IncludeSpecs
( IncludeSpecs(..)
, addGlobalInclude
, addQuoteInclude
, addImplicitQuoteInclude
, flattenIncludes
) where
import GHC.Prelude
data IncludeSpecs
= IncludeSpecs { IncludeSpecs -> [String]
includePathsQuote :: [String]
, IncludeSpecs -> [String]
includePathsGlobal :: [String]
, IncludeSpecs -> [String]
includePathsQuoteImplicit :: [String]
}
deriving Int -> IncludeSpecs -> ShowS
[IncludeSpecs] -> ShowS
IncludeSpecs -> String
(Int -> IncludeSpecs -> ShowS)
-> (IncludeSpecs -> String)
-> ([IncludeSpecs] -> ShowS)
-> Show IncludeSpecs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IncludeSpecs -> ShowS
showsPrec :: Int -> IncludeSpecs -> ShowS
$cshow :: IncludeSpecs -> String
show :: IncludeSpecs -> String
$cshowList :: [IncludeSpecs] -> ShowS
showList :: [IncludeSpecs] -> ShowS
Show
addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs
addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs
addGlobalInclude IncludeSpecs
spec [String]
paths = let f :: [String]
f = IncludeSpecs -> [String]
includePathsGlobal IncludeSpecs
spec
in IncludeSpecs
spec { includePathsGlobal = f ++ paths }
addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
addQuoteInclude IncludeSpecs
spec [String]
paths = let f :: [String]
f = IncludeSpecs -> [String]
includePathsQuote IncludeSpecs
spec
in IncludeSpecs
spec { includePathsQuote = f ++ paths }
addImplicitQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
addImplicitQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
addImplicitQuoteInclude IncludeSpecs
spec [String]
paths = let f :: [String]
f = IncludeSpecs -> [String]
includePathsQuoteImplicit IncludeSpecs
spec
in IncludeSpecs
spec { includePathsQuoteImplicit = f ++ paths }
flattenIncludes :: IncludeSpecs -> [String]
flattenIncludes :: IncludeSpecs -> [String]
flattenIncludes IncludeSpecs
specs =
IncludeSpecs -> [String]
includePathsQuote IncludeSpecs
specs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
IncludeSpecs -> [String]
includePathsQuoteImplicit IncludeSpecs
specs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
IncludeSpecs -> [String]
includePathsGlobal IncludeSpecs
specs