Skip to content
Commits on Source (2)
...@@ -498,7 +498,7 @@ pRELUDE :: Module ...@@ -498,7 +498,7 @@ pRELUDE :: Module
pRELUDE = mkBaseModule_ pRELUDE_NAME pRELUDE = mkBaseModule_ pRELUDE_NAME
gHC_PRIM, gHC_TYPES, gHC_GENERICS, gHC_MAGIC, gHC_PRIM, gHC_TYPES, gHC_GENERICS, gHC_MAGIC,
gHC_CLASSES, gHC_BASE, gHC_ENUM, gHC_GHCI, gHC_CSTRING, gHC_CLASSES, gHC_BASE, gHC_ENUM, gHC_GHCI, gHC_GHCI_HELPERS, gHC_CSTRING,
gHC_SHOW, gHC_READ, gHC_NUM, gHC_MAYBE, gHC_INTEGER_TYPE, gHC_NATURAL, gHC_SHOW, gHC_READ, gHC_NUM, gHC_MAYBE, gHC_INTEGER_TYPE, gHC_NATURAL,
gHC_LIST, gHC_TUPLE, dATA_TUPLE, dATA_EITHER, dATA_STRING, gHC_LIST, gHC_TUPLE, dATA_TUPLE, dATA_EITHER, dATA_STRING,
dATA_FOLDABLE, dATA_TRAVERSABLE, dATA_FOLDABLE, dATA_TRAVERSABLE,
...@@ -520,6 +520,7 @@ gHC_CLASSES = mkPrimModule (fsLit "GHC.Classes") ...@@ -520,6 +520,7 @@ gHC_CLASSES = mkPrimModule (fsLit "GHC.Classes")
gHC_BASE = mkBaseModule (fsLit "GHC.Base") gHC_BASE = mkBaseModule (fsLit "GHC.Base")
gHC_ENUM = mkBaseModule (fsLit "GHC.Enum") gHC_ENUM = mkBaseModule (fsLit "GHC.Enum")
gHC_GHCI = mkBaseModule (fsLit "GHC.GHCi") gHC_GHCI = mkBaseModule (fsLit "GHC.GHCi")
gHC_GHCI_HELPERS= mkBaseModule (fsLit "GHC.GHCi.Helpers")
gHC_SHOW = mkBaseModule (fsLit "GHC.Show") gHC_SHOW = mkBaseModule (fsLit "GHC.Show")
gHC_READ = mkBaseModule (fsLit "GHC.Read") gHC_READ = mkBaseModule (fsLit "GHC.Read")
gHC_NUM = mkBaseModule (fsLit "GHC.Num") gHC_NUM = mkBaseModule (fsLit "GHC.Num")
......
...@@ -41,14 +41,18 @@ import qualified GHC ...@@ -41,14 +41,18 @@ import qualified GHC
import GhcMonad hiding (liftIO) import GhcMonad hiding (liftIO)
import Outputable hiding (printForUser, printForUserPartWay) import Outputable hiding (printForUser, printForUserPartWay)
import qualified Outputable import qualified Outputable
import OccName
import DynFlags import DynFlags
import FastString import FastString
import HscTypes import HscTypes
import SrcLoc import SrcLoc
import Module import Module
import RdrName (mkOrig)
import PrelNames (gHC_GHCI_HELPERS)
import GHCi import GHCi
import GHCi.RemoteTypes import GHCi.RemoteTypes
import HsSyn (ImportDecl, GhcPs, GhciLStmt, LHsDecl) import HsSyn (ImportDecl, GhcPs, GhciLStmt, LHsDecl)
import HsUtils
import Util import Util
import Exception import Exception
...@@ -488,13 +492,12 @@ revertCAFs = do ...@@ -488,13 +492,12 @@ revertCAFs = do
-- | Compile "hFlush stdout; hFlush stderr" once, so we can use it repeatedly -- | Compile "hFlush stdout; hFlush stderr" once, so we can use it repeatedly
initInterpBuffering :: Ghc (ForeignHValue, ForeignHValue) initInterpBuffering :: Ghc (ForeignHValue, ForeignHValue)
initInterpBuffering = do initInterpBuffering = do
nobuf <- compileGHCiExpr $ let mkHelperExpr :: OccName -> Ghc ForeignHValue
"do { System.IO.hSetBuffering System.IO.stdin System.IO.NoBuffering; " ++ mkHelperExpr occ =
" System.IO.hSetBuffering System.IO.stdout System.IO.NoBuffering; " ++ GHC.compileParsedExprRemote
" System.IO.hSetBuffering System.IO.stderr System.IO.NoBuffering }" $ GHC.nlHsVar $ RdrName.mkOrig gHC_GHCI_HELPERS occ
flush <- compileGHCiExpr $ nobuf <- mkHelperExpr $ mkVarOcc "disableBuffering"
"do { System.IO.hFlush System.IO.stdout; " ++ flush <- mkHelperExpr $ mkVarOcc "flushAll"
" System.IO.hFlush System.IO.stderr }"
return (nobuf, flush) return (nobuf, flush)
-- | Invoke "hFlush stdout; hFlush stderr" in the interpreter -- | Invoke "hFlush stdout; hFlush stderr" in the interpreter
...@@ -517,9 +520,13 @@ turnOffBuffering_ fhv = do ...@@ -517,9 +520,13 @@ turnOffBuffering_ fhv = do
mkEvalWrapper :: GhcMonad m => String -> [String] -> m ForeignHValue mkEvalWrapper :: GhcMonad m => String -> [String] -> m ForeignHValue
mkEvalWrapper progname args = mkEvalWrapper progname args =
compileGHCiExpr $ GHC.compileParsedExprRemote
"\\m -> System.Environment.withProgName " ++ show progname ++ $ evalWrapper `GHC.mkHsApp` nlHsString progname
"(System.Environment.withArgs " ++ show args ++ " m)" `GHC.mkHsApp` nlList (map nlHsString args)
where
nlHsString = nlHsLit . mkHsString
evalWrapper =
GHC.nlHsVar $ RdrName.mkOrig gHC_GHCI_HELPERS (mkVarOcc "evalWrapper")
compileGHCiExpr :: GhcMonad m => String -> m ForeignHValue compileGHCiExpr :: GhcMonad m => String -> m ForeignHValue
compileGHCiExpr expr = compileGHCiExpr expr =
......
-----------------------------------------------------------------------------
-- |
-- Module : GHC.GHCi.Helpers
-- Copyright : (c) The GHC Developers
-- License : see libraries/base/LICENSE
--
-- Maintainer : cvs-ghc@haskell.org
-- Stability : internal
-- Portability : non-portable (GHC Extensions)
--
-- Various helpers used by the GHCi shell.
--
-----------------------------------------------------------------------------
module GHC.GHCi.Helpers
( disableBuffering, flushAll
, evalWrapper
) where
import System.IO
import System.Environment
disableBuffering :: IO ()
disableBuffering = do
hSetBuffering stdin NoBuffering
hSetBuffering stdout NoBuffering
hSetBuffering stderr NoBuffering
flushAll :: IO ()
flushAll = do
hFlush stdout
hFlush stderr
evalWrapper :: String -> [String] -> IO a -> IO a
evalWrapper progName args m =
withProgName progName (withArgs args m)
...@@ -230,6 +230,7 @@ Library ...@@ -230,6 +230,7 @@ Library
GHC.Foreign GHC.Foreign
GHC.ForeignPtr GHC.ForeignPtr
GHC.GHCi GHC.GHCi
GHC.GHCi.Helpers
GHC.Generics GHC.Generics
GHC.IO GHC.IO
GHC.IO.Buffer GHC.IO.Buffer
......
...@@ -4,14 +4,14 @@ f :: Int -> a = _ ...@@ -4,14 +4,14 @@ f :: Int -> a = _
x :: Int = 1 x :: Int = 1
xs :: [Int] = [2,3] xs :: [Int] = [2,3]
xs :: [Int] = [2,3] xs :: [Int] = [2,3]
f :: Int -> a = _
x :: Int = 1 x :: Int = 1
f :: Int -> a = _
_result :: [a] = _ _result :: [a] = _
y = (_t1::a) y = (_t1::a)
y = 2 y = 2
xs :: [Int] = [2,3] xs :: [Int] = [2,3]
f :: Int -> Int = _
x :: Int = 1 x :: Int = 1
f :: Int -> Int = _
_result :: [Int] = _ _result :: [Int] = _
y :: Int = 2 y :: Int = 2
_t1 :: Int = 2 _t1 :: Int = 2
......
...@@ -3,7 +3,7 @@ _result :: (Bool, Bool, ()) = _ ...@@ -3,7 +3,7 @@ _result :: (Bool, Bool, ()) = _
a :: Bool = _ a :: Bool = _
b :: Bool = _ b :: Bool = _
c :: () = _ c :: () = _
b :: Bool = _
c :: () = _ c :: () = _
b :: Bool = _
a :: Bool = _ a :: Bool = _
_result :: (Bool, Bool, ()) = _ _result :: (Bool, Bool, ()) = _
...@@ -20,8 +20,8 @@ _result :: a ...@@ -20,8 +20,8 @@ _result :: a
f :: Integer -> a f :: Integer -> a
x :: Integer x :: Integer
xs :: [t] = [] xs :: [t] = []
f :: Integer -> a = _
x :: Integer = 2 x :: Integer = 2
f :: Integer -> a = _
_result :: a = _ _result :: a = _
_result = 3 _result = 3
Logged breakpoint at Test3.hs:2:18-31 Logged breakpoint at Test3.hs:2:18-31
......
...@@ -20,8 +20,8 @@ _result :: a ...@@ -20,8 +20,8 @@ _result :: a
f :: Integer -> a f :: Integer -> a
x :: Integer x :: Integer
xs :: [t] = [] xs :: [t] = []
f :: Integer -> a = _
x :: Integer = 2 x :: Integer = 2
f :: Integer -> a = _
_result :: a = _ _result :: a = _
_result = 3 _result = 3
Logged breakpoint at Test3.hs:2:18-31 Logged breakpoint at Test3.hs:2:18-31
......
...@@ -21,9 +21,9 @@ instance Eq () -- Defined in ‘GHC.Classes’ ...@@ -21,9 +21,9 @@ instance Eq () -- Defined in ‘GHC.Classes’
instance Monoid () -- Defined in ‘GHC.Base’ instance Monoid () -- Defined in ‘GHC.Base’
instance Ord () -- Defined in ‘GHC.Classes’ instance Ord () -- Defined in ‘GHC.Classes’
instance Semigroup () -- Defined in ‘GHC.Base’ instance Semigroup () -- Defined in ‘GHC.Base’
instance Enum () -- Defined in ‘GHC.Enum’
instance Show () -- Defined in ‘GHC.Show’ instance Show () -- Defined in ‘GHC.Show’
instance Read () -- Defined in ‘GHC.Read’ instance Read () -- Defined in ‘GHC.Read’
instance Enum () -- Defined in ‘GHC.Enum’
instance Bounded () -- Defined in ‘GHC.Enum’ instance Bounded () -- Defined in ‘GHC.Enum’
type instance D () () = Bool -- Defined at T4175.hs:22:10 type instance D () () = Bool -- Defined at T4175.hs:22:10
type instance D Int () = String -- Defined at T4175.hs:19:10 type instance D Int () = String -- Defined at T4175.hs:19:10
...@@ -38,8 +38,8 @@ instance Ord a => Ord (Maybe a) -- Defined in ‘GHC.Maybe’ ...@@ -38,8 +38,8 @@ instance Ord a => Ord (Maybe a) -- Defined in ‘GHC.Maybe’
instance Semigroup a => Semigroup (Maybe a) instance Semigroup a => Semigroup (Maybe a)
-- Defined in ‘GHC.Base’ -- Defined in ‘GHC.Base’
instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’ instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
instance Read a => Read (Maybe a) -- Defined in ‘GHC.Read’
instance MonadFail Maybe -- Defined in ‘Control.Monad.Fail’ instance MonadFail Maybe -- Defined in ‘Control.Monad.Fail’
instance Read a => Read (Maybe a) -- Defined in ‘GHC.Read’
instance Foldable Maybe -- Defined in ‘Data.Foldable’ instance Foldable Maybe -- Defined in ‘Data.Foldable’
instance Traversable Maybe -- Defined in ‘Data.Traversable’ instance Traversable Maybe -- Defined in ‘Data.Traversable’
type instance A (Maybe a) a = a -- Defined at T4175.hs:9:15 type instance A (Maybe a) a = a -- Defined at T4175.hs:9:15
...@@ -47,11 +47,11 @@ data Int = GHC.Types.I# GHC.Prim.Int# -- Defined in ‘GHC.Types’ ...@@ -47,11 +47,11 @@ data Int = GHC.Types.I# GHC.Prim.Int# -- Defined in ‘GHC.Types’
instance [safe] C Int -- Defined at T4175.hs:18:10 instance [safe] C Int -- Defined at T4175.hs:18:10
instance Eq Int -- Defined in ‘GHC.Classes’ instance Eq Int -- Defined in ‘GHC.Classes’
instance Ord Int -- Defined in ‘GHC.Classes’ instance Ord Int -- Defined in ‘GHC.Classes’
instance Show Int -- Defined in ‘GHC.Show’
instance Read Int -- Defined in ‘GHC.Read’
instance Enum Int -- Defined in ‘GHC.Enum’ instance Enum Int -- Defined in ‘GHC.Enum’
instance Num Int -- Defined in ‘GHC.Num’ instance Num Int -- Defined in ‘GHC.Num’
instance Real Int -- Defined in ‘GHC.Real’ instance Real Int -- Defined in ‘GHC.Real’
instance Show Int -- Defined in ‘GHC.Show’
instance Read Int -- Defined in ‘GHC.Read’
instance Bounded Int -- Defined in ‘GHC.Enum’ instance Bounded Int -- Defined in ‘GHC.Enum’
instance Integral Int -- Defined in ‘GHC.Real’ instance Integral Int -- Defined in ‘GHC.Real’
type instance D Int () = String -- Defined at T4175.hs:19:10 type instance D Int () = String -- Defined at T4175.hs:19:10
......
...@@ -3,9 +3,9 @@ instance Eq () -- Defined in ‘GHC.Classes’ ...@@ -3,9 +3,9 @@ instance Eq () -- Defined in ‘GHC.Classes’
instance Monoid () -- Defined in ‘GHC.Base’ instance Monoid () -- Defined in ‘GHC.Base’
instance Ord () -- Defined in ‘GHC.Classes’ instance Ord () -- Defined in ‘GHC.Classes’
instance Semigroup () -- Defined in ‘GHC.Base’ instance Semigroup () -- Defined in ‘GHC.Base’
instance Enum () -- Defined in ‘GHC.Enum’
instance Show () -- Defined in ‘GHC.Show’ instance Show () -- Defined in ‘GHC.Show’
instance Read () -- Defined in ‘GHC.Read’ instance Read () -- Defined in ‘GHC.Read’
instance Enum () -- Defined in ‘GHC.Enum’
instance Bounded () -- Defined in ‘GHC.Enum’ instance Bounded () -- Defined in ‘GHC.Enum’
data (##) = (##) -- Defined in ‘GHC.Prim’ data (##) = (##) -- Defined in ‘GHC.Prim’
() :: () () :: ()
......
data Int = GHC.Types.I# GHC.Prim.Int# -- Defined in ‘GHC.Types’ data Int = GHC.Types.I# GHC.Prim.Int# -- Defined in ‘GHC.Types’
instance Eq Int -- Defined in ‘GHC.Classes’ instance Eq Int -- Defined in ‘GHC.Classes’
instance Ord Int -- Defined in ‘GHC.Classes’ instance Ord Int -- Defined in ‘GHC.Classes’
instance Show Int -- Defined in ‘GHC.Show’
instance Read Int -- Defined in ‘GHC.Read’
instance Enum Int -- Defined in ‘GHC.Enum’ instance Enum Int -- Defined in ‘GHC.Enum’
instance Num Int -- Defined in ‘GHC.Num’ instance Num Int -- Defined in ‘GHC.Num’
instance Real Int -- Defined in ‘GHC.Real’ instance Real Int -- Defined in ‘GHC.Real’
instance Show Int -- Defined in ‘GHC.Show’
instance Read Int -- Defined in ‘GHC.Read’
instance Bounded Int -- Defined in ‘GHC.Enum’ instance Bounded Int -- Defined in ‘GHC.Enum’
instance Integral Int -- Defined in ‘GHC.Real’ instance Integral Int -- Defined in ‘GHC.Real’
...@@ -296,5 +296,6 @@ test('T16089', normal, ghci_script, ['T16089.script']) ...@@ -296,5 +296,6 @@ test('T16089', normal, ghci_script, ['T16089.script'])
test('T14828', normal, ghci_script, ['T14828.script']) test('T14828', normal, ghci_script, ['T14828.script'])
test('T16376', normal, ghci_script, ['T16376.script']) test('T16376', normal, ghci_script, ['T16376.script'])
test('T16527', normal, ghci_script, ['T16527.script']) test('T16527', normal, ghci_script, ['T16527.script'])
test('T16563', extra_hc_opts("-clear-package-db -global-package-db"), ghci_script, ['T16563.script'])
test('T16569', normal, ghci_script, ['T16569.script']) test('T16569', normal, ghci_script, ['T16569.script'])
test('T16767', normal, ghci_script, ['T16767.script']) test('T16767', normal, ghci_script, ['T16767.script'])
...@@ -7,8 +7,8 @@ instance Monoid [a] -- Defined in ‘GHC.Base’ ...@@ -7,8 +7,8 @@ instance Monoid [a] -- Defined in ‘GHC.Base’
instance Ord a => Ord [a] -- Defined in ‘GHC.Classes’ instance Ord a => Ord [a] -- Defined in ‘GHC.Classes’
instance Semigroup [a] -- Defined in ‘GHC.Base’ instance Semigroup [a] -- Defined in ‘GHC.Base’
instance Show a => Show [a] -- Defined in ‘GHC.Show’ instance Show a => Show [a] -- Defined in ‘GHC.Show’
instance Read a => Read [a] -- Defined in ‘GHC.Read’
instance MonadFail [] -- Defined in ‘Control.Monad.Fail’ instance MonadFail [] -- Defined in ‘Control.Monad.Fail’
instance Read a => Read [a] -- Defined in ‘GHC.Read’
instance Foldable [] -- Defined in ‘Data.Foldable’ instance Foldable [] -- Defined in ‘Data.Foldable’
instance Traversable [] -- Defined in ‘Data.Traversable’ instance Traversable [] -- Defined in ‘Data.Traversable’
data () = () -- Defined in ‘GHC.Tuple’ data () = () -- Defined in ‘GHC.Tuple’
...@@ -16,9 +16,9 @@ instance Eq () -- Defined in ‘GHC.Classes’ ...@@ -16,9 +16,9 @@ instance Eq () -- Defined in ‘GHC.Classes’
instance Monoid () -- Defined in ‘GHC.Base’ instance Monoid () -- Defined in ‘GHC.Base’
instance Ord () -- Defined in ‘GHC.Classes’ instance Ord () -- Defined in ‘GHC.Classes’
instance Semigroup () -- Defined in ‘GHC.Base’ instance Semigroup () -- Defined in ‘GHC.Base’
instance Enum () -- Defined in ‘GHC.Enum’
instance Show () -- Defined in ‘GHC.Show’ instance Show () -- Defined in ‘GHC.Show’
instance Read () -- Defined in ‘GHC.Read’ instance Read () -- Defined in ‘GHC.Read’
instance Enum () -- Defined in ‘GHC.Enum’
instance Bounded () -- Defined in ‘GHC.Enum’ instance Bounded () -- Defined in ‘GHC.Enum’
data (,) a b = (,) a b -- Defined in ‘GHC.Tuple’ data (,) a b = (,) a b -- Defined in ‘GHC.Tuple’
instance Monoid a => Applicative ((,) a) -- Defined in ‘GHC.Base’ instance Monoid a => Applicative ((,) a) -- Defined in ‘GHC.Base’
......
...@@ -9,13 +9,11 @@ instance Ord _ => Ord (Maybe _) -- Defined in ‘GHC.Maybe’ ...@@ -9,13 +9,11 @@ instance Ord _ => Ord (Maybe _) -- Defined in ‘GHC.Maybe’
instance Semigroup _ => Semigroup (Maybe _) instance Semigroup _ => Semigroup (Maybe _)
-- Defined in ‘GHC.Base’ -- Defined in ‘GHC.Base’
instance Show _ => Show (Maybe _) -- Defined in ‘GHC.Show’ instance Show _ => Show (Maybe _) -- Defined in ‘GHC.Show’
instance Read _ => Read (Maybe _) -- Defined in ‘GHC.Read’
instance Eq _ => Eq [_] -- Defined in ‘GHC.Classes’ instance Eq _ => Eq [_] -- Defined in ‘GHC.Classes’
instance Monoid [_] -- Defined in ‘GHC.Base’ instance Monoid [_] -- Defined in ‘GHC.Base’
instance Ord _ => Ord [_] -- Defined in ‘GHC.Classes’ instance Ord _ => Ord [_] -- Defined in ‘GHC.Classes’
instance Semigroup [_] -- Defined in ‘GHC.Base’ instance Semigroup [_] -- Defined in ‘GHC.Base’
instance Show _ => Show [_] -- Defined in ‘GHC.Show’ instance Show _ => Show [_] -- Defined in ‘GHC.Show’
instance Read _ => Read [_] -- Defined in ‘GHC.Read’
instance [safe] MyShow _ => MyShow [_] instance [safe] MyShow _ => MyShow [_]
-- Defined at ghci064.hs:7:10 -- Defined at ghci064.hs:7:10
instance Monoid [T] -- Defined in ‘GHC.Base’ instance Monoid [T] -- Defined in ‘GHC.Base’
...@@ -24,12 +22,8 @@ instance [safe] MyShow [T] -- Defined at ghci064.hs:7:10 ...@@ -24,12 +22,8 @@ instance [safe] MyShow [T] -- Defined at ghci064.hs:7:10
instance [safe] MyShow [T] -- Defined at ghci064.hs:15:10 instance [safe] MyShow [T] -- Defined at ghci064.hs:15:10
instance Eq Bool -- Defined in ‘GHC.Classes’ instance Eq Bool -- Defined in ‘GHC.Classes’
instance Ord Bool -- Defined in ‘GHC.Classes’ instance Ord Bool -- Defined in ‘GHC.Classes’
instance Show Bool -- Defined in ‘GHC.Show’
instance Read Bool -- Defined in ‘GHC.Read’
instance Enum Bool -- Defined in ‘GHC.Enum’ instance Enum Bool -- Defined in ‘GHC.Enum’
instance Show Bool -- Defined in ‘GHC.Show’
instance Bounded Bool -- Defined in ‘GHC.Enum’ instance Bounded Bool -- Defined in ‘GHC.Enum’
instance Data.Bits.Bits Bool -- Defined in ‘Data.Bits’
instance Data.Bits.FiniteBits Bool -- Defined in ‘Data.Bits’
instance GHC.Arr.Ix Bool -- Defined in ‘GHC.Arr’
instance Functor ((,) Int) -- Defined in ‘GHC.Base’ instance Functor ((,) Int) -- Defined in ‘GHC.Base’
instance Foldable ((,) Int) -- Defined in ‘Data.Foldable’ instance Foldable ((,) Int) -- Defined in ‘Data.Foldable’