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

107 lines
2.9 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
2013-05-20 05:28:56 +00:00
-- | Output style.
data OutputStyle = LispStyle -- ^ S expression style
| PlainStyle -- ^ Plain textstyle
2012-02-14 01:21:48 +00:00
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]
, ghcOpts :: [String]
, 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
2013-05-20 05:28:56 +00:00
-- | Whether or not Template Haskell should be expanded.
2013-09-03 05:40:51 +00:00
, expandSplice :: Bool
2013-05-20 05:28:56 +00:00
-- | The sandbox directory.
2013-09-03 05:40:51 +00:00
, sandbox :: Maybe FilePath
, 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
, expandSplice = False
, sandbox = Nothing
, 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
2012-02-14 02:33:27 +00:00
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")
----------------------------------------------------------------
2013-05-20 05:28:56 +00:00
-- | The environment where this library is used
data Cradle = Cradle {
2013-05-20 05:28:56 +00:00
-- | The directory where this library is executed
2013-03-04 09:11:09 +00:00
cradleCurrentDir :: FilePath
2013-05-20 05:28:56 +00:00
-- | The directory where a cabal file is found
2013-03-04 09:11:09 +00:00
, cradleCabalDir :: Maybe FilePath
2013-05-20 05:28:56 +00:00
-- | The file name of the found cabal file
2013-03-04 09:11:09 +00:00
, cradleCabalFile :: Maybe FilePath
2013-05-20 05:28:56 +00:00
-- | The sandbox directory (e.g. \"\/foo\/bar\/packages-\<ver\>.conf/\")
2013-03-04 09:11:09 +00:00
, cradlePackageConf :: Maybe FilePath
2013-03-05 01:22:33 +00:00
} deriving (Eq, Show)
----------------------------------------------------------------
-- | A single GHC option, as it would appear on the command line
type GHCOption = String
type IncludeDir = FilePath
type Package = String
2013-05-20 05:28:56 +00:00
-- | GHC version in 'String'
type GHCVersion = String
-- | Haskell expression
type Expression = String
-- | Module name
type ModuleString = String
data CheckSpeed = Slow | Fast