{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module HIE.Bios.Types where
import System.Exit
import System.IO
data BIOSVerbosity = Silent | Verbose
data CradleOpts = CradleOpts
{ cradleOptsVerbosity :: BIOSVerbosity
, cradleOptsHandle :: Maybe Handle
}
defaultCradleOpts :: CradleOpts
defaultCradleOpts = CradleOpts Silent Nothing
data OutputStyle = LispStyle
| PlainStyle
newtype LineSeparator = LineSeparator String
data Options = Options {
outputStyle :: OutputStyle
, hlintOpts :: [String]
, ghcOpts :: [String]
, operators :: Bool
, detailed :: Bool
, qualified :: Bool
, lineSeparator :: LineSeparator
}
defaultOptions :: Options
defaultOptions = Options {
outputStyle = PlainStyle
, hlintOpts = []
, ghcOpts = []
, operators = False
, detailed = False
, qualified = False
, lineSeparator = LineSeparator "\0"
}
type Builder = String -> String
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
convert :: ToString a => Options -> a -> String
convert opt@Options { outputStyle = LispStyle } x = toLisp opt x "\n"
convert opt@Options { outputStyle = PlainStyle } x
| str == "\n" = ""
| otherwise = str
where
str = toPlain opt x "\n"
class ToString a where
toLisp :: Options -> a -> Builder
toPlain :: Options -> a -> Builder
lineSep :: Options -> String
lineSep opt = lsep
where
LineSeparator lsep = lineSeparator opt
instance ToString String where
toLisp opt = quote opt
toPlain opt = replace '\n' (lineSep opt)
instance ToString [String] where
toLisp opt = toSexp1 opt
toPlain opt = inter '\n' . map (toPlain opt)
instance ToString [((Int,Int,Int,Int),String)] where
toLisp opt = toSexp2 . map toS
where
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
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
data Cradle = Cradle {
cradleRootDir :: FilePath
, cradleOptsProg :: CradleAction
} deriving (Show)
data CradleAction = CradleAction {
actionName :: String
, getDependencies :: IO [FilePath]
, getOptions :: FilePath -> IO (ExitCode, String, [String])
}
instance Show CradleAction where
show CradleAction { actionName = name } = "CradleAction: " ++ name
data CompilerOptions = CompilerOptions {
ghcOptions :: [String]
} deriving (Eq, Show)