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

196 lines
5.4 KiB
Haskell
Raw Normal View History

2012-02-14 02:33:27 +00:00
{-# LANGUAGE FlexibleInstances #-}
2013-05-17 01:00:01 +00:00
module Language.Haskell.GhcMod.Types where
2010-04-30 09:36:31 +00:00
2014-04-21 05:58:25 +00:00
import Data.List (intercalate)
2013-05-20 05:28:56 +00:00
-- | Output style.
2013-09-05 05:35:28 +00:00
data OutputStyle = LispStyle -- ^ S expression style.
| PlainStyle -- ^ Plain textstyle.
2012-02-14 01:21:48 +00:00
2013-09-05 05:35:28 +00:00
-- | The type for line separator. Historically, a Null string is used.
2013-09-03 05:40:51 +00:00
newtype LineSeparator = LineSeparator String
2010-04-30 09:36:31 +00:00
data Options = Options {
2013-09-03 05:40:51 +00:00
outputStyle :: OutputStyle
, hlintOpts :: [String]
2014-04-23 01:41:28 +00:00
, ghcOpts :: [GHCOption]
2013-09-05 05:35:28 +00:00
-- | If 'True', 'browse' also returns operators.
2013-09-03 05:40:51 +00:00
, operators :: Bool
2013-05-20 05:28:56 +00:00
-- | If 'True', 'browse' also returns types.
2013-09-03 05:40:51 +00:00
, detailed :: Bool
-- | If 'True', 'browse' will return fully qualified name
, qualified :: Bool
2013-09-05 05:35:28 +00:00
-- | Line separator string.
2013-09-03 05:40:51 +00:00
, lineSeparator :: LineSeparator
2012-02-27 02:23:56 +00:00
}
2013-05-20 05:28:56 +00:00
-- | A default 'Options'.
2012-02-27 02:23:56 +00:00
defaultOptions :: Options
defaultOptions = Options {
2013-09-03 05:40:51 +00:00
outputStyle = PlainStyle
, hlintOpts = []
, ghcOpts = []
, operators = False
, detailed = False
, qualified = False
2013-09-03 05:40:51 +00:00
, lineSeparator = LineSeparator "\0"
2010-04-30 09:36:31 +00:00
}
2012-02-14 02:33:27 +00:00
----------------------------------------------------------------
2012-02-14 07:09:53 +00:00
2014-04-22 02:28:27 +00:00
type Builder = String -> String
-- |
--
-- >>> replace '"' "\\\"" "foo\"bar" ""
-- "foo\\\"bar"
replace :: Char -> String -> String -> Builder
replace _ _ [] = id
replace c cs (x:xs)
| x == c = (cs ++) . replace c cs xs
| otherwise = (x :) . replace c cs xs
inter :: Char -> [Builder] -> Builder
inter _ [] = id
inter c bs = foldr1 (\x y -> x . (c:) . y) bs
2012-02-14 02:33:27 +00:00
convert :: ToString a => Options -> a -> String
2014-04-22 02:28:27 +00:00
convert opt@Options { outputStyle = LispStyle } x = toLisp opt x "\n"
2014-05-10 15:27:26 +00:00
convert opt@Options { outputStyle = PlainStyle } x
| str == "\n" = ""
| otherwise = str
where
str = toPlain opt x "\n"
2012-02-14 02:33:27 +00:00
class ToString a where
2014-04-22 02:28:27 +00:00
toLisp :: Options -> a -> Builder
toPlain :: Options -> a -> Builder
lineSep :: Options -> String
lineSep opt = lsep
where
LineSeparator lsep = lineSeparator opt
2012-02-14 02:33:27 +00:00
2014-04-21 00:45:00 +00:00
-- |
--
2014-04-22 02:28:27 +00:00
-- >>> toLisp defaultOptions "fo\"o" ""
-- "\"fo\\\"o\""
2014-04-22 02:28:27 +00:00
-- >>> toPlain defaultOptions "foo" ""
-- "foo"
2014-04-21 00:45:00 +00:00
instance ToString String where
toLisp opt = quote opt
toPlain opt = replace '\n' (lineSep opt)
2014-04-21 00:45:00 +00:00
-- |
--
2014-04-22 02:28:27 +00:00
-- >>> toLisp defaultOptions ["foo", "bar", "ba\"z"] ""
-- "(\"foo\" \"bar\" \"ba\\\"z\")"
2014-04-22 02:28:27 +00:00
-- >>> toPlain defaultOptions ["foo", "bar", "baz"] ""
-- "foo\nbar\nbaz"
2012-02-14 02:33:27 +00:00
instance ToString [String] where
2014-04-22 02:28:27 +00:00
toLisp opt = toSexp1 opt
toPlain opt = inter '\n' . map (toPlain opt)
2012-02-14 02:33:27 +00:00
2014-04-21 00:45:00 +00:00
-- |
--
-- >>> let inp = [((1,2,3,4),"foo"),((5,6,7,8),"bar")] :: [((Int,Int,Int,Int),String)]
2014-04-22 02:28:27 +00:00
-- >>> toLisp defaultOptions inp ""
-- "((1 2 3 4 \"foo\") (5 6 7 8 \"bar\"))"
2014-04-22 02:28:27 +00:00
-- >>> toPlain defaultOptions inp ""
-- "1 2 3 4 \"foo\"\n5 6 7 8 \"bar\""
2012-02-14 02:33:27 +00:00
instance ToString [((Int,Int,Int,Int),String)] where
2014-04-22 02:28:27 +00:00
toLisp opt = toSexp2 . map toS
2012-02-14 02:33:27 +00:00
where
2014-04-22 02:28:27 +00:00
toS x = ('(' :) . tupToString opt x . (')' :)
toPlain opt = inter '\n' . map (tupToString opt)
toSexp1 :: Options -> [String] -> Builder
toSexp1 opt ss = ('(' :) . inter ' ' (map (quote opt) ss) . (')' :)
toSexp2 :: [Builder] -> Builder
toSexp2 ss = ('(' :) . (inter ' ' ss) . (')' :)
tupToString :: Options -> ((Int,Int,Int,Int),String) -> Builder
tupToString opt ((a,b,c,d),s) = (show a ++) . (' ' :)
. (show b ++) . (' ' :)
. (show c ++) . (' ' :)
. (show d ++) . (' ' :)
. quote opt s -- fixme: quote is not necessary
quote :: Options -> String -> Builder
quote opt str = ("\"" ++) . (quote' str ++) . ("\"" ++)
where
lsep = lineSep opt
quote' [] = []
quote' (x:xs)
| x == '\n' = lsep ++ quote' xs
| x == '\\' = "\\\\" ++ quote' xs
| x == '"' = "\\\"" ++ quote' xs
| otherwise = x : quote' xs
----------------------------------------------------------------
2013-09-05 05:35:28 +00:00
-- | The environment where this library is used.
data Cradle = Cradle {
2013-09-05 05:35:28 +00:00
-- | The directory where this library is executed.
cradleCurrentDir :: FilePath
-- | The project root directory.
, cradleRootDir :: FilePath
2013-09-05 05:35:28 +00:00
-- | The file name of the found cabal file.
, cradleCabalFile :: Maybe FilePath
-- | Package database stack
, cradlePkgDbStack :: [GhcPkgDb]
2013-03-05 01:22:33 +00:00
} deriving (Eq, Show)
----------------------------------------------------------------
-- | GHC package database flags.
data GhcPkgDb = GlobalDb | UserDb | PackageDb String deriving (Eq, Show)
2013-09-19 06:58:50 +00:00
-- | A single GHC command line option.
type GHCOption = String
2013-09-19 06:58:50 +00:00
-- | An include directory for modules.
type IncludeDir = FilePath
2013-09-16 00:56:08 +00:00
2013-09-19 06:58:50 +00:00
-- | 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]
2013-09-05 05:35:28 +00:00
-- | Haskell expression.
2013-05-20 05:28:56 +00:00
type Expression = String
2013-09-05 05:35:28 +00:00
-- | Module name.
2013-05-20 05:28:56 +00:00
type ModuleString = String
2013-09-19 06:58:50 +00:00
-- | Option information for GHC
data CompilerOptions = CompilerOptions {
ghcOptions :: [GHCOption] -- ^ Command line options
, includeDirs :: [IncludeDir] -- ^ Include directories for modules
, depPackages :: [Package] -- ^ Dependent package names
2013-09-20 02:21:31 +00:00
} deriving (Eq, Show)