ghc-mod/Language/Haskell/GhcMod/Types.hs

174 lines
4.6 KiB
Haskell

{-# LANGUAGE FlexibleInstances #-}
module Language.Haskell.GhcMod.Types where
import Data.List
-- | Output style.
data OutputStyle = LispStyle -- ^ S expression style.
| PlainStyle -- ^ Plain textstyle.
-- | The type for line separator. Historically, a Null string is used.
newtype LineSeparator = LineSeparator String
data Options = Options {
outputStyle :: OutputStyle
, hlintOpts :: [String]
, ghcOpts :: [String]
-- | If 'True', 'browse' also returns operators.
, operators :: Bool
-- | If 'True', 'browse' also returns types.
, detailed :: Bool
-- | If 'True', 'browse' will return fully qualified name
, qualified :: Bool
-- | Whether or not Template Haskell should be expanded.
, expandSplice :: Bool
-- | Line separator string.
, lineSeparator :: LineSeparator
-- | Package id of module
, packageId :: Maybe String
}
-- | A default 'Options'.
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
-- |
--
-- >>> toLisp "fo\"o"
-- "\"fo\\\"o\"\n"
-- >>> toPlain "foo"
-- "foo\n"
instance ToString String where
toLisp = addNewLine . quote
toPlain = addNewLine
-- |
--
-- >>> toLisp ["foo", "bar", "ba\"z"]
-- "(\"foo\" \"bar\" \"ba\\\"z\")\n"
-- >>> toPlain ["foo", "bar", "baz"]
-- "foo\nbar\nbaz\n"
instance ToString [String] where
toLisp = addNewLine . toSexp True
toPlain = unlines
-- |
--
-- >>> let inp = [((1,2,3,4),"foo"),((5,6,7,8),"bar")] :: [((Int,Int,Int,Int),String)]
-- >>> toLisp inp
-- "((1 2 3 4 \"foo\") (5 6 7 8 \"bar\"))\n"
-- >>> toPlain inp
-- "1 2 3 4 \"foo\"\n5 6 7 8 \"bar\"\n"
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 -- fixme: quote is not necessary
quote :: String -> String
quote x = "\"" ++ escape x ++ "\""
where
escape [] = []
escape ('"':ys) = '\\':'\"':escape ys
escape (y:ys) = y:escape ys
addNewLine :: String -> String
addNewLine = (++ "\n")
----------------------------------------------------------------
-- | The environment where this library is used.
data Cradle = Cradle {
-- | The directory where this library is executed.
cradleCurrentDir :: FilePath
-- | The project root directory.
, cradleRootDir :: FilePath
-- | The file name of the found cabal file.
, cradleCabalFile :: Maybe FilePath
-- | Package database stack
, cradlePkgDbStack :: [GhcPkgDb]
} deriving (Eq, Show)
----------------------------------------------------------------
-- | GHC package database flags.
data GhcPkgDb = GlobalDb | UserDb | PackageDb String deriving (Eq, Show)
-- | A single GHC command line option.
type GHCOption = String
-- | An include directory for modules.
type IncludeDir = FilePath
-- | A package name.
type PackageBaseName = String
-- | A package version.
type PackageVersion = String
-- | A package id.
type PackageId = String
-- | A package's name, verson and id.
type Package = (PackageBaseName, PackageVersion, PackageId)
pkgName :: Package -> PackageBaseName
pkgName (n,_,_) = n
pkgVer :: Package -> PackageVersion
pkgVer (_,v,_) = v
pkgId :: Package -> PackageId
pkgId (_,_,i) = i
showPkg :: Package -> String
showPkg (n,v,_) = intercalate "-" [n,v]
showPkgId :: Package -> String
showPkgId (n,v,i) = intercalate "-" [n,v,i]
-- | Haskell expression.
type Expression = String
-- | Module name.
type ModuleString = String
-- | Option information for GHC
data CompilerOptions = CompilerOptions {
ghcOptions :: [GHCOption] -- ^ Command line options
, includeDirs :: [IncludeDir] -- ^ Include directories for modules
, depPackages :: [Package] -- ^ Dependent package names
} deriving (Eq, Show)