Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
3a0ddd1f
Commit
3a0ddd1f
authored
Apr 18, 2007
by
Simon Marlow
Browse files
small cleanup: showForUser -> printForUser, eliminate some duplicate code
parent
9a7ac3c4
Changes
2
Hide whitespace changes
Inline
Side-by-side
compiler/ghci/GhciMonad.hs
View file @
3a0ddd1f
...
...
@@ -11,8 +11,9 @@ module GhciMonad where
#
include
"HsVersions.h"
import
qualified
GHC
import
Outputable
import
Panic
hiding
(
showException
)
import
Outputable
hiding
(
printForUser
)
import
qualified
Outputable
import
Panic
hiding
(
showException
)
import
Util
import
DynFlags
import
HscTypes
...
...
@@ -197,11 +198,11 @@ discardResumeContext = do
st
<-
getGHCiState
setGHCiState
st
{
resume
=
[]
}
show
ForUser
::
SDoc
->
GHCi
String
show
ForUser
doc
=
do
print
ForUser
::
SDoc
->
GHCi
()
print
ForUser
doc
=
do
session
<-
getSession
unqual
<-
io
(
GHC
.
getPrintUnqual
session
)
return
$!
showSDocForUser
unqual
doc
io
$
Outputable
.
printForUser
stdout
unqual
doc
-- --------------------------------------------------------------------------
-- timing & statistics
...
...
compiler/ghci/InteractiveUI.hs
View file @
3a0ddd1f
...
...
@@ -26,7 +26,7 @@ import Packages
import
PackageConfig
import
UniqFM
import
PprTyThing
import
Outputable
import
Outputable
hiding
(
printForUser
)
import
Module
-- for ModuleEnv
-- for createtags
...
...
@@ -517,9 +517,7 @@ switchOnRunResult (GHC.RunBreak threadId names info resume) = do
-- display information about the breakpoint
let
location
=
ticks
!
breakInfo_number
info
unqual
<-
io
$
GHC
.
getPrintUnqual
session
io
$
printForUser
stdout
unqual
$
ptext
SLIT
(
"Stopped at"
)
<+>
ppr
location
printForUser
$
ptext
SLIT
(
"Stopped at"
)
<+>
ppr
location
pushResume
location
threadId
resume
return
(
Just
(
True
,
names
))
...
...
@@ -830,8 +828,7 @@ typeOfExpr str
case
maybe_ty
of
Nothing
->
return
()
Just
ty
->
do
ty'
<-
cleanType
ty
tystr
<-
showForUser
(
ppr
ty'
)
io
(
putStrLn
(
str
++
" :: "
++
tystr
))
printForUser
$
text
str
<>
text
" :: "
<>
ppr
ty'
kindOfType
::
String
->
GHCi
()
kindOfType
str
...
...
@@ -839,8 +836,7 @@ kindOfType str
maybe_ty
<-
io
(
GHC
.
typeKind
cms
str
)
case
maybe_ty
of
Nothing
->
return
()
Just
ty
->
do
tystr
<-
showForUser
(
ppr
ty
)
io
(
putStrLn
(
str
++
" :: "
++
tystr
))
Just
ty
->
printForUser
$
text
str
<>
text
" :: "
<>
ppr
ty
quit
::
String
->
GHCi
Bool
quit
_
=
return
True
...
...
@@ -1222,8 +1218,7 @@ showBindings = do
showTyThing
(
AnId
id
)
=
do
ty'
<-
cleanType
(
GHC
.
idType
id
)
str
<-
showForUser
(
ppr
id
<>
text
" :: "
<>
ppr
ty'
)
io
(
putStrLn
str
)
printForUser
$
ppr
id
<>
text
" :: "
<>
ppr
ty'
showTyThing
_
=
return
()
-- if -fglasgow-exts is on we show the foralls, otherwise we don't.
...
...
@@ -1237,8 +1232,7 @@ cleanType ty = do
showBkptTable
::
GHCi
()
showBkptTable
=
do
activeBreaks
<-
getActiveBreakPoints
str
<-
showForUser
$
ppr
activeBreaks
io
$
putStrLn
str
printForUser
$
ppr
activeBreaks
-- -----------------------------------------------------------------------------
-- Completion
...
...
@@ -1555,7 +1549,6 @@ findBreakAndSet mod lookupTickTree = do
Just
(
tick
,
span
)
->
do
success
<-
io
$
setBreakFlag
True
breakArray
tick
session
<-
getSession
unqual
<-
io
$
GHC
.
getPrintUnqual
session
if
success
then
do
(
alreadySet
,
nm
)
<-
...
...
@@ -1564,15 +1557,14 @@ findBreakAndSet mod lookupTickTree = do
,
breakLoc
=
span
,
breakTick
=
tick
}
io
$
printForUser
stdout
unqual
$
printForUser
$
text
"Breakpoint "
<>
ppr
nm
<>
if
alreadySet
then
text
" was already set at "
<>
ppr
span
else
text
" activated at "
<>
ppr
span
else
do
str
<-
show
ForUser
$
text
"Breakpoint could not be activated at"
print
ForUser
$
text
"Breakpoint could not be activated at"
<+>
ppr
span
io
$
putStrLn
str
-- When a line number is specified, the current policy for choosing
-- the best breakpoint is this:
...
...
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment