| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
| |
Further work refactoring and enhancing GHCi will make it desirable to
split up GHCi's code-base into multiple modules with specific functions,
and rather than have several top-level 'Ghci*' modules, it's nicer to
have a common namespace. This commit is provides the basis for that.
Note that the remaining GHCi.* namespace belongs to the new `ghci`
package.
Differential Revision: https://phabricator.haskell.org/D1593
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Breakpoints become SCCs, so we have detailed call-stack info for
interpreted code. Currently this only works when GHC is compiled with
-prof, but D1562 (Remote GHCi) removes this constraint so that in the
future call stacks will be available without building your own GHCi.
How can you get a stack trace?
* programmatically: GHC.Stack.currentCallStack
* I've added an experimental :where command that shows the stack when
stopped at a breakpoint
* `error` attaches a call stack automatically, although since calls to
`error` are often lifted out to the top level, this is less useful
than it might be (ImplicitParams still works though).
* Later we might attach call stacks to all exceptions
Other related changes in this diff:
* I reduced the number of places that get ticks attached for
breakpoints. In particular there was a breakpoint around the whole
declaration, which was often redundant because it bound no variables.
This reduces clutter in the stack traces and speeds up compilation.
* I tidied up some RealSrcSpan stuff in InteractiveUI, and made a few
other small cleanups
Test Plan: validate
Reviewers: ezyang, bgamari, austin, hvr
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1595
GHC Trac Issues: #11047
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This adds the new commands `:all-types`, `:loc-at`, `:type-at`, and
`:uses` designed for editor-integration (such as Emacs' `haskell-mode`).
This was originally implemented by Chris Done on
https://github.com/chrisdone/ghci-ng
and has been in use by Emacs' `haskell-mode` for over a year already,
and closely missed the GHC 7.10 release back then.
I've squashed the commits, rebased to GHC HEAD, and heavily refactored and
improved the patch.
Tests will be added in a separate commit.
Reviewed By: bgamari
Differential Revision: https://phabricator.haskell.org/D1240
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
(Apologies for the size of this patch, I couldn't make a smaller one
that was validate-clean and also made sense independently)
(Some of this code is derived from GHCJS.)
This commit adds support for running interpreted code (for GHCi and
TemplateHaskell) in a separate process. The functionality is
experimental, so for now it is off by default and enabled by the flag
-fexternal-interpreter.
Reaosns we want this:
* compiling Template Haskell code with -prof does not require
building the code without -prof first
* when GHC itself is profiled, it can interpret unprofiled code, and
the same applies to dynamic linking. We would no longer need to
force -dynamic-too with TemplateHaskell, and we can load ordinary
objects into a dynamically-linked GHCi (and vice versa).
* An unprofiled GHCi can load and run profiled code, which means it
can use the stack-trace functionality provided by profiling without
taking the performance hit on the compiler that profiling would
entail.
Amongst other things; see
https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi for more details.
Notes on the implementation are in Note [Remote GHCi] in the new
module compiler/ghci/GHCi.hs. It probably needs more documenting,
feel free to suggest things I could elaborate on.
Things that are not currently implemented for -fexternal-interpreter:
* The GHCi debugger
* :set prog, :set args in GHCi
* `recover` in Template Haskell
* Redirecting stdin/stdout for the external process
These are all doable, I just wanted to get to a working validate-clean
patch first.
I also haven't done any benchmarking yet. I expect there to be slight hit
to link times for byte code and some penalty due to having to
serialize/deserialize TH syntax, but I don't expect it to be a serious
problem. There's also lots of low-hanging fruit in the byte code
generator/linker that we could exploit to speed things up.
Test Plan:
* validate
* I've run parts of the test suite with
EXTRA_HC_OPTS=-fexternal-interpreter, notably tests/ghci and tests/th.
There are a few failures due to the things not currently implemented
(see above).
Reviewers: simonpj, goldfire, ezyang, austin, alanz, hvr, niteria, bgamari, gibiansky, luite
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1562
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This also updates the user's guide to refer to the `-W`-based warning
flags by default.
Quoting the release note entry:
| Warnings can now be controlled with `-W(no-)...` flags in addition to
| the old `-f(no-)warn...` ones. This was done as the first part of a
| rewrite of the warning system to provide better control over warnings,
| better warning messages, and more common syntax compared to other
| compilers. The old `-fwarn...`-based warning flags will remain
| functional for the forseeable future.
This is part of
https://ghc.haskell.org/wiki/Design/Warnings
and addresses #11218
Reviewed By: hvr, bgamari
Differential Revision: https://phabricator.haskell.org/D1613
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This exposes `template-haskell` functions for querying the language
extensions which are enabled when compiling a module,
- an `isExtEnabled` function to check whether an extension is enabled
- an `extsEnabled` function to obtain a full list of enabled extensions
To avoid code duplication this adds a `GHC.LanguageExtensions` module to
`ghc-boot` and moves `DynFlags.ExtensionFlag` into it. A happy
consequence of this is that the ungainly `DynFlags` lost around 500
lines. Moreover, flags corresponding to language extensions are now
clearly distinguished from other flags due to the `LangExt.*` prefix.
Updates haddock submodule.
This fixes #10820.
Test Plan: validate
Reviewers: austin, spinda, hvr, goldfire, alanz
Reviewed By: goldfire
Subscribers: mpickering, RyanGlScott, hvr, simonpj, thomie
Differential Revision: https://phabricator.haskell.org/D1200
GHC Trac Issues: #10820
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This transforms the 'Command' tuple into a record which is
easier to extend.
While at it, this refactoring turns the IDE `:complete` into a hidden
command excluded from completion.
The next obvious step is to add a summary text field for constructing
the `:help` output (as well as allowing to get `:help <CMD>` for single
commands.
This is a preparatory refactoring for D1240 / #10874
Reviewed By: thomie, bgamari
Differential Revision: https://phabricator.haskell.org/D1590
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Ideally, we'd have the more general
instance (MonadTrans t, Monad m, HasDynFlags m) => HasDynFlags (t m) where
getDynFlags = lift getDynFlags
definition. However, that one would overlap with the `HasDynFlags (GhcT m)`
instance. Instead we define instances for a couple of common Monad
transformers explicitly in order to avoid nasty overlapping instances.
This is a preparatory refactoring for #10874
Reviewed By: austin
Differential Revision: https://phabricator.haskell.org/D1581
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This allows to reach the GhciState without having to keep
track how many Monad transformer layers sit on top of the
GHCi monad.
While at it, this also refactors code to make more use of the
existing `modifyGHCiState` operation.
This is a preparatory refactoring for #10874
Differential Revision: https://phabricator.haskell.org/D1582
|
|
|
|
|
|
|
| |
It makes little sense to have __GLASGOW_HASKELL__ conditional
code inside GHCi's source-code, as GHCi is only ever build
by the current stage1 GHC, whose version is assumed to be the
same as the GHCi version being built.
|
|
|
|
|
|
|
|
|
|
|
|
| |
Reviewers: austin, thomie, bgamari
Reviewed By: thomie, bgamari
Subscribers: mpickering, thomie
Differential Revision: https://phabricator.haskell.org/D1518
GHC Trac Issues: #9015
|
|
|
|
|
| |
This reverts commit 72e362076e7ce823678797a162d0645e088cd594 which was
accidentally merged.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch began as a modest refactoring of HsType and friends, to
clarify and tidy up exactly where quantification takes place in types.
Although initially driven by making the implementation of wildcards more
tidy (and fixing a number of bugs), I gradually got drawn into a pretty
big process, which I've been doing on and off for quite a long time.
There is one compiler performance regression as a result of all
this, in perf/compiler/T3064. I still need to look into that.
* The principal driving change is described in Note [HsType binders]
in HsType. Well worth reading!
* Those data type changes drive almost everything else. In particular
we now statically know where
(a) implicit quantification only (LHsSigType),
e.g. in instance declaratios and SPECIALISE signatures
(b) implicit quantification and wildcards (LHsSigWcType)
can appear, e.g. in function type signatures
* As part of this change, HsForAllTy is (a) simplified (no wildcards)
and (b) split into HsForAllTy and HsQualTy. The two contructors
appear when and only when the correponding user-level construct
appears. Again see Note [HsType binders].
HsExplicitFlag disappears altogether.
* Other simplifications
- ExprWithTySig no longer needs an ExprWithTySigOut variant
- TypeSig no longer needs a PostRn name [name] field
for wildcards
- PatSynSig records a LHsSigType rather than the decomposed
pieces
- The mysterious 'GenericSig' is now 'ClassOpSig'
* Renamed LHsTyVarBndrs to LHsQTyVars
* There are some uninteresting knock-on changes in Haddock,
because of the HsSyn changes
I also did a bunch of loosely-related changes:
* We already had type synonyms CoercionN/CoercionR for nominal and
representational coercions. I've added similar treatment for
TcCoercionN/TcCoercionR
mkWpCastN/mkWpCastN
All just type synonyms but jolly useful.
* I record-ised ForeignImport and ForeignExport
* I improved the (poor) fix to Trac #10896, by making
TcTyClsDecls.checkValidTyCl recover from errors, but adding a
harmless, abstract TyCon to the envt if so.
* I did some significant refactoring in RnEnv.lookupSubBndrOcc,
for reasons that I have (embarrassingly) now totally forgotten.
It had to do with something to do with import and export
Updates haddock submodule.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In so doing ensure that the help text can't fall out of sync with the
implementation.
Test Plan: Validate and play in ghci
Reviewers: austin, thomie
Reviewed By: austin, thomie
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1538
GHC Trac Issues: #11111
|
|
|
|
|
| |
This is an updated version of @jlengyel's original patch adding support
for prompt functions.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch allows define and re-define functions in ghci. `let` is not
required anymore (but can be used).
Idea: If ghci input string can be parsed as statement then run it as
statement else run it as declaration.
Reviewers: mpickering, bgamari, austin
Reviewed By: mpickering, bgamari, austin
Subscribers: hvr, mpickering, dterei, thomie
Differential Revision: https://phabricator.haskell.org/D1299
GHC Trac Issues: #7253
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
A ource file which was accidently passed as parameter into `:ctags` or `:etags`
can be overwritten by tag data. This patch updates documentation to avoid
confusion in commands usage and prevents `collateAndWriteTags` from modifying
existing source files.
Reviewed By: thomie, bgamari, austin
Differential Revision: https://phabricator.haskell.org/D1471
GHC Trac Issues: #10989
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Amazingly, there were zero changes to the byte code generator and very
few changes to the interpreter - mainly because we've used good
abstractions that hide the differences between profiling and
non-profiling. So that bit was pleasantly straightforward, but there
were a pile of other wibbles to get the whole test suite through.
Note that a compiler built with -prof is now like one built with
-dynamic, in that to use TH you have to build the code the same way.
For dynamic, we automatically enable -dynamic-too when TH is required,
but we don't have anything equivalent for profiling, so you have to
explicitly use -prof when building code that uses TH with a profiled
compiler. For this reason Cabal won't work with TH. We don't expect
to ship a profiled compiler, so I think that's OK.
Test Plan: validate with GhcProfiled=YES in validate.mk
Reviewers: goldfire, bgamari, rwbarton, austin, hvr, erikd, ezyang
Reviewed By: ezyang
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1407
GHC Trac Issues: #4837, #545
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This is the second attempt at merging D757.
This patch implements the idea floated in Trac #9858, namely that we
should generate type-representation information at the data type
declaration site, rather than when solving a Typeable constraint.
However, this turned out quite a bit harder than I expected. I still
think it's the right thing to do, and it's done now, but it was quite
a struggle.
See particularly
* Note [Grand plan for Typeable] in TcTypeable (which is a new module)
* Note [The overall promotion story] in DataCon (clarifies existing
stuff)
The most painful bit was that to generate Typeable instances (ie
TyConRepName bindings) for every TyCon is tricky for types in ghc-prim
etc:
* We need to have enough data types around to *define* a TyCon
* Many of these types are wired-in
Also, to minimise the code generated for each data type, I wanted to
generate pure data, not CAFs with unpackCString# stuff floating about.
Performance
~~~~~~~~~~~
Three perf/compiler tests start to allocate quite a bit more. This isn't
surprising, because they all allocate zillions of data types, with
practically no other code, esp. T1969
* T1969: GHC allocates 19% more
* T4801: GHC allocates 13% more
* T5321FD: GHC allocates 13% more
* T9675: GHC allocates 11% more
* T783: GHC allocates 11% more
* T5642: GHC allocates 10% more
I'm treating this as acceptable. The payoff comes in Typeable-heavy
code.
Remaining to do
~~~~~~~~~~~~~~~
* I think that "TyCon" and "Module" are over-generic names to use for
the runtime type representations used in GHC.Typeable. Better might
be
"TrTyCon" and "TrModule". But I have not yet done this
* Add more info the the "TyCon" e.g. source location where it was
defined
* Use the new "Module" type to help with Trac Trac #10068
* It would be possible to generate TyConRepName (ie Typeable
instances) selectively rather than all the time. We'd need to persist
the information in interface files. Lacking a motivating reason I
have
not done this, but it would not be difficult.
Refactoring
~~~~~~~~~~~
As is so often the case, I ended up refactoring more than I intended.
In particular
* In TyCon, a type *family* (whether type or data) is repesented by a
FamilyTyCon
* a algebraic data type (including data/newtype instances) is
represented by AlgTyCon This wasn't true before; a data family
was represented as an AlgTyCon. There are some corresponding
changes in IfaceSyn.
* Also get rid of the (unhelpfully named) tyConParent.
* In TyCon define 'Promoted', isomorphic to Maybe, used when things are
optionally promoted; and use it elsewhere in GHC.
* Cleanup handling of knownKeyNames
* Each TyCon, including promoted TyCons, contains its TyConRepName, if
it has one. This is, in effect, the name of its Typeable instance.
Updates haddock submodule
Test Plan: Let Harbormaster validate
Reviewers: austin, hvr, goldfire
Subscribers: goldfire, thomie
Differential Revision: https://phabricator.haskell.org/D1404
GHC Trac Issues: #9858
|
|
|
|
|
|
|
|
| |
This reverts commit bef2f03e4d56d88a7e9752a7afd6a0a35616da6c.
This merge was botched
Also reverts haddock submodule.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch implements the idea floated in Trac #9858, namely that we
should generate type-representation information at the data type
declaration site, rather than when solving a Typeable constraint.
However, this turned out quite a bit harder than I expected. I still
think it's the right thing to do, and it's done now, but it was quite
a struggle.
See particularly
* Note [Grand plan for Typeable] in TcTypeable (which is a new module)
* Note [The overall promotion story] in DataCon (clarifies existing stuff)
The most painful bit was that to generate Typeable instances (ie
TyConRepName bindings) for every TyCon is tricky for types in ghc-prim
etc:
* We need to have enough data types around to *define* a TyCon
* Many of these types are wired-in
Also, to minimise the code generated for each data type, I wanted to
generate pure data, not CAFs with unpackCString# stuff floating about.
Performance
~~~~~~~~~~~
Three perf/compiler tests start to allocate quite a bit more. This isn't
surprising, because they all allocate zillions of data types, with
practically no other code, esp. T1969
* T3294: GHC allocates 110% more (filed #11030 to track this)
* T1969: GHC allocates 30% more
* T4801: GHC allocates 14% more
* T5321FD: GHC allocates 13% more
* T783: GHC allocates 12% more
* T9675: GHC allocates 12% more
* T5642: GHC allocates 10% more
* T9961: GHC allocates 6% more
* T9203: Program allocates 54% less
I'm treating this as acceptable. The payoff comes in Typeable-heavy
code.
Remaining to do
~~~~~~~~~~~~~~~
* I think that "TyCon" and "Module" are over-generic names to use for
the runtime type representations used in GHC.Typeable. Better might be
"TrTyCon" and "TrModule". But I have not yet done this
* Add more info the the "TyCon" e.g. source location where it was
defined
* Use the new "Module" type to help with Trac Trac #10068
* It would be possible to generate TyConRepName (ie Typeable
instances) selectively rather than all the time. We'd need to persist
the information in interface files. Lacking a motivating reason I have
not done this, but it would not be difficult.
Refactoring
~~~~~~~~~~~
As is so often the case, I ended up refactoring more than I intended.
In particular
* In TyCon, a type *family* (whether type or data) is repesented by a
FamilyTyCon
* a algebraic data type (including data/newtype instances) is
represented by AlgTyCon This wasn't true before; a data family
was represented as an AlgTyCon. There are some corresponding
changes in IfaceSyn.
* Also get rid of the (unhelpfully named) tyConParent.
* In TyCon define 'Promoted', isomorphic to Maybe, used when things are
optionally promoted; and use it elsewhere in GHC.
* Cleanup handling of knownKeyNames
* Each TyCon, including promoted TyCons, contains its TyConRepName, if
it has one. This is, in effect, the name of its Typeable instance.
Requires update of the haddock submodule.
Differential Revision: https://phabricator.haskell.org/D757
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previous suggestion would clear executable bit, meaning directory
couldn't be entered. Fixes #11003.
Test Plan: Read message.
Reviewers: austin, thomie, dfeuer
Reviewed By: thomie, dfeuer
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1350
GHC Trac Issues: #11003
|
|
|
|
|
|
| |
Comes with Haddock submodule update.
Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The Windows preprocessor code calls `runInteractiveProcess` but does
not check if an exception is thrown.
`runInteractiveProcess` calls `CreateProcess` which when given a format
the system loader does not know about
will throw an exception. This is what makes #9399 fail.
Ultimately we should not use any `CreateProcess` based calls but
instead `ShellExecuteEx` as this would allow
us to run applications that the shell knows about instead of just the
loader. More details on #365.
This patch removes `PhaseFailed` and throws `ProgramError` instead.
`PhaseFailed` was largely unneeded since it never gave
very useful information aside from the `errorcode` which was almost
always `1`. `IOErrors` have also been eliminated and `GhcExceptions`
thrown in their place wherever possible.
Updates haddock submodule.
Test Plan:
`./validate` to make sure anything didn't break and
`make TESTS="T365"` to test that an error is now properly thrown
Reviewers: austin, thomie, bgamari
Reviewed By: thomie, bgamari
Subscribers: #ghc_windows_task_force
Differential Revision: https://phabricator.haskell.org/D1256
GHC Trac Issues: #365
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Phab:D907 introduced SourceText for a number of data types, by replacing
FastString with (SourceText,FastString). Since this has an Outputable
instance, no warnings are generated when ppr is called on it, but
unexpected output is generated. See Phab:D1096 for an example of this.
Replace the (SourceText,FastString) tuples with a new data type,
```lang=hs
data StringLiteral = StringLiteral SourceText FastString
```
Update haddock submodule accordingly
Test Plan: ./validate
Reviewers: hvr, austin, rwbarton, trofi, bgamari
Reviewed By: trofi, bgamari
Subscribers: thomie, trofi, rwbarton, mpickering
Differential Revision: https://phabricator.haskell.org/D1101
GHC Trac Issues: #10692
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: I couldn't add tests because apparently line number
reporting was already working correctly when loading script files. I
don't know how to test by running commands using stdin, is this
supported?
Reviewers: austin, thomie, bgamari
Reviewed By: thomie, bgamari
Subscribers: hvr, thomie
Differential Revision: https://phabricator.haskell.org/D1067
|
|
|
|
|
|
|
|
| |
Added load! and reload! commands, effectively setting
"-fdefer-type-errors" before loading a file and
unsetting it after loading if it has not been set before.
Differential Revision: https://phabricator.haskell.org/D960
|
|
|
|
| |
Follow up to 124f3999d78d8ef6b093e4f1bb1dcef87e4283da.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary: It was possible to kill GHCi with a carefully-timed ^C
Test Plan: The bug in #10017 exposed this
Reviewers: bgamari, austin
Reviewed By: austin
Subscribers: thomie, bgamari
Differential Revision: https://phabricator.haskell.org/D1015
GHC Trac Issues: #10017
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
This commit brings following changes and fixes:
* Implement parseExpr and compileParsedExpr;
* Fix compileExpr and dynCompilerExpr, which returned `()` for empty expr;
* Fix :def and :cmd, which didn't work if `IO` or `String` is not in scope;
* Use GHCiMonad instead IO in :def and :cmd;
* Clean PrelInfo: delete dead comment and duplicate entries, add assertion.
See new tests for more details.
Test Plan: ./validate
Reviewers: austin, dterei, simonmar
Reviewed By: simonmar
Subscribers: thomie, bgamari
Differential Revision: https://phabricator.haskell.org/D974
GHC Trac Issues: #10508
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
`enqueueCommands` should always force exception in commands. Otherwise
the exception thrown in `:cmd` (e.g. `:cmd return $ head []`) will cause
GHCi to terminate with panic.
Test Plan: `cd testsuite/tests/ghci/ && make`
Reviewed By: austin
Differential Revision: https://phabricator.haskell.org/D967
GHC Trac Issues: #10501
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
The strings used in a WARNING pragma are captured via
strings :: { Located ([AddAnn],[Located FastString]) }
: STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) }
..
The STRING token has a method getSTRINGs that returns the original
source text for a string.
A warning of the form
{-# WARNING Logic
, mkSolver
, mkSimpleSolver
, mkSolverForLogic
, solverSetParams
, solverPush
, solverPop
, solverReset
, solverGetNumScopes
, solverAssertCnstr
, solverAssertAndTrack
, solverCheck
, solverCheckAndGetModel
, solverGetReasonUnknown
"New Z3 API support is still incomplete and fragile: \
\you may experience segmentation faults!"
#-}
returns the concatenated warning string rather than the original source.
This patch now deals with all remaining instances of getSTRING to bring
in a SourceText for each.
This updates the haddock submodule as well, for the AST change.
Test Plan: ./validate
Reviewers: hvr, austin, goldfire
Reviewed By: austin
Subscribers: bgamari, thomie, mpickering
Differential Revision: https://phabricator.haskell.org/D907
GHC Trac Issues: #10313
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Introduce by #95 'canonicalizePath' throws and exception when given
an invalid file in a call to 'sameFile'.
There are two cases when this can happen when using ghci:
1) If there is an error at the interactive prompt, "<interactive>"
file is searched for and not found.
2) If there is an error in any loaded file and editing an inexistent/new
file with 'e: foo'.
Both cases are now tested.
Test Plan: validate
Reviewers: austin, #ghc
Reviewed By: austin, #ghc
Subscribers: bgamari, thomie
Differential Revision: https://phabricator.haskell.org/D930
GHC Trac Issues: #10101
|
|
|
|
|
|
|
|
|
| |
These behave like the count arguments of the gdb `up` and `down`
commands, allowing the user to quickly jump around in history.
Reviewed By: austin
Differential Revision: https://phabricator.haskell.org/D853
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Do not check dir perms when .ghci doesn't exist, otherwise GHCi will
print some confusing and useless warnings in some cases (e.g. in travis).
This will fix test T8333 and T10408A in travis.
T10408A will be a test case to cover this. And T8333 is changed to be
not affected by this.
Test Plan:
chmod o+w ~/.ghc
make TESTS="T8333 T10408A T10408B"
chmod o-w ~/.ghc
Reviewers: austin, nomeata
Differential Revision: https://phabricator.haskell.org/D890
|
|
|
|
|
|
|
|
|
|
|
|
| |
* Make `-ghci-script` be executed in the order they are specified;
* Make `-ignore-dot-ghci` only ignores the default .ghci files but
still execute the scripts passed by `-ghci-script`.
Reviewed By: simonmar, austin
Differential Revision: https://phabricator.haskell.org/D887
GHC Trac Issues: #10408
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The point of this commit is to make the memory allocation statistic
from :set +s in GHCi a lot more accurate. Currently it uses the total
allocation figure calculated by the RTS, which is only updated during
GC, so can be wrong by an arbitrary amount. The fix is to the the
per-thread allocation counter that was introduced for allocation
limits.
This required changes to the GHC API, because we now have to return
the allocation value from each evaluation. Rather than just change
the API, I introduced a new API and deprecated the old one. The new
one is simpler and more extensible, so hopefully we won't need to make
this transition in the future. See GHC.hs for details.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
There is currently no way to separate whether UnicodeSyntax is accepted
for input from the corresponding output syntax using unicode symbols.
This patch implements a separate flag for affecting ghc(i)'s output.
Signed-off-by: Bertram Felgenhauer <int-e@gmx.de>
Reviewed By: nomeata, austin
Differential Revision: https://phabricator.haskell.org/D807
GHC Trac Issues: #8959
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
```
chmod 664 $PATH_TO_GHCI_CONF/.ghci
```
Run ghci. You will now get a warning + a suggestion:
```
*** WARNING: $PATH_TO_GHCI_CONF/.ghci is writable by someone else, IGNORING!
Suggested fix: execute 'chmod 644 $PATH_TO_GHCI_CONF/.ghci'
```
Execute fix and the warning should disappear.
Reviewed By: mboes, thomie
Differential Revision: https://phabricator.haskell.org/D805
|
|
|
|
|
|
| |
This involves recognizing lines starting with `"pattern "` as declarations,
keeping non-exported pattern synonyms in `deSugar`, and including
pattern synonyms in the result of `hscDeclsWithLocation`.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Note: This commit includes an API change to GhciMonad.runDecls
to allow the caller to determine whether the declarations were
run successfully or not.
Test Plan: harbormaster
Reviewers: austin
Reviewed By: austin
Subscribers: carter, thomie
Differential Revision: https://phabricator.haskell.org/D582
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Some Trues and Falses were mixed up due to Bool being used in
different senses in different parts of GHCi.
Test Plan: harbormaster; validate
Reviewers: austin
Reviewed By: austin
Subscribers: carter, thomie
Differential Revision: https://phabricator.haskell.org/D581
GHC Trac Issues: #9905
Conflicts:
ghc/InteractiveUI.hs
|
| |
|
|
|
|
| |
declaration (fixes #9914)
|
|
|
|
| |
look like prefixes of valid declarations (fixes #9915)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Previously 'ghc --show-options' showed all options that GHC can possibly
accept. With this patch, it'll only show the options that have effect in
non-interactive modes.
This change also adds support for using 'ghc --interactive --show-options'
which previously was disallowed. This command will show all options that have
effect in the interactive mode.
The CmdLineParser is updated to know about the GHC modes, and then each flag
is annotated with which mode it has effect.
This fixes #9259.
Test Plan:
Try out --show-options with --interactive on the command line. With and without
--interactive should give different results.
Run the test suite, mode001 has been updated to verify this new flag
combination.
Reviewers: austin, jstolarek
Reviewed By: austin, jstolarek
Subscribers: jstolarek, thomie, carter, simonmar
Differential Revision: https://phabricator.haskell.org/D337
GHC Trac Issues: #9259
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
trac #9293)
Summary: ghci unset could not reverse language extensions.
Reviewers: hvr, thomie, austin
Reviewed By: hvr, thomie, austin
Subscribers: goldfire, hvr, thomie, carter
Differential Revision: https://phabricator.haskell.org/D516
GHC Trac Issues: #9293
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
The final design and discussion is captured at
https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations
This is a proof of concept implementation of a completely
separate annotation structure, populated in the parser,and tied to the
AST by means of a virtual "node-key" comprising the surrounding
SrcSpan and a value derived from the specific constructor used for the
node.
The key parts of the design are the following.
== The Annotations ==
In `hsSyn/ApiAnnotation.hs`
```lang=haskell
type ApiAnns = (Map.Map ApiAnnKey SrcSpan, Map.Map SrcSpan [Located Token])
type ApiAnnKey = (SrcSpan,AnnKeywordId)
-- ---------------------------------------------------------------------
-- | Retrieve an annotation based on the @SrcSpan@ of the annotated AST
-- element, and the known type of the annotation.
getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> Maybe SrcSpan
getAnnotation (anns,_) span ann = Map.lookup (span,ann) anns
-- |Retrieve the comments allocated to the current @SrcSpan@
getAnnotationComments :: ApiAnns -> SrcSpan -> [Located Token]
getAnnotationComments (_,anns) span =
case Map.lookup span anns of
Just cs -> cs
Nothing -> []
-- | Note: in general the names of these are taken from the
-- corresponding token, unless otherwise noted
data AnnKeywordId
= AnnAs
| AnnBang
| AnnClass
| AnnClose -- ^ } or ] or ) or #) etc
| AnnComma
| AnnDarrow
| AnnData
| AnnDcolon
....
```
== Capturing in the lexer/parser ==
The annotations are captured in the lexer / parser by extending PState to include a field
In `parser/Lexer.x`
```lang=haskell
data PState = PState {
....
annotations :: [(ApiAnnKey,SrcSpan)]
-- Annotations giving the locations of 'noise' tokens in the
-- source, so that users of the GHC API can do source to
-- source conversions.
}
```
The lexer exposes a helper function to add an annotation
```lang=haskell
addAnnotation :: SrcSpan -> Ann -> SrcSpan -> P ()
addAnnotation l a v = P $ \s -> POk s {
annotations = ((AK l a), v) : annotations s
} ()
```
The parser also has some helper functions of the form
```lang=haskell
type MaybeAnn = Maybe (SrcSpan -> P ())
gl = getLoc
gj x = Just (gl x)
ams :: Located a -> [MaybeAnn] -> P (Located a)
ams a@(L l _) bs = (mapM_ (\a -> a l) $ catMaybes bs) >> return a
```
This allows annotations to be captured in the parser by means of
```
ctypedoc :: { LHsType RdrName }
: 'forall' tv_bndrs '.' ctypedoc {% hintExplicitForall (getLoc $1) >>
ams (LL $ mkExplicitHsForAllTy $2 (noLoc []) $4)
[mj AnnForall $1,mj AnnDot $3] }
| context '=>' ctypedoc {% ams (LL $ mkQualifiedHsForAllTy $1 $3)
[mj AnnDarrow $2] }
| ipvar '::' type {% ams (LL (HsIParamTy (unLoc $1) $3))
[mj AnnDcolon $2] }
| typedoc { $1 }
```
== Parse result ==
```lang-haskell
data HsParsedModule = HsParsedModule {
hpm_module :: Located (HsModule RdrName),
hpm_src_files :: [FilePath],
-- ^ extra source files (e.g. from #includes). The lexer collects
-- these from '# <file> <line>' pragmas, which the C preprocessor
-- leaves behind. These files and their timestamps are stored in
-- the .hi file, so that we can force recompilation if any of
-- them change (#3589)
hpm_annotations :: ApiAnns
}
-- | The result of successful parsing.
data ParsedModule =
ParsedModule { pm_mod_summary :: ModSummary
, pm_parsed_source :: ParsedSource
, pm_extra_src_files :: [FilePath]
, pm_annotations :: ApiAnns }
```
This diff depends on D426
Test Plan: sh ./validate
Reviewers: austin, simonpj, Mikolaj
Reviewed By: simonpj, Mikolaj
Subscribers: Mikolaj, goldfire, thomie, carter
Differential Revision: https://phabricator.haskell.org/D438
GHC Trac Issues: #9628
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
AST changes to prepare for API annotations
Add locations to parts of the AST so that API annotations can
then be added.
The outline of the whole process is captured here
https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations
This change updates the haddock submodule.
Test Plan: sh ./validate
Reviewers: austin, simonpj, Mikolaj
Reviewed By: simonpj, Mikolaj
Subscribers: thomie, goldfire, carter
Differential Revision: https://phabricator.haskell.org/D426
GHC Trac Issues: #9628
|