module Language.Haskell.GhcMod.Types where
data OutputStyle = LispStyle
| PlainStyle
newtype LineSeparator = LineSeparator String
data Options = Options {
outputStyle :: OutputStyle
, hlintOpts :: [String]
, ghcOpts :: [String]
, operators :: Bool
, detailed :: Bool
, qualified :: Bool
, expandSplice :: Bool
, lineSeparator :: LineSeparator
, packageId :: Maybe String
}
defaultOptions :: Options
defaultOptions = Options {
outputStyle = PlainStyle
, hlintOpts = []
, ghcOpts = []
, operators = False
, detailed = False
, qualified = False
, expandSplice = False
, lineSeparator = LineSeparator "\0"
, packageId = Nothing
}
convert :: ToString a => Options -> a -> String
convert Options{ outputStyle = LispStyle } = toLisp
convert Options{ outputStyle = PlainStyle } = toPlain
class ToString a where
toLisp :: a -> String
toPlain :: a -> String
instance ToString [String] where
toLisp = addNewLine . toSexp True
toPlain = unlines
instance ToString [((Int,Int,Int,Int),String)] where
toLisp = addNewLine . toSexp False . map toS
where
toS x = "(" ++ tupToString x ++ ")"
toPlain = unlines . map tupToString
toSexp :: Bool -> [String] -> String
toSexp False ss = "(" ++ unwords ss ++ ")"
toSexp True ss = "(" ++ unwords (map quote ss) ++ ")"
tupToString :: ((Int,Int,Int,Int),String) -> String
tupToString ((a,b,c,d),s) = show a ++ " "
++ show b ++ " "
++ show c ++ " "
++ show d ++ " "
++ quote s
quote :: String -> String
quote x = "\"" ++ x ++ "\""
addNewLine :: String -> String
addNewLine = (++ "\n")
data Cradle = Cradle {
cradleCurrentDir :: FilePath
, cradleCabalDir :: Maybe FilePath
, cradleCabalFile :: Maybe FilePath
, cradlePackageDbOpts :: [GHCOption]
, cradlePackages :: [Package]
} deriving (Eq, Show)
type GHCOption = String
type IncludeDir = FilePath
type PackageBaseName = String
type Package = (PackageBaseName, Maybe String)
type Expression = String
type ModuleString = String
data CheckSpeed = Slow | Fast
data CompilerOptions = CompilerOptions {
ghcOptions :: [GHCOption]
, includeDirs :: [IncludeDir]
, depPackages :: [Package]
} deriving (Eq, Show)