diff --git a/gcc/cobol/gcobol.1 b/gcc/cobol/gcobol.1
index 204def16b2736d283078872a38859e04a1de0b79..8dd40e86cbef5df3bcb20c74e53afb206ef11942 100644
--- a/gcc/cobol/gcobol.1
+++ b/gcc/cobol/gcobol.1
@@ -5,7 +5,7 @@
 .Os Linux
 .Sh NAME
 .Nm gcobol
-.Nd Features of the \*[gcobol]
+.Nd \*[gcobol]
 .Sh SYNOPSIS
 .Nm
 .Op Fl D Ns Ar name Ns Oo Li = Ns Ar value Oc
@@ -246,13 +246,15 @@ constants.
 .Pp
 Only a few such non-standard constructs are accepted, and
 .Nm
-makes no claim or aspiration to emulate other compilers.  But to the
-extent that a feature is popular but nonstandard, this
-option provides a way to support it, or add it.
+makes no claim to emulate other compilers.  But to the extent that a
+feature is popular but nonstandard, this option provides a way to
+support it, or add it.
 .
 .It Fl preprocess Ar preprocess-filter
 After all CDF text-manipulation has been applied, and before the
-prepared \*[lang] is sent to the cobol1 compiler, the input may be
+prepared \*[lang] is sent to the
+.Sy cobol1
+compiler, the input may be
 further altered by one or more filters.  In the tradition of
 .Xr sed 1 ,
 each
@@ -267,6 +269,18 @@ name matches
 .Ar preprocess-filter .
 The first one found is used.  If none is found, an error is reported
 and the compiler is not invoked.
+.Pp
+The
+.Fl preprocess
+option may appear more than once on the command line.  Each 
+.Ar preprocess-filter
+is applied in turn, in order of appearance.  
+.Pp
+The 
+.Ar preprocess-filter
+should return a zero exit status, indicating success.  If it returns a
+nonzero exit status, an error is reported and the compiler is not
+invoked.
 .
 .It Fl fflex-debug Ns Li , Fl fyacc-debug
 produce messages useful for compiler development.  The
@@ -373,6 +387,11 @@ At the present time, this is an all-or-nothing setting.  Support for
 and
 .Sy CODESET ,
 which would allow conversion between encodings, remains a future goal.
+.Pp
+See also
+.Sx "Feature-set Variables" ,
+below.
+.
 .Sh REDEFINES ... USAGE POINTER
 Per ISO, an item that
 .Sy REDEFINES
@@ -388,11 +407,15 @@ with
 whose redefined member is a 4-byte
 .Sy USAGE COMP-5
 (usually
-.Sy PIC S9(8) Ns ).
+.Sy PIC S9(8) Ns ),
+or vice-versa.
 In that case, the redefined member is re-sized to be 8 bytes, to
 accommodate the pointer.  This feature allows pointer arithmetic on a
 64-bit system with source code targeted at a 32-bit system.
-.Sy
+.Pp
+See also
+.Sx "Feature-set Variables" ,
+below.
 .
 .Sh IMPLEMENTATION NOTES
 .Nm
@@ -918,13 +941,20 @@ was invoked.
 .Ss Binary floating point DISPLAY
 How the DISPLAY presents binary floating point numbers depends on the value.
 .Pp
-When a value has six or fewer decimal digits to the left of the decimal point, it is expressed as 123456.789…
+When a value has six or fewer decimal digits to the left of the
+decimal point, it is expressed as
+.Em 123456.789... .
 .Pp
-When a value is less than 1 and has no more than three zeroes to the right of the decimal point, it is expressed as 0.0001234.\|.\|.
+When a value is less than 1 and has no more than three zeroes to the
+right of the decimal point, it is expressed as
+.Em 0.0001234... .
 .Pp
-Otherwise, exponential notation is used: 1.23456E+7
+Otherwise, exponential notation is used:
+.Em 1.23456E+7 .
+.Pp
+In all cases, trailing zeroes on the right of the number are removed
+from the displayed value.
 .Pp
