Commit 049796bc authored by Vaibhav Sagar's avatar Vaibhav Sagar

Remove more CPP

parent 000ea0fb
{-# LANGUAGE CPP #-}
module IHaskell.Display.Charts () where module IHaskell.Display.Charts () where
import System.Directory import System.Directory
...@@ -34,7 +32,7 @@ chartData renderable format = do ...@@ -34,7 +32,7 @@ chartData renderable format = do
-- Write the PNG image. -- Write the PNG image.
let filename = ".ihaskell-chart.png" let filename = ".ihaskell-chart.png"
opts = def { _fo_format = format, _fo_size = (width, height) } opts = def { _fo_format = format, _fo_size = (width, height) }
mkFile opts filename renderable renderableToFile opts filename renderable
-- Convert to base64. -- Convert to base64.
imgData <- Char.readFile filename imgData <- Char.readFile filename
...@@ -42,8 +40,3 @@ chartData renderable format = do ...@@ -42,8 +40,3 @@ chartData renderable format = do
case format of case format of
PNG -> png width height $ base64 imgData PNG -> png width height $ base64 imgData
SVG -> svg $ Char.unpack imgData SVG -> svg $ Char.unpack imgData
#if MIN_VERSION_Chart_cairo(1,3,0)
mkFile opts filename renderable = renderableToFile opts filename renderable
#else
mkFile opts filename renderable = renderableToFile opts renderable filename
#endif
...@@ -63,11 +63,9 @@ import StringUtils (replace) ...@@ -63,11 +63,9 @@ import StringUtils (replace)
import CmdLineParser (warnMsg) import CmdLineParser (warnMsg)
#endif #endif
#if MIN_VERSION_ghc(8,0,1)
import GHC.LanguageExtensions import GHC.LanguageExtensions
type ExtensionFlag = Extension type ExtensionFlag = Extension
#endif
-- | A extension flag that can be set or unset. -- | A extension flag that can be set or unset.
data ExtFlag = SetFlag ExtensionFlag data ExtFlag = SetFlag ExtensionFlag
...@@ -265,11 +263,7 @@ initGhci sandboxPackages = do ...@@ -265,11 +263,7 @@ initGhci sandboxPackages = do
originalFlags <- getSessionDynFlags originalFlags <- getSessionDynFlags
let flag = flip xopt_set let flag = flip xopt_set
unflag = flip xopt_unset unflag = flip xopt_unset
#if MIN_VERSION_ghc(8,0,0)
dflags = flag ExtendedDefaultRules . unflag MonomorphismRestriction $ originalFlags dflags = flag ExtendedDefaultRules . unflag MonomorphismRestriction $ originalFlags
#else
dflags = flag Opt_ExtendedDefaultRules . unflag Opt_MonomorphismRestriction $ originalFlags
#endif
#if MIN_VERSION_ghc(8,2,0) #if MIN_VERSION_ghc(8,2,0)
pkgFlags = pkgFlags =
case sandboxPackages of case sandboxPackages of
......
{-# language NoImplicitPrelude, DoAndIfThenElse, OverloadedStrings, ExtendedDefaultRules #-} {-# language NoImplicitPrelude, DoAndIfThenElse, OverloadedStrings, ExtendedDefaultRules #-}
{-# LANGUAGE CPP #-}
-- | Description : Shell scripting wrapper using @Shelly@ for the @notebook@, and -- | Description : Shell scripting wrapper using @Shelly@ for the @notebook@, and
-- @console@ commands. -- @console@ commands.
...@@ -278,16 +277,6 @@ getIHaskellPath = do ...@@ -278,16 +277,6 @@ getIHaskellPath = do
Nothing -> error "ihaskell not on $PATH and not referenced relative to directory." Nothing -> error "ihaskell not on $PATH and not referenced relative to directory."
Just path -> return $ T.unpack $ SH.toTextIgnore path Just path -> return $ T.unpack $ SH.toTextIgnore path
else liftIO $ makeAbsolute f else liftIO $ makeAbsolute f
#if !MIN_VERSION_directory(1, 2, 2)
-- This is included in later versions of `directory`, but we cannot use later versions because GHC
-- library depends on a particular version of it.
makeAbsolute :: FilePath -> IO FilePath
makeAbsolute = fmap FP.normalise . absolutize
where
absolutize path -- avoid the call to `getCurrentDirectory` if we can
| FP.isRelative path = fmap (FP.</> path) getCurrentDirectory
| otherwise = return path
#endif
getSandboxPackageConf :: IO (Maybe String) getSandboxPackageConf :: IO (Maybe String)
getSandboxPackageConf = SH.shelly $ do getSandboxPackageConf = SH.shelly $ do
myPath <- getIHaskellPath myPath <- getIHaskellPath
......
{-# language NoImplicitPrelude, DoAndIfThenElse, OverloadedStrings, ExtendedDefaultRules #-} {-# language NoImplicitPrelude, DoAndIfThenElse, OverloadedStrings, ExtendedDefaultRules #-}
{-# LANGUAGE CPP #-}
module IHaskell.Test.Completion (testCompletions) where module IHaskell.Test.Completion (testCompletions) where
import Prelude import Prelude
...@@ -23,12 +22,8 @@ import IHaskell.Eval.Completion (complete, CompletionType(..), complet ...@@ -23,12 +22,8 @@ import IHaskell.Eval.Completion (complete, CompletionType(..), complet
completionTarget) completionTarget)
import IHaskell.Test.Util (replace, shouldBeAmong, ghc) import IHaskell.Test.Util (replace, shouldBeAmong, ghc)
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
-- | @readCompletePrompt "xs*ys"@ return @(xs, i)@ where i is the location of -- | @readCompletePrompt "xs*ys"@ return @(xs, i)@ where i is the location of
-- @'*'@ in the input string. -- @'*'@ in the input string.
readCompletePrompt :: String -> (String, Int) readCompletePrompt :: String -> (String, Int)
readCompletePrompt string = readCompletePrompt string =
case elemIndex '*' string of case elemIndex '*' string of
...@@ -197,7 +192,7 @@ inDirectory :: [Shelly.FilePath] -- ^ directories relative to temporary director ...@@ -197,7 +192,7 @@ inDirectory :: [Shelly.FilePath] -- ^ directories relative to temporary director
-> [Shelly.FilePath] -- ^ files relative to temporary directory -> [Shelly.FilePath] -- ^ files relative to temporary directory
-> (Shelly.FilePath -> Interpreter a) -> (Shelly.FilePath -> Interpreter a)
-> IO a -> IO a
-- | Run an Interpreter action, but first make a temporary directory -- | Run an Interpreter action, but first make a temporary directory
-- with some files and folder and cd to it. -- with some files and folder and cd to it.
inDirectory dirs files action = shelly $ withTmpDir $ \dirPath -> do inDirectory dirs files action = shelly $ withTmpDir $ \dirPath -> do
cd dirPath cd dirPath
......
{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE CPP #-}
module IHaskell.Test.Parser (testParser) where module IHaskell.Test.Parser (testParser) where
import Prelude import Prelude
...@@ -15,11 +14,6 @@ import IHaskell.Eval.Parser (parseString, getModuleName, unloc, layout ...@@ -15,11 +14,6 @@ import IHaskell.Eval.Parser (parseString, getModuleName, unloc, layout
CodeBlock(..), DirectiveType(..), StringLoc(..), PragmaType(..)) CodeBlock(..), DirectiveType(..), StringLoc(..), PragmaType(..))
import IHaskell.Eval.ParseShell (parseShell) import IHaskell.Eval.ParseShell (parseShell)
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
parses :: String -> IO [CodeBlock] parses :: String -> IO [CodeBlock]
parses str = map unloc <$> ghc (parseString str) parses str = map unloc <$> ghc (parseString str)
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment