| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Most of the other users of the fptools build system have migrated to
Cabal, and with the move to darcs we can now flatten the source tree
without losing history, so here goes.
The main change is that the ghc/ subdir is gone, and most of what it
contained is now at the top level. The build system now makes no
pretense at being multi-project, it is just the GHC build system.
No doubt this will break many things, and there will be a period of
instability while we fix the dependencies. A straightforward build
should work, but I haven't yet fixed binary/source distributions.
Changes to the Building Guide will follow, too.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Use the lexer to parse OPTIONS, LANGUAGE and INCLUDE pragmas.
This gives us greater flexibility and far better error
messages. However, I had to make a few quirks:
* The token parser is written manually since Happy doesn't
like lexer errors (we need to extract options before the
buffer is passed through 'cpp'). Still better than
manually parsing a String, though.
* The StringBuffer API has been extended so files can be
read in blocks.
I also made a new field in ModSummary called ms_hspp_opts
which stores the updated DynFlags. Oh, and I took the liberty
of moving 'getImports' into HeaderInfo together with
'getOptions'.
|
|
|
|
|
|
|
|
| |
Fix up to compile with GHC 5.04.x again.
Also includes a fix for a memory error I discovered along the way:
should fix the "scavenge_one" crash in the stage2 build of recent
HEADs.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Add support for UTF-8 source files
GHC finally has support for full Unicode in source files. Source
files are now assumed to be UTF-8 encoded, and the full range of
Unicode characters can be used, with classifications recognised using
the implementation from Data.Char. This incedentally means that only
the stage2 compiler will recognise Unicode in source files, because I
was too lazy to port the unicode classifier code into libcompat.
Additionally, the following synonyms for keywords are now recognised:
forall symbol (U+2200) forall
right arrow (U+2192) ->
left arrow (U+2190) <-
horizontal ellipsis (U+22EF) ..
there are probably more things we could add here.
This will break some source files if Latin-1 characters are being used.
In most cases this should result in a UTF-8 decoding error. Later on
if we want to support more encodings (perhaps with a pragma to specify
the encoding), I plan to do it by recoding into UTF-8 before parsing.
Internally, there were some pretty big changes:
- FastStrings are now stored in UTF-8
- Z-encoding has been moved right to the back end. Previously we
used to Z-encode every identifier on the way in for simplicity,
and only decode when we needed to show something to the user.
Instead, we now keep every string in its UTF-8 encoding, and
Z-encode right before printing it out. To avoid Z-encoding the
same string multiple times, the Z-encoding is cached inside the
FastString the first time it is requested.
This speeds up the compiler - I've measured some definite
improvement in parsing at least, and I expect compilations overall
to be faster too. It also cleans up a lot of cruft from the
OccName interface. Z-encoding is nicely hidden inside the
Outputable instance for Names & OccNames now.
- StringBuffers are UTF-8 too, and are now represented as
ForeignPtrs.
- I've put together some test cases, not by any means exhaustive,
but there are some interesting UTF-8 decoding error cases that
aren't obvious. Also, take a look at unicode001.hs for a demo.
|
|
|
|
|
|
|
| |
Tweaks to get the GHC sources through Haddock. Doesn't quite work
yet, because Haddock complains about the recursive modules. Haddock
needs to understand SOURCE imports (it can probably just ignore them
as a first attempt).
|
|
|
|
|
|
|
| |
hGetStringBuffer: hClose the file after we've read it (duh). This
causes a real problem on Windows, where the file remains locked in
GHCi, and cannot be modified until after the finalizer has closed it
(bug #1047408).
|
|
|
|
| |
Merge backend-hacking-branch onto HEAD. Yay!
|
|
|
|
| |
Don't call hGetArray with a size of zero (fixes read021).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Some small steps in the direction of making GHC useable as a library:
- The ErrMsg type is now richer: we keep the location info and the
PrintUnqualified separate until the message is printed out, and
messages have a short summary and "extra info", where the extra
info is used for things like the context info in the typechecker
(stuff that you don't normally want to see in a more visual setting,
where the context is obvious because you're looking at the code).
- hscMain now takes an extra argument of type (Messages -> IO ()),
which says what to do with the error messages. In normal usage,
we just pass ErrUtils.printErrorsAndWarnings, but eg. a development
environment will want to do something different. The direction we
need to head in is for hscMain to *never* do any output to
stdout/stderr except via abstractions like this.
|
|
|
|
|
|
| |
GC some dead code. In some places, I left useful-looking but
currently unused definitions in place, surrounded by #ifdef UNUSED
... #endif.
|
|
|
|
| |
hGetStringBuffer: open file in binary mode
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Replace the handwritten lexer with one generated by Alex.
YOU NOW NEED ALEX (v 2.0 or later) TO COMPILE GHC FROM CVS.
Highlights:
- Faster than the previous lexer (about 10% of total parse time,
depending on the token mix).
- More correct than the previous lexer: a couple of minor wibbles
in the syntax were fixed.
- Completely accurate source spans for each token are now collected.
This information isn't used yet, but it will be used to give much
more accurate error messages in the future.
- SrcLoc now contains a column field as well as a line number,
although this is currently ignored when printing out SrcLocs.
- StringBuffer is now based on a ByteArray# rather than a Ptr, which
means that StringBuffers are now garbage collected. Previously
StringBuffers were hardly ever released, so a GHCi session would
leak space as more source files were loaded in.
- Code size reduction: Lexer.x is about the same size as the old
Lex.lhs, but StringBuffer.lhs is significantly shorter and
simpler. Sadly I wasn't able to get rid of parser/Ctypes.hs
(yet).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Fix recent breakage on the HEAD. This was caused by the fix to
Lex.lhs to treat primitive strings as "narrow" FastStrings in all
cases, rather than Unicode ("wide") FastStrings if the string
contained a '\0'. The problem is that narrow FastStrings aren't set
up to handle strings containing '\0'. They used to be, but it got
broken somewhere along the line.
This commit:
- remove the '\0' test from unpackCStringBA (it takes a length
argument anyway), and rename it to unpackNBytesBA. This fixes
the bug.
- remove the '\0' terminator from all strings generated by the
functions in PrimPacked. The terminators aren't required,
as far as I can tell. This should have a tiny but positive
effect on compile times.
MERGE TO STABLE
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------------
Make Template Haskell into the HEAD
--------------------------------------
This massive commit transfers to the HEAD all the stuff that
Simon and Tim have been doing on Template Haskell. The
meta-haskell-branch is no more!
WARNING: make sure that you
* Update your links if you are using link trees.
Some modules have been added, some have gone away.
* Do 'make clean' in all library trees.
The interface file format has changed, and you can
get strange panics (sadly) if GHC tries to read old interface files:
e.g. ghc-5.05: panic! (the `impossible' happened, GHC version 5.05):
Binary.get(TyClDecl): ForeignType
* You need to recompile the rts too; Linker.c has changed
However the libraries are almost unaltered; just a tiny change in
Base, and to the exports in Prelude.
NOTE: so far as TH itself is concerned, expression splices work
fine, but declaration splices are not complete.
---------------
The main change
---------------
The main structural change: renaming and typechecking have to be
interleaved, because we can't rename stuff after a declaration splice
until after we've typechecked the stuff before (and the splice
itself).
* Combine the renamer and typecheker monads into one
(TcRnMonad, TcRnTypes)
These two replace TcMonad and RnMonad
* Give them a single 'driver' (TcRnDriver). This driver
replaces TcModule.lhs and Rename.lhs
* The haskell-src library package has a module
Language/Haskell/THSyntax
which defines the Haskell data type seen by the TH programmer.
* New modules:
hsSyn/Convert.hs converts THSyntax -> HsSyn
deSugar/DsMeta.hs converts HsSyn -> THSyntax
* New module typecheck/TcSplice type-checks Template Haskell splices.
-------------
Linking stuff
-------------
* ByteCodeLink has been split into
ByteCodeLink (which links)
ByteCodeAsm (which assembles)
* New module ghci/ObjLink is the object-code linker.
* compMan/CmLink is removed entirely (was out of place)
Ditto CmTypes (which was tiny)
* Linker.c initialises the linker when it is first used (no need to call
initLinker any more). Template Haskell makes it harder to know when
and whether to initialise the linker.
-------------------------------------
Gathering the LIE in the type checker
-------------------------------------
* Instead of explicitly gathering constraints in the LIE
tcExpr :: RenamedExpr -> TcM (TypecheckedExpr, LIE)
we now dump the constraints into a mutable varabiable carried
by the monad, so we get
tcExpr :: RenamedExpr -> TcM TypecheckedExpr
Much less clutter in the code, and more efficient too.
(Originally suggested by Mark Shields.)
-----------------
Remove "SysNames"
-----------------
Because the renamer and the type checker were entirely separate,
we had to carry some rather tiresome implicit binders (or "SysNames")
along inside some of the HsDecl data structures. They were both
tiresome and fragile.
Now that the typechecker and renamer are more intimately coupled,
we can eliminate SysNames (well, mostly... default methods still
carry something similar).
-------------
Clean up HsPat
-------------
One big clean up is this: instead of having two HsPat types (InPat and
OutPat), they are now combined into one. This is more consistent with
the way that HsExpr etc is handled; there are some 'Out' constructors
for the type checker output.
So:
HsPat.InPat --> HsPat.Pat
HsPat.OutPat --> HsPat.Pat
No 'pat' type parameter in HsExpr, HsBinds, etc
Constructor patterns are nicer now: they use
HsPat.HsConDetails
for the three cases of constructor patterns:
prefix, infix, and record-bindings
The *same* data type HsConDetails is used in the type
declaration of the data type (HsDecls.TyData)
Lots of associated clean-up operations here and there. Less code.
Everything is wonderful.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Housekeeping:
- The main goal is to remove dependencies on hslibs for a
bootstrapped compiler, leaving only a requirement that the
packages base, haskell98 and readline are built in stage 1 in
order to bootstrap. We're almost there: Posix is still required
for signal handling, but all other dependencies on hslibs are now
gone.
Uses of Addr and ByteArray/MutableByteArray array are all gone
from the compiler. PrimPacked defines the Ptr type for GHC 4.08
(which didn't have it), and it defines simple BA and MBA types to
replace uses of ByteArray and MutableByteArray respectively.
- Clean up import lists. HsVersions.h now defines macros for some
modules which have moved between GHC versions. eg. one now
imports 'GLAEXTS' to get at unboxed types and primops in the
compiler.
Many import lists have been sorted as per the recommendations in
the new style guidelines in the commentary.
I've built the compiler with GHC 4.08.2, 5.00.2, 5.02.3, 5.04 and
itself, and everything still works here. Doubtless I've got something
wrong, though.
|
|
|
|
| |
Re-enable bootstrapping: More Ptr trouble, now that it's (almost) abstract...
|
|
|
|
|
| |
Misc cleanup: remove the iface pretty-printing style, and clean up
bits of StringBuffer that aren't required any more.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Binary Interface Files - stage 1
--------------------------------
This commit changes the default interface file format from text to
binary, in order to improve compilation performace.
To view an interface file, use 'ghc --show-iface Foo.hi'.
utils/Binary.hs is the basic Binary I/O library, based on the nhc98
binary I/O library but much stripped-down and working in terms of
bytes rather than bits, and with some special features for GHC: it
remembers which Module is being emitted to avoid dumping too many
qualified names, and it keeps track of a "dictionary" of FastStrings
so that we don't dump the same FastString more than once into the
binary file. I'll make a generic version of this for the libraries at
some point.
main/BinIface.hs contains most of the Binary instances. Some
instances are in the same module as the data type (RdrName, Name,
OccName in particular). Most instances were generated using a
modified version of DrIFT, which I'll commit later. However, editing
them by hand isn't hard (certainly easier than modifying
ParseIface.y).
The first thing in a binary interface is the interface version, so
nice error messages will be generated if the binary format changes and
you still have old interfaces lying around. The version also now
includes the "way" as an extra sanity check.
Other changes
-------------
I don't like the way FastStrings contain both hashed strings (with
O(1) comparison) and literal C strings (with O(n) comparison). So as
a first step to separating these I made serveral "literal" type
strings into hashed strings. SLIT() still generates a literal, and
now FSLIT() generates a hashed string. With DEBUG on, you'll get a
warning if you try to compare any SLIT()s with anything, and the
compiler will fall over if you try to dump any literal C strings into
an interface file (usually indicating a use of SLIT() which should be
FSLIT()).
mkSysLocal no longer re-encodes its FastString argument each time it
is called.
I also fixed the -pgm options so that the argument can now optionally
be separted from the option.
Bugfix: PrelNames declared Names for several comparison primops, eg.
eqCharName, eqIntName etc. but these had different uniques from the
real primop names. I've moved these to PrimOps and defined them using
mkPrimOpIdName instead, and deleted some for which we don't have real
primops (Manuel: please check that things still work for you after
this change).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Switch over to the new hierarchical libraries
---------------------------------------------
This commit reorganises our libraries to use the new hierarchical
module namespace extension.
The basic story is this:
- fptools/libraries contains the new hierarchical libraries.
Everything in here is "clean", i.e. most deprecated stuff has
been removed.
- fptools/libraries/base is the new base package
(replacing "std") and contains roughly what was previously
in std, lang, and concurrent, minus deprecated stuff.
Things that are *not allowed* in libraries/base include:
Addr, ForeignObj, ByteArray, MutableByteArray,
_casm_, _ccall_, ``'', PrimIO
For ByteArrays and MutableByteArrays we use UArray and
STUArray/IOUArray respectively now.
Modules previously called PrelFoo are now under
fptools/libraries/GHC. eg. PrelBase is now GHC.Base.
- fptools/libraries/haskell98 provides the Haskell 98 std.
libraries (Char, IO, Numeric etc.) as a package. This
package is enabled by default.
- fptools/libraries/network is a rearranged version of
the existing net package (the old package net is still
available; see below).
- Other packages will migrate to fptools/libraries in
due course.
NB. you need to checkout fptools/libraries as well as
fptools/hslibs now. The nightly build scripts will need to be
tweaked.
- fptools/hslibs still contains (almost) the same stuff as before.
Where libraries have moved into the new hierarchy, the hslibs
version contains a "stub" that just re-exports the new version.
The idea is that code will gradually migrate from fptools/hslibs
into fptools/libraries as it gets cleaned up, and in a version or
two we can remove the old packages altogether.
- I've taken the opportunity to make some changes to the build
system, ripping out the old hslibs Makefile stuff from
mk/target.mk; the new package building Makefile code is in
mk/package.mk (auto-included from mk/target.mk).
The main improvement is that packages now register themselves at
make boot time using ghc-pkg, and the monolithic package.conf
in ghc/driver is gone.
I've updated the standard packages but haven't tested win32,
graphics, xlib, object-io, or OpenGL yet. The Makefiles in
these packages may need some further tweaks, and they'll need
pkg.conf.in files added.
- Unfortunately all this rearrangement meant I had to bump the
interface-file version and create a bunch of .hi-boot-6 files :-(
|
|
|
|
| |
track 5.03's change to PrelHandle.fillReadBuffer
|
|
|
|
| |
Tidy up imports
|
|
|
|
| |
Handle completely empty files without crashing in slurpFileExpandTabs.
|
|
|
|
|
|
|
|
|
| |
Deleted HsVersions.h #defines that were now past their use-by-dates; in
particular, make the assumption that a post-Haskell 1.4 compiler is now
used to compile ghc/compiler/
Hanging on to those FastString #defines is probably not worth it any longer,
either, but I punted on making that (much bigger) change.
|
|
|
|
| |
Removed unused imports.
|
|
|
|
| |
correct off-by-one error in hGetStringBuffer
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Change the story about POSIX headers in C compilation.
Until now, all C code in the RTS and library cbits has by default been
compiled with settings for POSIXness enabled, that is:
#define _POSIX_SOURCE 1
#define _POSIX_C_SOURCE 199309L
#define _ISOC9X_SOURCE
If you wanted to negate this, you'd have to define NON_POSIX_SOURCE
before including headers.
This scheme has some bad effects:
* It means that ccall-unfoldings exported via interfaces from a
module compiled with -DNON_POSIX_SOURCE may not compile when
imported into a module which does not -DNON_POSIX_SOURCE.
* It overlaps with the feature tests we do with autoconf.
* It seems to have caused borkage in the Solaris builds for some
considerable period of time.
The New Way is:
* The default changes to not-being-in-Posix mode.
* If you want to force a C file into Posix mode, #include as
the **first** include the new file ghc/includes/PosixSource.h.
Most of the RTS C sources have this include now.
* NON_POSIX_SOURCE is almost totally expunged. Unfortunately
we have to retain some vestiges of it in ghc/compiler so that
modules compiled via C on Solaris using older compilers don't
break.
|
|
|
|
|
| |
Add {-# OPTION -fvia-C #-} so that the compiler can compile itself
in --make mode (yes, really!)
|
|
|
|
|
| |
- remove support for GHC < 4.00
- fixed to work with GHC 5.01 (new I/O system)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Make ghc compilable with itself after the implementation of handle
IO changed, by changing an ugly mess of #ifdefs and low-level
ghc-internals-specific kludges into a yet uglier mess with more
#ifdefs and kludges.
Wouldn't Haskell 98 implementation of a lexer be fast enough? :-)
This won't compile with older versions of ghc-5.01. You may temporarily
change 501 to 502 in #ifdefs here, or use an older ghc.
The compiler still doesn't work at all when compiled with itself:
it writes complete nonsense into .hc files.
A remaining error: ghc/lib/std doesn't link PrelHandle_hsc.o into
libHSstd.a. Function read_wrap is inline but for some reason it's
needed for linking some programs (e.g. ghc itself).
|
|
|
|
| |
put the NUL terminator in the right place in stringToStringBuffer.
|
|
|
|
| |
Try and fix the freeStringBuffer nightmare once and for all.
|
|
|
|
|
| |
More stuff to do with primop support in the interpreter. Also, track
some changes to the libraries.
|
|
|
|
|
| |
Adapt to the Addr/Ptr changes.
Throw away mkFastSubStringFO, mkFastSubStringFO#, eqStrPrefixFO.
|
|
|
|
| |
head -> head bootability wibbles (rm disallowed OPTIONS pragmas)
|
|
|
|
|
|
|
|
|
|
| |
When renaming, typechecking an expression from the user
interface, we may suck in declarations from interface
files (e.g. the Prelude). This commit takes account of that.
To do so, I did some significant restructuring in TcModule,
with consequential changes and tidy ups elsewhere in the type
checker. I think there should be fewer lines in total than before.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Results of today's hacking:
- We can now execute expressions from the GHCi prompt. However,
a problem with the typechecker environment means that identifiers
from outside the current module aren't resolved :-(
- loading up a multi-module program in the interpreter seems to
work. Interpreting is kinda slow (ok, very slow), but I'm hoping
it'll get better when I compile the interpreter w/ optimisation.
- :set sort of works - you can do ":set -dshow-passes", for example
- lots of bugfixes, etc.
|
|
|
|
| |
More small changes
|
|
|
|
| |
s/allocMemory__/malloc
|
|
|
|
|
| |
Wave goodbye to hscpp, GHC's lexer now understands the '# \d+ \".*\"'
output from cpp.
|
|
|
|
|
| |
Text => Show
_ByteArray => ByteArray
|
|
|
|
|
| |
Again: Addr is an abstract type in Addr, so import from PrelAddr instead.
Told you so...
|
|
|
|
| |
Bootstrapping fix, this time for slurpFile
|
|
|
|
|
| |
Emit a reasonable error message instead of crashing when there's an
unterminated literal-liberal in the source file.
|
|
|
|
| |
error.h --> stgerror.h
|
|
|
|
| |
Fix for compiling w/ ghc-2.10
|
|
|
|
| |
pre-4.03 didn't have __HASKELL98__, use something else.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Main things:
* Add splitProductType_maybe to DataCon.lhs, with type
splitProductType_maybe
:: Type -- A product type, perhaps
-> Maybe (TyCon, -- The type constructor
[Type], -- Type args of the tycon
DataCon, -- The data constructor
[Type]) -- Its *representation* arg types
Then use it in many places (e.g. worker-wrapper places) instead
of a pile of junk
* Clean up various uses of dataConArgTys, which were plain wrong because
they weren't passed the existential type arguments. Most of these calls
are eliminated by using splitProductType_maybe above. I hope I correctly
squashed the others. This fixes a bug that Meurig's programs showed up.
module FailGHC (killSustainer) where
import Weak
import IOExts
data Sustainer = forall a . Sustainer (IORef (Maybe a)) (IO ())
killSustainer :: Sustainer -> IO ()
killSustainer (Sustainer _ act) = act
The above program used to kill the compiler.
* A fairly concerted attack on the Dreaded Space Leak.
- Add Type.seqType, CoreSyn.seqExpr, CoreSyn.seqRules
- Add some seq'ing when building Ids and IdInfos
These reduce the space usage a lot
- Add CoreSyn.coreBindsSize, which is pretty strict in the program,
and call it when we have -dshow-passes.
- Do not put the inlining in an Id that is being plugged into
the result-expression of the simplifier. This cures
a the 'wedge' in the space profile for reasons I don't understand fully
Together, these things reduce the max space usage when compiling PrelNum from
17M to about 7Mbytes.
I think there are now *too many* seqs, and they waste work, but I don't have
time to find which ones.
Furthermore, we aren't done. For some reason, some of the stuff allocated by
the simplifier makes it through all during code generation and I don't see why.
There's a should-be-unnecessary call to coreBindsSize in Main.main which
zaps some, but not all of this space.
-dshow-passes reduces space usage a bit, but I don't think it should really.
All the measurements were made on a compiler compiled with profiling by
GHC 3.03. I hope they carry over to other builds!
* One trivial thing: changed all variables 'label' to 'lbl', becuase the
former is a keyword with -fglagow-exts in GHC 3.03 (which I was compiling with).
Something similar in StringBuffer.
|
|
|
|
| |
Make this more Haskell 1.3-insensitive
|
|
|
|
| |
writeHandle has been removed.
|
|
|
|
| |
Don't chop off the last character of the buffer.
|