-In all cases, trailing zeroes on the right of the number are removed from the displayed value.
 .Bl -tag -compact -width FLOAT-EXTENDED
 .It COMP-1
 displayed with 9 decimal digits.
@@ -934,16 +964,26 @@ displayed with 17 decimal digits.
 displayed with 36 decimal digits.
 .El
 .Pp
-Those digit counts are consistent with the IEEE 754 requirements for information interchange.  As one example, the description for COMP-2 binary64 values (per Wikipedia)
+Those digit counts are consistent with the IEEE 754 requirements for
+information interchange.  As one example, the description for COMP-2
+binary64 values (per Wikipedia).
 .Pp
-If an IEEE 754 double-precision number is converted to a decimal string with at least 17 significant digits, and then converted back to double-precision representation, the final result must match the original number.
+If an IEEE 754 double-precision number is converted to a decimal
+string with at least 17 significant digits, and then converted back to
+double-precision representation, the final result must match the
+original number.
 .Pp
-17 digits was chosen so that the DISPLAY statement shows the contents of a COMP-2 variable without hiding any information.
+17 digits was chosen so that the
+.Sy DISPLAY
+statement shows the contents
+of a COMP-2 variable without hiding any information.
 .
 .Ss Binary floating point MOVE
-During MOVE statements, floating-point values are truncated.  It
-will not be unusual for Numeric Display values to be altered when
-moved through a floating-point value:
+During a
+.Sy MOVE
+statement, a floating-point value may be truncated.  It will not be
+unusual for Numeric Display values to be altered when moved through a
+floating-point value.
 .Pp
 This program:
 .Bd -literal
@@ -969,9 +1009,11 @@ However, the internal implementation can produce results that might be seem surp
     The result of MOVE COMP2    TO PICV999 is 0055.110
 .Ed
 .Pp
-The source of this inconsistency is the way GCOBOL stores and converts
+The source of this inconsistency is the way
+.Nm
+stores and converts
 numbers.  Converting the floating-point value to the numeric display
-value 0055110 is done by multiplying 55.109999… by 1,000 and then
+value 0055110 is done by multiplying 55.109999...\& by 1,000 and then
 truncating the result to an integer.  And it turns out that even
 though 55.11 can’t be represented in floating-point as an exact value,
 the product of the multiplication, 55110, is an exact value.
@@ -1117,7 +1159,7 @@ errors.
 .Sh FILES
 Executables produced by
 .Nm
-require a runtime support library,
+require the runtime support library
 .Pa libgcobol ,
 which is provided both as a static library and as a shared object.
 .
@@ -1127,7 +1169,7 @@ which is provided both as a static library and as a shared object.
 The ISO standard leaves the default file organization up to the implementation; in
 .Nm ,
 the default is
-.Sy "LINE SEQUENTIAL" .
+.Sy "SEQUENTIAL" .
 .
 .Ss On-Disk Format
 Any ability to use files produced by other \*[lang] compilers, or for
@@ -1290,24 +1332,14 @@ This compiler,
 was begun by COBOLworx (www.cobolworx.com) in the fall of 2021. The
 project announced a complete implementation of the core language
 features in December 2022.
-.Pp
-Besides
-.Nm ,
-other active free \*[lang] compiler projects include
-.sp
-.Bl -tag -compact -width GnuCOBOL
-.It GnuCOBOL
-https://www.gnu.org/software/gnucobol/
-.It Otterkit
-https://otterkit.com/
-.El
 .
 .Sh AUTHORS
 .Bl -tag -compact
 .It "James K. Lowden"
 (jklowden@cobolworx.com) is responsible for the parser.
 .It "Robert Dubner"
-(rdubner@cobolworx.com) is responsible for producing the GIMPLE tree, which is input to the GCC back-end.
+(rdubner@cobolworx.com) is responsible for producing the GIMPLE tree,
+which is input to the GCC back-end.
 .
 .Sh CAVEATS
 .Bl -bullet -compact
@@ -1316,8 +1348,6 @@ https://otterkit.com/
 has been tested only on x64 and Apple M1 processors running Linux in
 64-bit mode.
 .It
-There is no support for Packed Decimal.
-.It
 The I/O support has not been extensively tested, and does not
 implement or emulate many features related to VSAM and other mainframe
 subsystems.  While LINE-SEQUENTIAL files are ordinary text files that
diff --git a/gcc/cobol/parse_util.h b/gcc/cobol/parse_util.h
index bc733ed9107418387bec9564f8344509dea378cc..792e26628fa9020a1abb8522acabccc1e6bf09bf 100644
--- a/gcc/cobol/parse_util.h
+++ b/gcc/cobol/parse_util.h
@@ -301,6 +301,16 @@ intrinsic_cname( int token ) {
   return p == function_descrs_end?  NULL :  p->cname;
 }
 
+const char *
+intrinsic_function_name( int token ) {
+  auto p = std::find_if( function_descrs,
+                         function_descrs_end,
+                         [token]( const auto& descr ) {
+                           return token == descr.token;
+                         } );
+  return p == function_descrs_end?  NULL :  p->name;
+}
+
 /*
  * Provide supplied function parameters.
  * Return pointer in 1st invalid parameter type.
diff --git a/gcc/cobol/scan.l b/gcc/cobol/scan.l
index 62d3f38170999d17f4089849bf9204a497deebdc..d1fd0b9edfca5515f0369c9ce8c487d70cdd366b 100644
--- a/gcc/cobol/scan.l
+++ b/gcc/cobol/scan.l
@@ -1735,16 +1735,23 @@ COPY		{
    {NAME}{OSPC}/[(] { /* If /{OSPC}, "dangerous trailing context" "*/
                   if( is_integer_token() ) return numstr_of(yytext);
                   ydflval.string = yylval.string = strdup(yytext);
-#if 0
-		  warnx("%s:%d: function '%s' has yyleng %d", __FILE__, __LINE__,
-			 yylval.string, yyleng);
-#endif
-                  int token = keyword_tok(null_trim(yylval.string));
-                  if( token ) return token;
-#if 0
-		  warnx("%s:%d: function '%s' is token %d", __FILE__, __LINE__,
-			 yylval.string, token);
-#endif
+
+                  int token = keyword_tok(null_trim(yylval.string), true);
+		  auto elem = symbol_field(PROGRAM, 0, yylval.string);
+
+                  if( token && ! elem ) { // not a data item name
+                    // If token is an intrinsic, and not in Repository, pretend
+                    // it's a name and let the parser sort it out.
+                    auto name = intrinsic_function_name(token);
+                    if( ! name ) return token; // valid keyword, like IF
+                    if( token == intrinsic_repository_tok(name) ) {
+                      return token; // intrinsic and in repository
+                    }
+                    yyerrorv("error: 'FUNCTION %s' required because %s "
+			     "is not mentioned in REPOSITORY paragraph",  
+			     name, name);
+                  }
+
 		  if( 0 != (token = intrinsic_repository_tok(yylval.string)) ) {
 		    auto e = symbol_function(0, yylval.string);
 		    assert(e);
diff --git a/gcc/cobol/symbols.h b/gcc/cobol/symbols.h
index 67643930e5311636b5d9d533cbe731c8b33cb893..463a0ecf161a109d84725eda9415716fccaf388d 100644
--- a/gcc/cobol/symbols.h
+++ b/gcc/cobol/symbols.h
@@ -2039,6 +2039,8 @@ bool is_elementary( enum cbl_field_type_t type );
 
 bool is_numeric_edited( const char picture[] );
 
+const char * intrinsic_function_name( int token );
+
 size_t current_program_index();
 const char * current_declarative_section_name();