From 81f22c02200f3b9006b21fbd3fd754ffd43769e9 Mon Sep 17 00:00:00 2001 From: "James K. Lowden" <jklowden@symas.com> Date: Fri, 14 Feb 2025 16:09:54 -0500 Subject: [PATCH] whitepace --- gcc/cobol/Make-lang.in | 38 ++-- gcc/cobol/gcobol.1 | 88 ++++----- gcc/cobol/gcobol.3 | 28 +-- gcc/cobol/gengen.cc | 61 +++--- gcc/cobol/genmath.cc | 2 +- gcc/cobol/lexio.cc | 130 ++++++------- gcc/cobol/parse.y | 407 ++++++++++++++++++++--------------------- gcc/cobol/scan.l | 58 +++--- 8 files changed, 405 insertions(+), 407 deletions(-) diff --git a/gcc/cobol/Make-lang.in b/gcc/cobol/Make-lang.in index cc37639e295e..26dec534c3a4 100644 --- a/gcc/cobol/Make-lang.in +++ b/gcc/cobol/Make-lang.in @@ -1,5 +1,5 @@ # Top level -*- makefile -*- fragment for Cobol -# Copyright (C) 2016 Free Software Foundation, Inc. +# Copyright (C) 2021-2024 Free Software Foundation, Inc. # This file is part of GCC. @@ -42,7 +42,6 @@ gcobol_INSTALL_NAME := $(shell echo gcobol|sed '$(program_transform_name)') gcobol_TARGET_INSTALL_NAME := $(target_noncanonical)-$(shell echo gcobol|sed '$(program_transform_name)') cobol: cobol1$(exeext) - .PHONY: cobol BINCLUDE ?= ./gcc @@ -159,23 +158,6 @@ cobol/cdf.c: cobol/cdf.y $(BISON) -o $@ $(YFLAGS) \ --defines=cobol/cdf.h --report-file=cobol/cdf.out $< - -# The src<foo> targets are executed if -# ‘--enable-generated-files-in-srcdir’ was specified as a configure -# option. -# -# srcextra copies generated dependencies into the source -# directory. This is used for files such as Flex/Bison output: files -# that are not version-controlled but should be included in any -# release tarballs. -# -# Although versioned snapshots require Flex to be installed, they do -# not require Bison. Release tarballs always include Flex/Bison -# output, and do not require those tools to be installed. - -cobol.srcextra: cobol/parse.c cobol/cdf.c - ln -f $^ cobol/parse.h cobol/cdf.h $(srcdir)/cobol/ - # See "Trailing context is getting confused with trailing optional patterns" # in Flex manual. We suppress those messages, as a convenience. FLEX_WARNING = warning, dangerous trailing context @@ -263,6 +245,24 @@ cobol/scan.o: cobol/scan.c \ cobol/cdf.c \ cobol/parse.c +# +# The src<foo> targets are executed if +# ‘--enable-generated-files-in-srcdir’ was specified as a configure +# option. +# +# srcextra copies generated dependencies into the source +# directory. This is used for files such as Flex/Bison output: files +# that are not version-controlled but should be included in any +# release tarballs. +# +# Although versioned snapshots require Flex to be installed, they do +# not require Bison. Release tarballs always include Flex/Bison +# output, and do not require those tools to be installed. +# +cobol.srcextra: cobol/parse.c cobol/cdf.c cobol/scan.c + ln -f $^ cobol/parse.h cobol/cdf.h $(srcdir)/cobol/ + + # And the cobol1.exe front end cobol1$(exeext): $(cobol1_OBJS) $(BACKEND) $(LIBDEPS) attribs.o diff --git a/gcc/cobol/gcobol.1 b/gcc/cobol/gcobol.1 index 415ad36aa786..64c017c22144 100644 --- a/gcc/cobol/gcobol.1 +++ b/gcc/cobol/gcobol.1 @@ -64,18 +64,18 @@ will include a entry point calling the first PROGRAM-ID in .Ar filename .It Fl main Ns Li = Ns Ar filename:program-id -The .o object module for +The .o object module for .Ar filename -will include a +will include a .Fn main -entry point that calls the +entry point that calls the .Ar program-id entry point .It Fl nomain No .Fn main entry point will be generated by this -compilation. The +compilation. The .Fl nomain option is incompatible with .Fl main , @@ -83,11 +83,11 @@ and is implied by .Fl shared . It is also implied by .Fl c -when there is no +when there is no .Fl main present. .Pp -See below for examples showing the use of +See below for examples showing the use of .Fl main and .Fl nomain. @@ -104,7 +104,7 @@ line-number consistency with the input, blank lines are retained. .Pp Unlike the C compiler, This option does not prevent compilation. To prevent compilation, use the option -.D1 Fl Sy fsyntax-only +.D1 Fl Sy fsyntax-only also. .It Fl fdefaultbyte Ns Li = Ns Ar value Use @@ -118,7 +118,7 @@ items are initialized to zero. This option overrides the default with Invoke only the parser. Check the code for syntax errors, but don't do anything beyond that. .It Fl copyext Ar ext -For the CDF directive +For the CDF directive .D1 COPY Ar name if .Ar name @@ -135,7 +135,7 @@ If is all uppercase or all lowercase, both forms are tried, with preference given to the one supplied. If .Ar ext is mixed-case, only that version is tried. -For example, with +For example, with .D1 Fl copyext Ar .abc given the CDF directive .D1 COPY name @@ -144,7 +144,7 @@ will add to possible names searched .Ql name.abc and .Ql name.ABC -in that order. +in that order. .It Fl ffixed-form Use strict .Em "Reference Format" @@ -192,7 +192,7 @@ auto-detects the source code format by examining the of the first line of the first file: if those characters are all digits or blanks, the file is assumed to be in .Em "reference format" , -with the indicator area in column 7. +with the indicator area in column 7. .Pp . .It Fl fcobol-exceptions Ar exception Op Ns , Ns Ar exception Ns ... @@ -203,8 +203,8 @@ CDF directive. This option enables one or more exception conditions by default, as though .Sy TURN -had appeared at the top of the first source code file. -This option may also appear more than once on the command line. +had appeared at the top of the first source code file. +This option may also appear more than once on the command line. .Pp The value of .Ar exception @@ -327,13 +327,13 @@ each .Ar preprocess-filter reads from standard input and writes to standard output. .Pp -To supply options to +To supply options to .Ar preprocess-filter , use a comma-separated string, similar to how linker options are supplied to .Fl Sy Wl . (Do not put any spaces after the commas, because the shell will treat it as an option separator.) .Nm -replaces each comma with a space when +replaces each comma with a space when .Ar preprocess-filter is invoked. For example, .D1 Fl preprocess Li tee,output.cbl @@ -352,11 +352,11 @@ and the compiler is not invoked. .Pp The .Fl preprocess -option may appear more than once on the command line. Each +option may appear more than once on the command line. Each .Ar preprocess-filter -is applied in turn, in order of appearance. +is applied in turn, in order of appearance. .Pp -The +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 @@ -376,7 +376,7 @@ option shows the shift and reduce actions taken by the parser. .D1 gcobol -main= Ns Ar xyz.cob Ar xyz.cob These are equivalent. The .Ar xyz.cob -code is compiled and a +code is compiled and a .Fn main function is inserted that calls the first PROGRAM-ID in the @@ -386,10 +386,10 @@ source file. .D1 gcobol -nomain Ar xyz.cob Ar elsewhere.o The .Fl nomain -option prevents a +option prevents a .Fn main function from being generated by the gcobol compiler. -A +A .Fn main entry point must be present in the .Ar elsewhere.o @@ -433,7 +433,7 @@ file will contain a entry point that calls the first PROGRAM-ID in .Ar bbb . The fourth links the three .o files into an -.Ar a.out . +.Ar a.out . . .Sh EBCDIC The @@ -583,7 +583,7 @@ The following are implemented: .Pp .Bl -tag -offset 5n -compact .It EC-FUNCTION-ARGUMENT -for the following functions: +for the following functions: .Bl -item -compact .It ACOS @@ -617,8 +617,8 @@ for both fixed-point and floating-point division .El .Pp As of this writing, no \*[lang] compiler documents a complete -implementation of \*[isostd] Exception Conditions. -.Nm +implementation of \*[isostd] Exception Conditions. +.Nm will give priority to those ECs that the user community deems most valuable. . @@ -710,7 +710,7 @@ argument, the target is set to .Sy LOW-VALUES . .Pp The system command line parameters can also be accessed through the LINKAGE -SECTION in the program where execution starts. The data structure looks like +SECTION in the program where execution starts. The data structure looks like this: .Bd -literal linkage section. @@ -798,7 +798,7 @@ types, most of which alias LB LB LB LB LB LB LB LB L L L L . -COMP-5 Compatible +COMP-5 Compatible Picture BINARY Type Bytes Value T{ BINARY-CHAR [UNSIGNED] @@ -868,7 +868,7 @@ supports the ISO syntax for returning an exit status to the operating system, .Pp .D1 STOP RUN Oo WITH Oc Bro NORMAL | ERROR Brc Oo STATUS Oc Ar status .Pp -In addition, +In addition, .Nm also supports the IBM syntax for returning an exit status to the operating system. Use the @@ -916,9 +916,9 @@ as a compilation variable to have the value .Ar expression . If .Ar name -was previously defined, +was previously defined, .Sy OVERRIDE -is required, else the directive is invalid. +is required, else the directive is invalid. .Sy AS PARAMETER is accepted, but has no effect in .Nm . @@ -927,9 +927,9 @@ is accepted, but has no effect in releases the definition .Ar name , making it subsequently invalid for use. -.\" ISO requires AS; cdf.y does not. +.\" ISO requires AS; cdf.y does not. . -.It >> Ns Sy IF Ar cce Ar text Oo >> Ns Sy ELSE Ar alt-text Oc Li >> Ns Sy END-IF +.It >> Ns Sy IF Ar cce Ar text Oo >> Ns Sy ELSE Ar alt-text Oc Li >> Ns Sy END-IF evaluates .Ar cce , a @@ -943,7 +943,7 @@ command-line parameter. If true, the \*[lang] text .Ar text is compiled. If false, .Ar else-text , -if present, is compiled. +if present, is compiled. .Bo Sy IS Bo Sy NOT Bc Bc Sy DEFINED is supported. Boolean literals are not supported. . @@ -952,7 +952,7 @@ Not implemented. .El . .Ss Other CDF Directives -.Bl -tag -width >>PROPAGATE +.Bl -tag -width >>PROPAGATE .It >> Ns Sy CALL-CONVENTION Ar convention .Ar convention may be one of: @@ -971,20 +971,20 @@ An alias for >>\c .Sy "CALL-CONVENTION C" . .El .It >> Ns Sy COBOL-WORDS EQUATE Ar keyword Sy WITH Ar alias -makes +makes .Ar alias -a synonym for +a synonym for .Ar keyword . .It >> Ns Sy COBOL-WORDS UNDEFINE Ar keyword .Ar keyword is removed from the \*[lang] grammar. Use of it in a program will provoke -a syntax error from the compiler. +a syntax error from the compiler. .It >> Ns Sy COBOL-WORDS SUBSTITUTE Ar keyword Sy BY Ar new-word .Ar keyword is deleted as a keyword from the grammar, replaced by .Ar new-word . .Ar keyword -may thereafter be used as a user-defined word. +may thereafter be used as a user-defined word. .It >> Ns Sy COBOL-WORDS RESERVE Ar new-word Treat .Ar new-word @@ -994,7 +994,7 @@ keyword or as a user-defined word. .It >> Ns Sy DISPLAY Ar string ... Write .Ar string -to standard error as a warning message. +to standard error as a warning message. .It >> Ns Sy SOURCE Ar format .Ar format may be one of: @@ -1042,7 +1042,7 @@ statement that triggered the exception condition. . .Ss Feature-set Variables Some command-line options affect CDF -.Em "feature-set" +.Em "feature-set" variables that are special to .Nm . They can be set and tested using @@ -1072,7 +1072,7 @@ the directive must appear before .Sy PROGRAM-ID . .Pp To test a feature-set variable, use -.Dl >>IF Ar feature Li DEFINED +.Dl >>IF Ar feature Li DEFINED .. .Ss Copybooks .Nm @@ -1359,7 +1359,7 @@ If defined, specifies the directory paths to be used by the runtime library, .Pa libgcobol.so , to locate shared objects. -Like +Like .Ev LD_LIBRARY_PATH , it may contain several directory names separated by a colon .Pq Ql \&: . @@ -1373,7 +1373,7 @@ For each such file, .Xr dlopen 3 is attempted, and, if successful .Xr dlsym 3 . -No relationship is defined between the symbol's name and the filename. +No relationship is defined between the symbol's name and the filename. .Pp Without .Ev COBPATH , @@ -1383,7 +1383,7 @@ behave as one might expect of any program compiled with gcc. Any shared objects needed by the program are mentioned on the command line with a .Fl l Ns Ar library -option, and are found by following the executable's +option, and are found by following the executable's .Pa RPATH or otherwise per the configuration of the runtime linker, .Xr ld.so 8 . diff --git a/gcc/cobol/gcobol.3 b/gcc/cobol/gcobol.3 index a9bed854c820..adc141a7aadc 100644 --- a/gcc/cobol/gcobol.3 +++ b/gcc/cobol/gcobol.3 @@ -61,7 +61,7 @@ implement sequential, relative, and indexed file operations over files whose On Disk Format (ODF) is defined by .Nm . A user wishing to use another library that implements the same -functionality over a different ODF must supply a different implementation of +functionality over a different ODF must supply a different implementation of .Fn gcobol_fileops , plus 7 functions, as described in this document. The pointers to those user-implemented functions are placed in a C++ object of type @@ -69,10 +69,10 @@ those user-implemented functions are placed in a C++ object of type and an instantiation of that type is returned by .Fn gcobol_fileops . The compiled program initializes I/O operations by calling that -function the first time any file is opened. +function the first time any file is opened. .Pp Each function takes as its first argument a pointer to a -.Vt cblc_file_t +.Vt cblc_file_t object, which is analogous to a .Vt FILE object used in the C @@ -85,7 +85,7 @@ there. Notably, the outcome of any operation is stored in that structure in the .Va file_status member, not as a return code. Information about the -.Em operation +.Em operation (as opposed to the .Em file ) appear as parameters to the function. @@ -99,14 +99,14 @@ that is reserved for the user: User-supplied I/O functions may assign and dereference .Pa implementation . .Nm -will preserve the value, but never references it. +will preserve the value, but never references it. .Pp The 7 function pointers in .Vt gcobol_io_t are .Bl -hang -width Rewrite .It Open -.Ft void +.Ft void .Fn open_t "cblc_file_t *file" "char *filename" "int mode_char" "int is_quoted" .br parameters: @@ -161,7 +161,7 @@ parameters: .It Ar relop is one of .Bl -hang -width LT -compact -.It Li 0 +.It Li 0 means .Sq < .It Li 1 @@ -183,7 +183,7 @@ means .It Ar first_last_key is the key number (starting at 1) of the key within the .Vt cblc_file_t -structure. +structure. .It Ar length is the size of the key (TODO: per the START statement?) .El @@ -201,7 +201,7 @@ NEXT .It Ar \0N represents a key number, starting with 1, in the .Vt cblc_file_t -structure. The value of that key is used to find the record, and read it. +structure. The value of that key is used to find the record, and read it. .El .El .It Write @@ -216,7 +216,7 @@ address of in-memory buffer to write .It Ar length length of in-memory buffer to write .It Ar after -has the value 1 if the +has the value 1 if the .D1 "AFTER ADVANCING n LINES" phrase was present in the .Sy WRITE @@ -288,7 +288,7 @@ This function populates a object with the above function pointers. The compiled binary begins by calling .Fn gcobol_fileops Ns , -and then uses the supplied pointers to effect I/O. +and then uses the supplied pointers to effect I/O. .El . .\" The following commands should be uncommented and @@ -317,12 +317,12 @@ It is not intended to be compatible with any other ODF. That is, .Sy libgcobolio.so cannot be used to exchange data with any other \*[lang] implementation. .Pp -The purpose of the +The purpose of the .Vt gcobol_io_t structure is to allow the use of other I/O implementations with other ODF representations. .\" .Sh HISTORY .\" .Sh AUTHORS .Sh CAVEATS -The library is not well tested, not least because it is not implemented. +The library is not well tested, not least because it is not implemented. .Sh BUGS -The future is yet to come. +The future is yet to come. diff --git a/gcc/cobol/gengen.cc b/gcc/cobol/gengen.cc index f044d45e5305..b84c3fa0fc98 100644 --- a/gcc/cobol/gengen.cc +++ b/gcc/cobol/gengen.cc @@ -846,7 +846,7 @@ gg_struct_field_ref(const tree base, const char *field) tree type = TREE_TYPE(base); if( POINTER_TYPE_P (type) ) { - tree pointer_type = TREE_TYPE(base); + tree pointer_type = TREE_TYPE(base); tree base_pointer_type = TREE_TYPE(pointer_type); // We need a COMPONENT_REF which is an INDIRECT_REF to a FIELD_DECL tree field_decl = gg_find_field_in_struct(base, field); @@ -1095,7 +1095,7 @@ gg_define_variable(tree type_decl, gg_variable_scope_t vs_scope) } tree -gg_define_variable( tree type_decl, +gg_define_variable( tree type_decl, const char *var_name, gg_variable_scope_t vs_scope, tree initial_value) @@ -1620,7 +1620,7 @@ static tree gg_get_larger_type(tree A, tree B) { tree larger = TREE_TYPE(B); - if( TREE_INT_CST_LOW(TYPE_SIZE(TREE_TYPE(A))) + if( TREE_INT_CST_LOW(TYPE_SIZE(TREE_TYPE(A))) > TREE_INT_CST_LOW(TYPE_SIZE(TREE_TYPE(B))) ) { larger = TREE_TYPE(A); @@ -2171,8 +2171,8 @@ gg_printf(const char *format_string, ...) // Because we don't actually use stderr ourselves, we just pick it up as a // VOID_P and pass it along to fprintf() - tree t_stderr = gg_declare_variable(VOID_P, "stderr", - NULL_TREE, + tree t_stderr = gg_declare_variable(VOID_P, "stderr", + NULL_TREE, vs_external_reference); gg_push_context(); @@ -2258,7 +2258,7 @@ gg_fprintf(tree fd, int nargs, const char *format_string, ...) va_end (ap); static tree function = NULL_TREE; - + if( !function ) { function = gg_get_function_address(INT, "sprintf"); @@ -2310,7 +2310,7 @@ gg_write(tree fd, tree buf, tree count) void gg_memset(tree dest, const tree value, tree size) { - tree the_call = + tree the_call = build_call_expr_loc(location_from_lineno(), builtin_decl_explicit (BUILT_IN_MEMSET), 3, @@ -2323,7 +2323,7 @@ gg_memset(tree dest, const tree value, tree size) tree gg_memchr(tree buf, tree ch, tree length) { - tree the_call = fold_convert( + tree the_call = fold_convert( pvoid_type_node, build_call_expr_loc(location_from_lineno(), builtin_decl_explicit (BUILT_IN_MEMCHR), @@ -2387,7 +2387,7 @@ gg_memdup(tree data, size_t length) void gg_strcpy(tree dest, tree src) { - tree the_call = + tree the_call = build_call_expr_loc(location_from_lineno(), builtin_decl_explicit (BUILT_IN_STRCPY), 2, @@ -2399,7 +2399,7 @@ gg_strcpy(tree dest, tree src) tree gg_strcmp(tree A, tree B) { - tree the_call = fold_convert( + tree the_call = fold_convert( integer_type_node, build_call_expr_loc(location_from_lineno(), builtin_decl_explicit (BUILT_IN_STRCMP), @@ -2431,7 +2431,7 @@ gg_close(tree int_A) tree gg_strncmp(tree char_star_A, tree char_star_B, tree size_t_N) { - tree the_call = fold_convert( + tree the_call = fold_convert( integer_type_node, build_call_expr_loc(location_from_lineno(), builtin_decl_explicit (BUILT_IN_STRNCMP), @@ -2446,7 +2446,7 @@ void gg_return(tree operand) { tree stmt; - + if( !gg_trans_unit.function_stack.size() ) { // I put this in to cope with the problem of two END PROGRAM statements, which @@ -2696,7 +2696,7 @@ gg_define_function(tree return_type, const char *funcname, ...) if(nparams > ARG_LIMIT) { yywarn("###### %10s in %s:%d", __func__, __FILE__,__LINE__ ); - yywarn("###### %d parameters? Really? Are you insane?", + yywarn("###### %d parameters? Really? Are you insane?", ARG_LIMIT+1); gcc_assert(false); } @@ -3002,7 +3002,7 @@ gg_push_context() // We are creating the initial context of the function: DECL_INITIAL(current_function->function_decl) = block; DECL_SAVED_TREE(current_function->function_decl) = bind_expr; - + // To avoid an N-squared time complexity when chaining blocks, we save the // current end of the chain of blocks: current_function->current_block = block; @@ -3051,7 +3051,7 @@ function_decl_from_name(tree return_type, tree arg_types[]) { tree fndecl; - std::unordered_map<std::string, tree>::const_iterator it = + std::unordered_map<std::string, tree>::const_iterator it = fndecl_from_name.find(function_name); if( it != fndecl_from_name.end() ) { @@ -3076,12 +3076,12 @@ gg_call_expr(tree return_type, const char *function_name, ...) // tree call_expr = gg_call_expr(...); // gg_assign( dest, call_expr ); - + // Note that everyt time call_expr is laid down, the function will be called, // so you probably don't want to do things like // gg_assign( dest1, call_expr ); // gg_assign( dest2, call_expr ); - + int nargs = 0; static tree arg_types[ARG_LIMIT+1]; static tree args[ARG_LIMIT+1]; @@ -3236,7 +3236,7 @@ gg_create_bind_expr() void gg_exit(tree exit_code) { - tree the_call = + tree the_call = build_call_expr_loc(location_from_lineno(), builtin_decl_explicit (BUILT_IN_EXIT), 1, @@ -3247,7 +3247,7 @@ gg_exit(tree exit_code) void gg_abort() { - tree the_call = + tree the_call = build_call_expr_loc(location_from_lineno(), builtin_decl_explicit (BUILT_IN_ABORT), 0); @@ -3257,7 +3257,7 @@ gg_abort() tree gg_strlen(tree psz) { - tree the_call = fold_convert( + tree the_call = fold_convert( size_type_node, build_call_expr_loc(location_from_lineno(), builtin_decl_explicit (BUILT_IN_STRLEN), @@ -3283,7 +3283,7 @@ gg_strdup(tree psz) tree gg_malloc(tree size) { - tree the_call = fold_convert( + tree the_call = fold_convert( pvoid_type_node, build_call_expr_loc(location_from_lineno(), builtin_decl_explicit (BUILT_IN_MALLOC), @@ -3295,7 +3295,7 @@ gg_malloc(tree size) tree gg_realloc(tree base, tree size) { - tree the_call = fold_convert( + tree the_call = fold_convert( pvoid_type_node, build_call_expr_loc(location_from_lineno(), builtin_decl_explicit (BUILT_IN_REALLOC), @@ -3320,7 +3320,7 @@ gg_malloc(size_t size) void gg_free(tree pointer) { - tree the_call = + tree the_call = build_call_expr_loc(location_from_lineno(), builtin_decl_explicit (BUILT_IN_FREE), 1, @@ -3388,9 +3388,9 @@ tree gg_string_literal(const char *string) { /* This is a message in a bottle. - - A genapi.cc program calling - + + A genapi.cc program calling + gg_call(VOID, "puts", build_string_literal(strlen(ach)+1, ach), @@ -3398,18 +3398,18 @@ gg_string_literal(const char *string) ten thousand times compiles about ten percent slower than a C program calling - + puts(ach); - + ten thousand times. Trapping through the C front end reveals that they do not call build_string_literal(). They instead use build_string() in a way that I gave up trying to figure out that produces, apparently, more efficient GENERIC. - + Their GENERIC: call_expr -> nop_expr -> addr_expr -> string_cst - + My GENERIC: call_expr -> addr_expr -> array_ref -> string_cst I tried for an hour to duplicate the C stuff, but made no headway. @@ -3475,4 +3475,3 @@ gg_insert_into_assembler(const char *format, ...) // And insert it as a statement gg_append_statement(asm_expr); } - diff --git a/gcc/cobol/genmath.cc b/gcc/cobol/genmath.cc index bd224da07a25..b890c4377026 100644 --- a/gcc/cobol/genmath.cc +++ b/gcc/cobol/genmath.cc @@ -1722,7 +1722,7 @@ parser_subtract(cbl_refer_t cref, // cref = aref - bref B[0] = bref; parser_subtract(1, C, // Beware: C = A - B, but the order has changed - 1, B, + 1, B, 1, A, giving_e, NULL, diff --git a/gcc/cobol/lexio.cc b/gcc/cobol/lexio.cc index 1e71a9fa85e5..f5d05ac94322 100644 --- a/gcc/cobol/lexio.cc +++ b/gcc/cobol/lexio.cc @@ -131,7 +131,7 @@ static char * remove_inline_comment( char *bol, char *eol ) { static char ends = '\0'; char *nl = std::find(bol, eol, '\n'); - + if( bol < nl ) { std::swap(*nl, ends); char *comment = strstr(bol, "*>"); @@ -265,12 +265,12 @@ recognize_replacements( filespan_t mfile, std::list<replace_t>& pending_replacem if( yy_flex_debug ) { size_t n = count_newlines(mfile.data, found.p); dbgmsg("%s:%d first '%.*s' is on line %zu (offset %zu)", __func__, __LINE__, - directive.before.size(), directive.before.p, - ++n, found.p - mfile.data); + directive.before.size(), directive.before.p, + ++n, found.p - mfile.data); } } else { - dbgmsg("%s:%d not found: '%s' in \n'%.*s'", __func__, __LINE__, - directive.before.p, int(strlen(directive.before.p)), mfile.cur); + dbgmsg("%s:%d not found: '%s' in \n'%.*s'", __func__, __LINE__, + directive.before.p, int(strlen(directive.before.p)), mfile.cur); } futures.push_back( future_replacement_t(directive, found) ); } @@ -295,10 +295,10 @@ recognize_replacements( filespan_t mfile, std::list<replace_t>& pending_replacem if( yy_flex_debug ) { size_t n = std::count((const char *)mfile.data, recognized.before.p, '\n'); dbgmsg( "%s:%d: line %zu @ %zu: '%s'\n/%.*s/%.*s/", __func__, __LINE__, - ++n, next.found.p - mfile.data, - next.directive.before.p, - int(recognized.before.size()), recognized.before.p, - int(recognized.after.size()), recognized.after.p ); + ++n, next.found.p - mfile.data, + next.directive.before.p, + int(recognized.before.size()), recognized.before.p, + int(recognized.after.size()), recognized.after.p ); } // Update the futures element for this pattern @@ -313,8 +313,8 @@ recognize_replacements( filespan_t mfile, std::list<replace_t>& pending_replacem size_t n = std::count((const char *)mfile.data, next.found.p, '\n'); if( false ) dbgmsg("%s:%d next '%.*s' will be on line %zu (offset %zu)", __func__, __LINE__, - next.directive.before.size(), next.directive.before.p, - ++n, next.found.p - mfile.data); + next.directive.before.size(), next.directive.before.p, + ++n, next.found.p - mfile.data); } pnext = std::min_element(futures.begin(), futures.end()); } @@ -349,7 +349,7 @@ check_source_format_directive( filespan_t& mfile ) { } mfile.cur = const_cast<char*>(cm[0].second); dbgmsg( "%s:%d: %s format set, on line %zu", __func__, __LINE__, - indicator.column == 7? "FIXED" : "FREE", mfile.lineno() ); + indicator.column == 7? "FIXED" : "FREE", mfile.lineno() ); erase_line(const_cast<char*>(cm[0].first), const_cast<char*>(cm[0].second)); } @@ -455,7 +455,7 @@ last_newline (const char *p, const char *pend ) { } /* * For some statement parsed with regex_search, set yyloc to indicate the line - * and column spans of the term. Assume stmt begins at the start of a line. + * and column spans of the term. Assume stmt begins at the start of a line. */ static void update_yylloc( const csub_match& stmt, const csub_match& term ) { @@ -465,17 +465,17 @@ update_yylloc( const csub_match& stmt, const csub_match& term ) { public: dump_loc_on_exit() { if( getenv( "update_yylloc" ) ) - location_dump( "update_yylloc", __LINE__, "begin", yylloc); + location_dump( "update_yylloc", __LINE__, "begin", yylloc); } ~dump_loc_on_exit() { if( getenv( "update_yylloc" ) ) - location_dump( "update_yylloc", __LINE__, "end ", yylloc); + location_dump( "update_yylloc", __LINE__, "end ", yylloc); } } dloe; - + size_t nline = std::count( stmt.first, term.second, '\n' ); size_t n = std::count( term.first, term.second, '\n' ); - + if( nline ) { yylloc.last_line += nline; yylloc.first_line = yylloc.last_line - n; @@ -499,9 +499,9 @@ update_yylloc( const csub_match& stmt, const csub_match& term ) { yylloc.last_column = (term.second - p) + 1; return; } - + const char *bol = p; // bol points to last newline before term - + yylloc.first_column = term.first - bol; p = last_newline(term.first, term.second); if( p ) { // term has newlines, too @@ -555,7 +555,7 @@ parse_replacing_term( const char *stmt, const char *estmt ) { output.stmt = cm[0]; gcc_assert(output.stmt.pend[-1] == '.'); dbgmsg("%s:%d: done at '%.*s'", __func__, __LINE__, - output.term.size(), output.term.p); + output.term.size(), output.term.p); return output; } @@ -572,8 +572,8 @@ parse_replacing_term( const char *stmt, const char *estmt ) { if( output.done ) output.stmt.pend++; } dbgmsg("%s:%d: %s '%.*s'", __func__, __LINE__, - output.done? "done at" : "term is", - output.term.size(), output.term.p); + output.done? "done at" : "term is", + output.term.size(), output.term.p); return output; } @@ -592,7 +592,7 @@ parse_replacing_term( const char *stmt, const char *estmt ) { output.matched = output.stmt.p < output.term.p; gcc_assert(output.matched); dbgmsg("%s:%d: term is '%.*s'", __func__, __LINE__, - output.term.size(), output.term.p); + output.term.size(), output.term.p); return output; } @@ -617,7 +617,7 @@ parse_replacing_term( const char *stmt, const char *estmt ) { gcc_assert(0 < output.term.size()); dbgmsg("%s:%d: more words starting at '%.80s'", __func__, __LINE__, - output.term.pend); + output.term.pend); static const char term_pattern[] = "^[[:space:]]+" @@ -673,7 +673,7 @@ parse_replacing_term( const char *stmt, const char *estmt ) { const char *status = "unmatched"; if( output.matched ) status = output.done? "done" : "matched"; dbgmsg("%s:%d: %s term is '%.*s'", __func__, __LINE__, status, - output.term.size(), output.term.p? output.term.p : ""); + output.term.size(), output.term.p? output.term.p : ""); } return output; } @@ -703,17 +703,17 @@ parse_replacing_pair( const char *stmt, const char *estmt ) { pair.stmt.pend = parsed.stmt.pend; pair.replace.after = parsed.term; } else { - dbgmsg("%s:%d: not matched '%.*s'", __func__, __LINE__, - pair.stmt.size(), pair.stmt.p); + dbgmsg("%s:%d: not matched '%.*s'", __func__, __LINE__, + pair.stmt.size(), pair.stmt.p); } } if( yy_flex_debug ) { const char *status = "unmatched"; if( pair.matched() ) status = pair.done()? "done" : "matched"; dbgmsg("%s:%d: [%s] replacing '%.*s' with '%.*s'", __func__, __LINE__, - status, - pair.replace.before.size(), pair.replace.before.p, - pair.replace.after.size(), pair.replace.after.p); + status, + pair.replace.before.size(), pair.replace.before.p, + pair.replace.after.size(), pair.replace.after.p); } } else { for( auto p = stmt; (p = std::find(p, estmt, '.')) < estmt; p++ ) { @@ -770,10 +770,10 @@ parse_replace_pairs( const char *stmt, const char *estmt, bool is_copy_stmt ) { if( false && yy_flex_debug ) { for( size_t i=0; i < cm.size(); i++ ) { dbgmsg("%s: %s %zu: '%.*s'", __func__, - cm[i].matched? "Pair" : "pair", - i, - cm[i].matched? int(cm[i].length()) : 0, - cm[i].matched? cm[i].first : ""); + cm[i].matched? "Pair" : "pair", + i, + cm[i].matched? int(cm[i].length()) : 0, + cm[i].matched? cm[i].first : ""); } } gcc_assert(cm[3].matched); @@ -812,7 +812,7 @@ parse_replace_pairs( const char *stmt, const char *estmt, bool is_copy_stmt ) { gcc_assert(false); } dbgmsg("%s:%d: dealing with %.*s", __func__, __LINE__, - int(parsed.leading_trailing.size()), parsed.leading_trailing.p); + int(parsed.leading_trailing.size()), parsed.leading_trailing.p); } src = xasprintf("%s(%s)%s", befter[0], src, befter[1]); @@ -831,12 +831,12 @@ parse_replace_pairs( const char *stmt, const char *estmt, bool is_copy_stmt ) { if( yy_flex_debug ) { dbgmsg( "%s:%d: %s: %zu pairs parsed from '%.*s'", __func__, __LINE__, - parsed.done()? "done" : "not done", - pairs.size(), parsed.stmt.size(), parsed.stmt.p ); + parsed.done()? "done" : "not done", + pairs.size(), parsed.stmt.size(), parsed.stmt.p ); int i = 0; for( const auto& replace : pairs ) { dbgmsg("%s:%d:%4d: '%s' => '%s'", __func__, __LINE__, - ++i, replace.before.p, replace.after.p); + ++i, replace.before.p, replace.after.p); } } if( !parsed.done() ) { @@ -860,7 +860,7 @@ struct copy_descr_t { static YYLTYPE location_in( const filespan_t& mfile, const csub_match cm ) { YYLTYPE loc { - int(mfile.lineno() + 1), int(mfile.colno() + 1), + int(mfile.lineno() + 1), int(mfile.colno() + 1), int(mfile.lineno() + 1), int(mfile.colno() + 1) }; gcc_assert(mfile.cur <= cm.first && cm.second <= mfile.eodata); @@ -915,8 +915,8 @@ parse_copy_directive( filespan_t& mfile ) { size_t nnl = 1 + count_newlines(mfile.data, copy_stmt.p); size_t nst = 1 + count_newlines(copy_stmt.p, copy_stmt.pend); dbgmsg("%s:%d: line %zu: COPY directive is %zu lines '%.*s'", - __func__, __LINE__, - nnl, nst, copy_stmt.size(), copy_stmt.p); + __func__, __LINE__, + nnl, nst, copy_stmt.size(), copy_stmt.p); } } } @@ -950,7 +950,7 @@ parse_copy_directive( filespan_t& mfile ) { } YYLTYPE loc = location_in( mfile, copybook_name ); outcome.fd = copybook.open( loc, xstrndup(copybook_name.first, - copybook_name.length()) ); + copybook_name.length()) ); if( outcome.fd == -1 ) { // let parser report missing copybook dbgmsg("%s:%d: (no copybook '%s' found)", __func__, __LINE__, copybook.source()); return outcome; @@ -1014,7 +1014,7 @@ parse_replace_last_off( filespan_t& mfile ) { } dbgmsg( "%s:%d: line %zu: parsed '%.*s', ", __func__, __LINE__, - mfile.lineno(), int(cm[0].length()), cm[0].first ); + mfile.lineno(), int(cm[0].length()), cm[0].first ); // Remove statement from input erase_line(const_cast<char*>(cm[0].first), @@ -1052,8 +1052,8 @@ parse_replace_text( filespan_t& mfile ) { if( ! regex_search(mfile.ccur(), (const char *)mfile.eodata, cm, re) ) { dbgmsg( "%s:%d: line %zu: not a REPLACE statement:\n'%.*s'", - __func__, __LINE__, current_lineno, - int(mfile.line_length()), mfile.cur ); + __func__, __LINE__, current_lineno, + int(mfile.line_length()), mfile.cur ); return span_t(); } @@ -1291,7 +1291,7 @@ lexer_input( char buf[], int max_size, FILE *input ) { char *next = std::min(mfile.eodata, mfile.cur + max_size); buffer_t output(buf, buf + max_size); // initializes pos - // Fill output, keeping only NL for blank lines. + // Fill output, keeping only NL for blank lines. for( auto p = mfile.cur; p < next; *output.pos++ = *p++ ) { static bool at_bol = false; if( at_bol ) { @@ -1353,7 +1353,7 @@ static std::list<preprocessor_filter_t> preprocessor_filters; static std::list<const char *> included_files; /* - * Keep a list of files added with -include on the command line. + * Keep a list of files added with -include on the command line. */ bool include_file_add(const char filename[]) { @@ -1372,11 +1372,11 @@ preprocess_filter_add( const char input[] ) { if( optstr ) { for( char *opt = optstr + 1; (opt = strtok(opt, ",")); opt = NULL ) { - options.push_back(opt); + options.push_back(opt); } *optstr = '\0'; } - + auto filename = find_filter(filter); if( !filename ) { yywarn("preprocessor '%s/%s' not found", getcwd(NULL, 0), filter); @@ -1391,7 +1391,7 @@ cdftext::echo_input( int input, const char filename[] ) { int fd; if( -1 == (fd = dup(input)) ) { yywarn( "could not open preprocessed file %s to echo to standard output", - filename ); + filename ); return; } @@ -1425,7 +1425,7 @@ cdftext::lex_open( const char filename[] ) { int output = open_output(); - // Process any files supplied by the -include comamnd-line option. + // Process any files supplied by the -include comamnd-line option. for( auto name : included_files ) { int input; if( -1 == (input = open(name, O_RDONLY)) ) { @@ -1437,7 +1437,7 @@ cdftext::lex_open( const char filename[] ) { process_file( mfile, output ); } - + cobol_filename(filename, inode_of(input)); filespan_t mfile( free_form_reference_format( input ) ); @@ -1461,7 +1461,7 @@ cdftext::lex_open( const char filename[] ) { return xstrdup(opt.c_str()); } ); *last_argv = NULL; - + pid_t pid = fork(); switch(pid){ @@ -1527,8 +1527,8 @@ cdftext::open_output() { if( name && 0 != strcmp(name, "/") ) { char * stem = xasprintf("%sXXXXXX", name); if( -1 == (fd = mkstemp(stem)) ) { - cbl_err( "could not open temporary file '%s' (%s)", - name, realpath(name, stem)); + cbl_err( "could not open temporary file '%s' (%s)", + name, realpath(name, stem)); } return fd; } @@ -1549,12 +1549,12 @@ cdftext::map_file( int fd ) { mfile.use_nada(); struct stat sb; - do { + do { if( 0 != fstat(fd, &sb) ) { cbl_err( "%s: could not stat fd %d", __func__, fd ); } if( S_ISFIFO(sb.st_mode) ) { - // Copy FIFO to regular file that can be mapped. + // Copy FIFO to regular file that can be mapped. int input = open_output(); std::swap(fd, input); // fd will continue to be the input static char block[4096 * 4]; @@ -1565,12 +1565,12 @@ cdftext::map_file( int fd ) { cbl_err( "%s: could not prepare map file from FIFO %d", __func__, input); } - if( false ) dbgmsg("%s: copied %ld bytes from FIFO", + if( false ) dbgmsg("%s: copied %ld bytes from FIFO", __func__, nout); } } } while( S_ISFIFO(sb.st_mode) ); - + if( sb.st_size > 0 ) { static const int flags = MAP_PRIVATE; @@ -1625,7 +1625,7 @@ cdftext::free_form_reference_format( int input ) { if( valid_sequence_area(p, mfile.eodata) ) indicator.column = 7; dbgmsg("%s:%d: %s format detected", __func__, __LINE__, - indicator.column == 7? "FIXED" : "FREE"); + indicator.column == 7? "FIXED" : "FREE"); } while( mfile.next_line() ) { @@ -1699,7 +1699,7 @@ cdftext::free_form_reference_format( int input ) { __attribute__ ((fallthrough)); default: // flag other characters in indicator area if( ! ISSPACE(indcol[0]) ) { - yyerrorvl( mfile.lineno(), cobol_filename(), + yyerrorvl( mfile.lineno(), cobol_filename(), "error: stray indicator '%c' (0x%x): \"%.*s\"", indcol[0], indcol[0], int(mfile.line_length() - 1), mfile.cur ); @@ -1777,8 +1777,8 @@ cdftext::process_file( filespan_t mfile, int output, bool second_pass ) { []( char ch ) { return ch == '\n'; } ); struct { int in, out; filespan_t mfile; } copy; dbgmsg("%s:%d: line %zu, opening %s on fd %d", __func__, __LINE__, - mfile.lineno(), - copybook.source(), copybook.current()->fd); + mfile.lineno(), + copybook.source(), copybook.current()->fd); copy.in = copybook.current()->fd; copy.mfile = free_form_reference_format( copy.in ); @@ -1813,7 +1813,7 @@ cdftext::process_file( filespan_t mfile, int output, bool second_pass ) { continue; // No active REPLACE directive. } - std::list<span_t> segments = segment_line(mfile); // no replace yields + std::list<span_t> segments = segment_line(mfile); // no replace yields // // 1 segment for( const auto& segment : segments ) { @@ -1824,7 +1824,7 @@ cdftext::process_file( filespan_t mfile, int output, bool second_pass ) { struct { size_t before, after; int delta() const { return before - after; } } nlines; - nlines.before = std::count(segments.front().p, + nlines.before = std::count(segments.front().p, segments.front().pend, '\n'); nlines.after = std::count(segments.back().p, segments.back().pend, '\n'); if( nlines.delta() < 0 ) { diff --git a/gcc/cobol/parse.y b/gcc/cobol/parse.y index ef027f94ada4..054745941b18 100644 --- a/gcc/cobol/parse.y +++ b/gcc/cobol/parse.y @@ -47,7 +47,7 @@ accept_command_line_e, accept_envar_e, }; - + class literal_t { size_t isym; public: @@ -200,7 +200,7 @@ {} }; - + #pragma GCC diagnostic push #pragma GCC diagnostic ignored "-Wunused-function" static data_category_t @@ -272,7 +272,7 @@ typedef struct Elem_list_t<size_t> isym_list_t; struct rel_part_t; - + bool set_debug(bool); #include "ec.h" @@ -342,7 +342,7 @@ %token <number> POSITIVE %token <field_attr> POINTER %token <string> SECTION -%token <number> STANDARD_ALPHABET "STANDARD ALPHABET" +%token <number> STANDARD_ALPHABET "STANDARD ALPHABET" %token <string> SWITCH %token <string> UPSI %token <number> ZERO @@ -363,7 +363,7 @@ TIME_FMT "time format" DATETIME_FMT "datetime format" - /* tokens without semantic value */ + /* tokens without semantic value */ /* CDF (COPY and >> defined here but used in cdf.y) */ %token BASIS CBL CONSTANT COPY DEFINED ENTER FEATURE INSERTT @@ -405,7 +405,7 @@ ASCENDING ACTIVATING ASIN ASSIGN AT ATAN BASED BASECONVERT - BEFORE BINARY BIT BIT_OF "BIT-OF" BIT_TO_CHAR "BIT-TO-CHAR" + BEFORE BINARY BIT BIT_OF "BIT-OF" BIT_TO_CHAR "BIT-TO-CHAR" BLANK BLOCK BOOLEAN_OF_INTEGER "BOOLEAN-OF-INTEGER" BOTTOM BY @@ -449,7 +449,7 @@ EXCEPTION_STATEMENT "EXCEPTION-STATEMENT" EXCEPTION_STATUS "EXCEPTION-STATUS" - FACTORIAL FALSE_kw "False" FD + FACTORIAL FALSE_kw "False" FD FILE_CONTROL "FILE-CONTROL" FILE_KW "File" FILE_LIMIT "FILE-LIMIT" @@ -461,7 +461,7 @@ FORMATTED_DATETIME "FORMATTED-DATETIME" FORMATTED_TIME "FORMATTED-TIME" FORM_OVERFLOW "FORM-OVERFLOW" - FREE + FREE FRACTION_PART "FRACTION-PART" FROM FUNCTION @@ -511,8 +511,8 @@ NATIONAL_EDITED "NATIONAL-EDITED" NATIONAL_OF "NATIONAL-OF" NATIVE NESTED NEXT - NO NOTE - NULLS NULLPTR + NO NOTE + NULLS NULLPTR NUMERIC NUMERIC_EDITED NUMVAL NUMVAL_C "NUMVAL-C" @@ -525,7 +525,7 @@ PACKED_DECIMAL PADDING PAGE PAGE_COUNTER "PAGE-COUNTER" - PF PH PI PIC PICTURE + PF PH PI PIC PICTURE PLUS PRESENT_VALUE PRINT_SWITCH PROCEDURE PROCEDURES PROCEED PROCESS PROGRAM_ID "PROGRAM-ID" @@ -546,7 +546,7 @@ SECURITY SEPARATE SEQUENCE SEQUENTIAL SHARING SIMPLE_EXIT "(simple) EXIT" - SIGN SIN SIZE + SIGN SIN SIZE SMALLEST_ALGEBRAIC "SMALLEST-ALGEBRAIC" SOURCE SOURCE_COMPUTER "SOURCE-COMPUTER" @@ -557,7 +557,7 @@ STANDARD_COMPARE "STANDARD-COMPARE" STATUS STRONG SUBSTITUTE SUM SYMBOL SYMBOLIC SYNCHRONIZED - + TALLY TALLYING TAN TERMINATE TEST TEST_DATE_YYYYMMDD "TEST-DATE-YYYYMMDD" TEST_DAY_YYYYDDD "TEST-DAY-YYYYDDD" @@ -663,7 +663,7 @@ %type <special_type> device_name %type <string> numed collating_sequence context_word ctx_name locale_spec %type <literal> namestr alphabet_lit program_as repo_as -%type <field> perform_cond kind_of_name +%type <field> perform_cond kind_of_name %type <refer> alloc_ret %type <field> log_term rel_expr rel_abbr eval_abbr @@ -675,10 +675,10 @@ %type <field_data> value78 %type <field> literal name nume typename %type <field> num_literal signed_literal - + %type <number> perform_start %type <refer> perform_times -%type <perf> perform_verb +%type <perf> perform_verb perform_inline perform_except %type <refer> eval_subject1 @@ -792,7 +792,7 @@ %type <labels> labels %type <label> label_1 section_name - + %type <switches> upsi_entry %type <special> acceptable disp_target @@ -817,7 +817,7 @@ %type <ec_list> except_names %type <isym_list> except_files %type <dcl_list_t> perform_ec - + %type <opt_init_sects> opt_init_sects %type <opt_init_sect> opt_init_sect %type <number> opt_init_value @@ -863,7 +863,7 @@ struct cbl_perform_tgt_t *tgt; Label_list_t *labels; key_list_t *file_keys; - cbl_file_mode_t io_mode; + cbl_file_mode_t io_mode; struct cbl_file_key_t *file_key; struct file_list_t *files; struct field_list_t *fields; @@ -1011,7 +1011,7 @@ ASCENDING ACTIVATING ASIN ASSIGN AT ATAN BACKWARD BASED BASECONVERT - BEFORE BINARY BIT BIT_OF BIT_TO_CHAR + BEFORE BINARY BIT BIT_OF BIT_TO_CHAR BLANK BLOCK BOOLEAN_OF_INTEGER BOTTOM BY @@ -1051,13 +1051,13 @@ E EBCDIC EC EGCS ENTRY ENVIRONMENT EQUAL ERROR EVERY EXAMINE EXCEPTION EXHIBIT EXP EXP10 EXTEND EXTERNAL - EXCEPTION_FILE - EXCEPTION_FILE_N - EXCEPTION_LOCATION + EXCEPTION_FILE + EXCEPTION_FILE_N + EXCEPTION_LOCATION EXCEPTION_LOCATION_N - EXCEPTION_NAME - EXCEPTION_STATEMENT - EXCEPTION_STATUS + EXCEPTION_NAME + EXCEPTION_STATEMENT + EXCEPTION_STATUS FACTORIAL FALSE_kw FD FILENAME FILE_CONTROL @@ -1071,7 +1071,7 @@ FORMATTED_DATETIME FORMATTED_TIME FORM_OVERFLOW - FREE + FREE FRACTION_PART FROM FUNCTION FUNCTION_UDF @@ -1117,13 +1117,13 @@ MANUAL MAXX MEAN MEDIAN MIDRANGE MIGHT_BE MINN MULTIPLE MOD MODE - MODULE_NAME + MODULE_NAME NAMED NAT NATIONAL NATIONAL_EDITED NATIONAL_OF NATIVE NEGATIVE NESTED NEXT - NINEDOT NINES NINEV NO NOTE NO_CONDITION + NINEDOT NINES NINEV NO NOTE NO_CONDITION NULLS NULLPTR NUMBER NUME NUMED NUMED_CR NUMED_DB NUMERIC NUMERIC_EDITED NUMSTR NUMVAL @@ -1166,12 +1166,12 @@ STANDARD STANDARD_ALPHABET STANDARD_1 - STANDARD_DEVIATION + STANDARD_DEVIATION STANDARD_COMPARE STATUS STRONG STDERR STDIN STDOUT LITERAL SUBSTITUTE SUM SWITCH SYMBOL SYMBOLIC SYNCHRONIZED SYSIN SYSIPT SYSLST SYSOUT SYSPCH SYSPUNCH - + TALLY TALLYING TAN TERMINATE TEST TEST_DATE_YYYYMMDD TEST_DAY_YYYYDDD @@ -1213,13 +1213,13 @@ HIGH_ORDER_LEFT HIGH_ORDER_RIGHT IGNORING IMPLEMENTS INITIALIZED INTERMEDIATE - LC_ALL_kw - LC_COLLATE_kw - LC_CTYPE_kw - LC_MESSAGES_kw - LC_MONETARY_kw - LC_NUMERIC_kw - LC_TIME_kw + LC_ALL_kw + LC_COLLATE_kw + LC_CTYPE_kw + LC_MESSAGES_kw + LC_MONETARY_kw + LC_NUMERIC_kw + LC_TIME_kw LOWLIGHT NEAREST_AWAY_FROM_ZERO NEAREST_EVEN NEAREST_TOWARD_ZERO @@ -1248,7 +1248,7 @@ END_UNSTRING END_WRITE error END_IF - + %left THRU %left OR %left AND @@ -1348,7 +1348,7 @@ cbl_field_t * new_literal( const literal_t& lit, enum cbl_field_attr_t attr ); - + static YYLTYPE first_line_of( YYLTYPE loc ); %} @@ -1512,7 +1512,7 @@ opt_arith: ARITHMETIC is opt_arith_type { } } ; -opt_arith_type: NATIVE { $$ = cbl_options_t::native_e; } +opt_arith_type: NATIVE { $$ = cbl_options_t::native_e; } | STANDARD { $$ = cbl_options_t::standard_e; } | STANDARD_BINARY { $$ = cbl_options_t::standard_binary_e; } | STANDARD_DECIMAL { $$ = cbl_options_t::standard_decimal_e; } @@ -1629,10 +1629,10 @@ opt_init_value: BINARY ZERO { $$ = constant_index(NULLS); } { if( $1.prefix[0] != 'X' ) { error_msg(@1, "hexadecimal literal required"); - } + } if( $1.len != 1 ) { error_msg(@1, "1-byte hexadecimal literal required"); - } + } char ach[16]; sprintf(ach, "%d", (int)($1.data[0])); //auto f = new_literal($1.data); @@ -1862,7 +1862,7 @@ selected_name: external scalar { $$ = $2; } uint32_t len = $name.len; cbl_field_t field = { 0, FldLiteralA, FldInvalid, quoted_e | constant_e, - 0, 0, 0, nonarray, 0, "", 0, cbl_field_t::linkage_t(), + 0, 0, 0, nonarray, 0, "", 0, cbl_field_t::linkage_t(), {len,len,0,0, $name.data, NULL, {NULL}, {NULL}}, NULL }; field.attr |= literal_attr($name.prefix); $$ = new cbl_refer_t( field_add(@name, &field) ); @@ -2073,7 +2073,7 @@ assign_clause: ASSIGN to selected_name[selected] { $$.clause = assign_clause_e; $$.file = new cbl_file_t(protofile); $$.file->filename = field_index($name); - } + } ; collate_clause: collate_claus1 { @@ -2462,7 +2462,7 @@ dev_mnemonic: device_name is NAME { "ARGUMENT-NUMBER", ARG_NUM_e }, { "ARGUMENT-VALUE", ARG_VALUE_e } , { "ENVIRONMENT-NAME", ENV_NAME_e }, - { "ENVIRONMENT-VALUE", ENV_VALUE_e }, + { "ENVIRONMENT-VALUE", ENV_VALUE_e }, }; char device[ 1 + strlen($device) ]; std::transform($device, $device + strlen($device) + 1, @@ -3168,7 +3168,7 @@ occurs_clause: OCCURS cardinal_lb indexed YYERROR; } cbl_occurs_t *occurs = ¤t_field()->occurs; - occurs->bounds.lower = + occurs->bounds.lower = occurs->bounds.upper = $name->data.value; } ; @@ -3438,7 +3438,7 @@ data_descr1: level_name } } - | LEVEL88 NAME /* VALUE */ NULLPTR + | LEVEL88 NAME /* VALUE */ NULLPTR { struct cbl_field_t field = { 0, FldClass, FldInvalid, 0, 0, 0, 88, nonarray, yylineno, "", @@ -3656,7 +3656,7 @@ data_descr1: level_name $field->data.digits); if( $field->attr & separate_e ) { - // This is a gentle kludge required by the the belated + // This is a gentle kludge required by the the belated // introduction of COMP-6, which is like COMP-3 but with no // sign nybble. The code in type_capacity assumes a sign // nybble. @@ -3680,7 +3680,7 @@ data_descr1: level_name $field->type != FldFloat ) { switch( $field->data.initial[0] ) { - case '-': + case '-': if( !$field->has_attr(signable_e) ) { error_msg(@field, "%s is unsigned but has signed VALUE '%s'", $field->name, $field->data.initial); @@ -3826,7 +3826,7 @@ data_clauses: data_clause if( redefined && redefined->type == FldPointer ) { if( yydebug ) { yywarn("expanding %s size from %u bytes to %zu " - "because it redefines %s with USAGE POINTER", + "because it redefines %s with USAGE POINTER", field->name, field->size(), sizeof(void*), redefined->name); } @@ -3834,7 +3834,7 @@ data_clauses: data_clause } } } - + switch( field->type ) { case FldFloat: if( ($$ & picture_clause_e) == picture_clause_e ) { @@ -3988,7 +3988,7 @@ picture_clause: PIC signed nps[fore] nines nps[aft] dialect_mf() ) { // PIC X COMP-X or COMP-9 if( ! field->has_attr(all_x_e) ) { - error_msg(@2, "COMP PICTURE requires all X's or all 9's"); + error_msg(@2, "COMP PICTURE requires all X's or all 9's"); YYERROR; } } else { @@ -4076,7 +4076,7 @@ alphanum_pic: alphanum_part { dbgmsg("%s has %s against %s", field->name, field_attr_str(field), cbl_field_attr_str($2.attr)); - + if( ! field->has_attr($2.attr) ) { field->clear_attr(all_ax_e); // clears 2 bits } @@ -4141,7 +4141,7 @@ count: %empty { $$ = 0; } auto e = symbol_field(PROGRAM, 0, $NAME); if( e ) { // verify not floating point with nonzero fraction auto field = cbl_field_of(e); - assert(is_literal(field)); + assert(is_literal(field)); if( field->data.value != size_t(field->data.value) ) { nmsg++; error_msg(@NAME, "invalid PICTURE count '(%s)'", @@ -4182,27 +4182,27 @@ usage_clause1: usage COMPUTATIONAL[comp] native __attribute__((fallthrough)); case FldNumericBin5: // If no capacity yet, then no picture, infer $comp.capacity. - // If field has capacity, ensure USAGE is compatible. + // If field has capacity, ensure USAGE is compatible. if( field->data.capacity > 0 ) { // PICTURE before USAGE infer = false; - switch( field->type ) { + switch( field->type ) { case FldAlphanumeric: // PIC X COMP-5 or COMP-X - assert( field->data.digits == 0 ); - assert( field->data.rdigits == 0 ); + assert( field->data.digits == 0 ); + assert( field->data.rdigits == 0 ); if( dialect_mf() ) { field->type = $comp.type; - field->clear_attr(signable_e); + field->clear_attr(signable_e); } else { - error_msg(@comp, "numeric USAGE invalid " + error_msg(@comp, "numeric USAGE invalid " "with Alpnanumeric PICTURE"); - YYERROR; + YYERROR; } break; case FldNumericDisplay: // PIC 9 COMP-5 or COMP-X if( $comp.capacity == 0xFF ) { // comp-x is a bit like comp-5 assert( field->data.digits == field->data.capacity ); if( ! dialect_mf() ) { - dialect_error(@1, "COMP-X", "mf"); + dialect_error(@1, "COMP-X", "mf"); } } field->type = $comp.type; @@ -4218,7 +4218,7 @@ usage_clause1: usage COMPUTATIONAL[comp] native field->attr |= separate_e; if( ! dialect_mf() ) { dialect_error(@1, "COMP-6", "mf"); - } + } if( field->type == FldNumericDisplay ) {// PICTURE before USAGE infer = false; assert(field->data.capacity > 0); @@ -4262,9 +4262,9 @@ usage_clause1: usage COMPUTATIONAL[comp] native field->clear_attr(signable_e); if( field->type == FldNumericDisplay ) {// PICTURE before USAGE assert(field->data.capacity > 0); - field->data.capacity = type_capacity(FldPacked, + field->data.capacity = type_capacity(FldPacked, field->data.digits); - } + } $$ = field->type = FldPacked; } | usage INDEX { @@ -4422,7 +4422,7 @@ redefines_clause: REDEFINES NAME[orig] auto f = cbl_field_of(&elem); return f->level == level && - f->parent != parent; + f->parent != parent; } return false; } ); @@ -4431,7 +4431,7 @@ redefines_clause: REDEFINES NAME[orig] error_msg(@2, "cannot redefine %s %s as %s %s " "because %s %s intervenes", orig->level_str(), name_of(orig), - field->level_str(), name_of(field), + field->level_str(), name_of(field), mid->level_str(), name_of(mid)); } @@ -4501,7 +4501,7 @@ same_clause: SAME AS name if( field->level == 77 and !is_elementary(other->type) ) { // ISO 2023 13.18.49.2,P8 error_msg(@name, "%s %s SAME AS %s: must be elementary", - field->level_str(), field->name, other->name); + field->level_str(), field->name, other->name); YYERROR; } @@ -4559,19 +4559,19 @@ sign_separate: %empty { $$ = false; } * by type-name-1 had been coded in place of the TYPE clause, excluding the * level-number, name, alignment, and the GLOBAL, SELECT WHEN, and TYPEDEF * clauses specified for type-name-1;" - * + * * The essential characteristics of a type, which is identified by its - * type-name, are the: - * — relative positions and lengths of the elementary items + * type-name, are the: + * — relative positions and lengths of the elementary items * — ALIGNED clause * — BLANK WHEN ZERO clause * — JUSTIFIED clause * — PICTURE clause * — SIGN clause * — SYNCHRONIZED clause - * — USAGE clause + * — USAGE clause */ -type_clause: TYPE to typename +type_clause: TYPE to typename { cbl_field_t *field = current_field(); if( $typename ) { @@ -4579,7 +4579,7 @@ type_clause: TYPE to typename symbol_field_location( symbol_index(e), @typename ); } } - | USAGE is typename + | USAGE is typename { if( ! dialect_mf() ) { dialect_error(@typename, "USAGE TYPENAME", "mf"); @@ -4593,7 +4593,7 @@ type_clause: TYPE to typename } ; -typedef_clause: is TYPEDEF strong +typedef_clause: is TYPEDEF strong { cbl_field_t *field = current_field(); switch( field->level ) { @@ -4717,14 +4717,14 @@ declaratives: %empty enabled_exceptions = current.enabled_exception_cache; current.enabled_exception_cache.clear(); ast_enter_section(implicit_section()); - } + } ; sentences: sentence { ast_first_statement(@1); symbol_temporaries_free(); } - | section_name + | section_name | paragraph_name[para] '.' { location_set(@para); @@ -4738,7 +4738,7 @@ sentences: sentence { } | sentences sentence { // sentences might not be sentence - ast_first_statement(@2); + ast_first_statement(@2); symbol_temporaries_free(); } | sentences section_name @@ -4879,7 +4879,7 @@ accept: accept_body end_accept { if( $1.from->field == NULL ) { // take next command-line arg parser_accept_command_line(*$1.into, argi, NULL, NULL); cbl_num_result_t tgt { truncation_e, argi }; - parser_add2(tgt, literally_one); // increment argi + parser_add2(tgt, literally_one); // increment argi } else if( $1.from->field == argi ) { parser_move(*$1.into, *$1.from); } else { @@ -4900,10 +4900,10 @@ accept: accept_body end_accept { break; case accept_command_line_e: if( $1.from->field == NULL ) { // take next command-line arg - parser_accept_command_line(*$1.into, argi, + parser_accept_command_line(*$1.into, argi, $ec.on_error, $ec.not_error); cbl_num_result_t tgt { truncation_e, argi }; - parser_add2(tgt, literally_one); // increment argi + parser_add2(tgt, literally_one); // increment argi } else if( $1.from->field == argi ) { parser_move(*$1.into, *$1.from); if( $ec.on_error || $ec.not_error ) { @@ -5330,7 +5330,7 @@ compute_expr: '=' { $$ = $expr; } ; - | EQUAL { + | EQUAL { if( ! dialect_ibm() ) { dialect_error(@1, "EQUAL invalid as assignment operator", "ibm"); } @@ -5526,7 +5526,7 @@ end_program: end_program1[end] '.' // pointer still valid because name is in symbol table ast_end_program(prog->name); } - | end_program1[end] error + | end_program1[end] error { const char *token_name = "???"; switch($end.token) { @@ -5553,7 +5553,7 @@ end_program1: END_PROGRAM namestr[name] $$.token = END_FUNCTION; $$.name = $name; } - | END_PROGRAM '.' // error + | END_PROGRAM '.' // error { $$.token = END_PROGRAM; } @@ -5566,7 +5566,7 @@ end_program1: END_PROGRAM namestr[name] continue_stmt: CONTINUE { statement_begin(@1, CONTINUE); parser_sleep(*cbl_refer_t::empty()); - } + } | CONTINUE AFTER expr SECONDS { statement_begin(@1, CONTINUE); parser_sleep(*$expr); @@ -5591,7 +5591,7 @@ exit: GOBACK exit_with[status] ; /* Valid "simple" EXIT (Format 1) swallowed by lexer */ - /* + /* * If the EXIT PROGRAM statement is executed in a program that * is not under the control of a calling runtime element, the * EXIT PROGRAM statement is treated as if it were a CONTINUE @@ -5636,8 +5636,8 @@ exit_with: %empty ; exit_what: PROGRAM_kw { parser_exit_program(); } | PROGRAM_kw exit_raising[ec] { parser_exit_program(); } - | SECTION { parser_exit_section(); } - | PARAGRAPH { parser_exit_paragraph(); } + | SECTION { parser_exit_section(); } + | PARAGRAPH { parser_exit_paragraph(); } | PERFORM { if( performs.empty() ) { error_msg(@$, "EXIT PERFORM valid only " @@ -5770,26 +5770,26 @@ bool_expr: log_expr { $$ = new_reference($1->resolve()); } ; log_expr: log_term { $$ = new log_expr_t($1); } %prec AND - | log_expr[lhs] OR rel_abbr[rhs] + | log_expr[lhs] OR rel_abbr[rhs] { $$ = $1; $$->or_term($rhs); } - | log_expr[lhs] OR log_expr[rhs] + | log_expr[lhs] OR log_expr[rhs] { $$ = $lhs; - assert( ! $rhs->unresolved() ); // what to do? + assert( ! $rhs->unresolved() ); // what to do? $$->or_term($rhs->and_term()); } - | log_expr[lhs] AND rel_abbr[rhs] + | log_expr[lhs] AND rel_abbr[rhs] { $$ = $1; $$->and_term($rhs); } - | log_expr[lhs] AND log_expr[rhs] + | log_expr[lhs] AND log_expr[rhs] { $$ = $lhs; - assert( ! $rhs->unresolved() ); // what to do? + assert( ! $rhs->unresolved() ); // what to do? $$->and_term($rhs->and_term()); } ; @@ -5816,10 +5816,10 @@ log_term: '(' log_expr ')' { ; rel_expr: rel_lhs rel_term[rhs] - { + { rel_part_t& ante = current.antecedent(); if( $rhs.invert ) { - error_msg(@rhs, "NOT %s is invalid, cannot negate RHS", + error_msg(@rhs, "NOT %s is invalid, cannot negate RHS", ante.operand->field->name); } auto op = ante.relop; @@ -5832,11 +5832,11 @@ rel_expr: rel_lhs rel_term[rhs] $$ = cond; } | rel_lhs[lhs] '(' rel_abbrs ')' { - $$ = $rel_abbrs->resolve(); + $$ = $rel_abbrs->resolve(); } ; -rel_abbrs: rel_abbr { $$ = new log_expr_t($1); } +rel_abbrs: rel_abbr { $$ = new log_expr_t($1); } | '(' rel_abbrs ')' { $$ = $2; $$->resolve(); @@ -5868,7 +5868,7 @@ rel_lhs: rel_term[lhs] relop { } ; -rel_abbr: rel_term { +rel_abbr: rel_term { static rel_part_t ante; ante = current.antecedent(); if( ! ante.operand ) { @@ -5883,11 +5883,11 @@ rel_abbr: rel_term { parser_relop(cond, *ante.operand, ante.relop, *$rel_term.term); $$ = cond; } - | relop rel_term { + | relop rel_term { static rel_part_t ante; if( $rel_term.invert ) { - error_msg(@2, "%s NOT %s is invalid", - keyword_str($relop), + error_msg(@2, "%s NOT %s is invalid", + keyword_str($relop), name_of($rel_term.term->field)); } auto op( relop_of($relop) ); @@ -5904,10 +5904,10 @@ rel_abbr: rel_term { } ; -rel_term: rel_term1 +rel_term: rel_term1 ; -rel_term1: all LITERAL +rel_term1: all LITERAL { $$.invert = false; $$.term = new_reference(new_literal($2, quoted_e)); @@ -6110,7 +6110,7 @@ eval_obj_cols: eval_obj_col | eval_obj_cols ALSO eval_obj_col ; -eval_obj_col: ANY { +eval_obj_col: ANY { auto& ev( eval_stack.current() ); if( ! ev.decide(ANY) ) { error_msg(@1, "WHEN 'ANY' phrase exceeds subject set count of %zu", @@ -6118,7 +6118,7 @@ eval_obj_col: ANY { YYERROR; } } - | true_false { + | true_false { auto& ev( eval_stack.current() ); auto subj( ev.subject() ); if( !subj ) { @@ -6130,7 +6130,7 @@ eval_obj_col: ANY { error_msg(@1, "subject %s, type %s, " "cannot be compared to TRUE/FALSE", subj->name, 3 + cbl_field_type_str(subj->type) ); - } + } ev.decide($1); } | eval_posneg[op] { @@ -6145,7 +6145,7 @@ eval_obj_col: ANY { } ev.decide(op, zero, false); } - | bool_expr { + | bool_expr { auto& ev( eval_stack.current() ); auto subj( ev.subject() ); if( !subj ) { @@ -6158,14 +6158,14 @@ eval_obj_col: ANY { error_msg(@1, "subject %s, type %s, " "cannot be compared to conditional expression", subj->name, 3 + cbl_field_type_str(subj->type) ); - } + } ev.decide(*$1, false); } | eval_abbrs { auto& ev( eval_stack.current() ); ev.decided( $1->resolve() ); } - | rel_term[a] THRU rel_term[b] %prec THRU { + | rel_term[a] THRU rel_term[b] %prec THRU { auto& ev( eval_stack.current() ); auto subj( ev.subject() ); if( !subj ) { @@ -6178,7 +6178,7 @@ eval_obj_col: ANY { error_msg(@a, "THRU with boolean operand"); } if( $b.invert ) { - error_msg(@b, "NOT %s is invalid with THRU", + error_msg(@b, "NOT %s is invalid with THRU", name_of($b.term->field)); } ev.decide(*$a.term, *$b.term, $a.invert); @@ -6205,9 +6205,9 @@ eval_abbrs: rel_term[a] { if( ! ev.compatible($a.term->field) ) { auto obj($a.term->field); error_msg(@1, "subject %s, type %s, " - "cannot be compared %s, type %s", - subj->name, 3 + cbl_field_type_str(subj->type), - obj->name, 3 + cbl_field_type_str(obj->type) ); + "cannot be compared %s, type %s", + subj->name, 3 + cbl_field_type_str(subj->type), + obj->name, 3 + cbl_field_type_str(obj->type) ); } auto result = ev.compare(*$a.term); if( ! result ) YYERROR; @@ -6230,18 +6230,18 @@ eval_abbrs: rel_term[a] { if( ! ev.compatible($a.term->field) ) { auto obj($a.term->field); error_msg(@1, "subject %s, type %s, " - "cannot be compared %s, type %s", - subj->name, 3 + cbl_field_type_str(subj->type), - obj->name, 3 + cbl_field_type_str(obj->type) ); - } + "cannot be compared %s, type %s", + subj->name, 3 + cbl_field_type_str(subj->type), + obj->name, 3 + cbl_field_type_str(obj->type) ); + } if( is_conditional(ev.subject()) ) { auto obj($a.term->field); error_msg(@1, "subject %s, type %s, " - "cannot be %s %s, type %s", - subj->name, 3 + cbl_field_type_str(subj->type), - relop_str(relop_of($relop)), - obj->name, 3 + cbl_field_type_str(obj->type) ); - } + "cannot be %s %s, type %s", + subj->name, 3 + cbl_field_type_str(subj->type), + relop_str(relop_of($relop)), + obj->name, 3 + cbl_field_type_str(obj->type) ); + } auto result = ev.compare(relop, *$a.term); if( ! result ) YYERROR; if( $a.invert ) { @@ -6301,7 +6301,7 @@ true_false: TRUE_kw { $$ = TRUE_kw; } ; scalar: tableref { - // Check for missing subscript; others already checked. + // Check for missing subscript; others already checked. if( $1->nsubscript == 0 && 0 < dimensions($1->field) ) { subscript_dimension_error(@1, 0, $$); } @@ -6350,14 +6350,14 @@ tableish: name subscripts[subs] refmod[ref] %prec NAME refmod: LPAREN expr[from] ':' expr[len] ')' %prec NAME { - if( ! require_numeric(@from, *$from) ) YYERROR; - if( ! require_numeric(@len, *$len) ) YYERROR; + if( ! require_numeric(@from, *$from) ) YYERROR; + if( ! require_numeric(@len, *$len) ) YYERROR; $$.from = $from; $$.len = $len; } | LPAREN expr[from] ':' ')' %prec NAME { - if( ! require_numeric(@from, *$from) ) YYERROR; + if( ! require_numeric(@from, *$from) ) YYERROR; $$.from = $from; $$.len = nullptr; } @@ -6382,7 +6382,7 @@ name: qname auto inner = namelocs.back(); if( ($$ = field_find(names)) == NULL ) { if( procedure_div_e == current_division ) { - error_msg(inner.loc, + error_msg(inner.loc, "DATA-ITEM '%s' not found", inner.name ); YYERROR; } @@ -6668,7 +6668,7 @@ move_tgts: move_tgt[tgt] { if( $tgt ) list_add($1->targets, *$tgt, current_rounded_mode()); } ; -move_tgt: scalar[tgt] { +move_tgt: scalar[tgt] { if( is_literal($tgt->field) ) { auto litcon = $tgt->field->name[0] == '_'? "literal" : "constant"; error_msg(@1, "%s is a %s", name_of($tgt->field), litcon); @@ -6690,7 +6690,7 @@ move_tgt: scalar[tgt] { { static const char * error_at; if( error_at != yytext ) { // avoid repeated message - error_at = yytext; + error_at = yytext; error_msg(first_line_of(@1), "invalid receiving operand"); } $$ = NULL; @@ -6871,7 +6871,7 @@ num_value: scalar // might actually be a string dialect_error(@1, "LENGTH OF", "ibm"); } if( 0 == dimensions($val) ) { - cbl_refer_t r1($val); + cbl_refer_t r1($val); subscript_dimension_error( @subs, $subs->refers.size(), &r1 ); } parser_set_numeric($$->field, $val->data.capacity); @@ -7013,7 +7013,7 @@ subscripts: LPAREN expr_list ')' { for( auto refer : exprs ) { if( ! is_numeric(refer.field) ) { error_msg(@1, "subscript %d, %s, is not numeric (%s)", - ++i, name_of(refer.field), + ++i, name_of(refer.field), cbl_field_type_str(refer.field->type) + 3); } } @@ -7023,7 +7023,7 @@ subscripts: LPAREN expr_list ')' { ; expr_list: expr { - if( ! require_numeric(@expr, *$expr) ) YYERROR; + if( ! require_numeric(@expr, *$expr) ) YYERROR; $$ = new refer_list_t($expr); } | expr_list expr { @@ -7032,7 +7032,7 @@ expr_list: expr MAXIMUM_TABLE_DIMENSIONS); YYERROR; } - if( ! require_numeric(@expr, *$expr) ) YYERROR; + if( ! require_numeric(@expr, *$expr) ) YYERROR; $1->push_back($2); $$ = $1; } | ALL { @@ -7077,7 +7077,7 @@ signed_literal: num_literal dialect_error(@1, "LENGTH OF", "ibm"); } if( 0 == dimensions($val) ) { - cbl_refer_t r1($val); + cbl_refer_t r1($val); subscript_dimension_error( @subs, $subs->refers.size(), &r1 ); } parser_set_numeric($$, $val->data.capacity); @@ -7353,11 +7353,11 @@ perform_except: perform_start auto lave = perf->ec_labels.new_label(LblParagraph, "lave"); auto handlers = cbl_field_of(symbol_at(iblob)); - // install blob + // install blob parser_label_label(perf->ec_labels.init); declarative_runtime_match(handlers, lave); - // uninstall blob + // uninstall blob parser_label_label(perf->ec_labels.fini); } ; @@ -7401,7 +7401,7 @@ perform_ec: EXCEPTION filenames { auto dcl = new cbl_declarative_t(0, ec_io_e, files, file_mode_none_e); dcls->elems.push_back(dcl); - } + } $$ = dcls; } | EXCEPTION io_mode { @@ -7416,7 +7416,7 @@ perform_ec: EXCEPTION filenames { std::back_inserter(dcls->elems), []( ec_type_t ec ) { - return new cbl_declarative_t(ec); + return new cbl_declarative_t(ec); } ); $$ = dcls; } @@ -7437,7 +7437,7 @@ perform_ec: EXCEPTION filenames { } ; -except_names: except_name { $$ = new ec_list_t($1); } +except_names: except_name { $$ = new ec_list_t($1); } | except_names except_name { $$ = $1->push_back($2); } @@ -7457,7 +7457,7 @@ except_files: except_name[ec] FILE_KW filenames { $$ = new isym_list_t; std::list<size_t>& files( $$->elems ); std::transform( $filenames->files.begin(), - $filenames->files.end(), + $filenames->files.end(), std::back_inserter(files), []( const cbl_file_t* f ) { return symbol_index(symbol_elem_of(f)); } ); @@ -7653,7 +7653,7 @@ varg1a: ADDRESS OF scalar { dialect_error(@1, "LENGTH OF", "ibm"); } if( 0 == dimensions($val) ) { - cbl_refer_t r1($val); + cbl_refer_t r1($val); subscript_dimension_error( @subs, $subs->refers.size(), &r1 ); } parser_set_numeric($$->field, $val->data.capacity); @@ -8606,7 +8606,7 @@ sort_table: SORT tableref[table] sort_keys sort_dup sort_seq { cbl_key_t keys[nkey], *pkey = keys; if( ! is_table($table->field) ) { error_msg(@1, "%s has no OCCURS clause", $table->field->name); - } + } // 23) If data-name-1 is omitted, the data item referenced by // data-name-2 is the key data item. for( auto k : $sort_keys->key_list ) { @@ -8622,7 +8622,7 @@ sort_table: SORT tableref[table] sort_keys sort_dup sort_seq { statement_begin(@1, SORT); if( ! is_table($table->field) ) { error_msg(@1, "%s has no OCCURS clause", $table->field->name); - } + } cbl_key_t key = cbl_key_t($table->field->occurs.keys[0]), guess(1, &$table->field); @@ -8919,7 +8919,7 @@ inspect: INSPECT backward inspected TALLYING tallies statement_begin(@1, INSPECT); // IBM Format 4 does not show the qualifiers as optional, but // they don't appear in Listing-15-1. - parser_inspect_conv( *$inspected, $backward, + parser_inspect_conv( *$inspected, $backward, *$match, *$replace_oper, $qual->before, $qual->after ); @@ -9138,7 +9138,7 @@ insp_qual: befter initial alpha_val first_leading: FIRST { $$ = bound_first_e; } | ALL { $$ = bound_all_e; } | LEADING { $$ = bound_leading_e; } - | TRAILING { $$ = bound_trailing_e; + | TRAILING { $$ = bound_trailing_e; if( ! dialect_mf() ) { dialect_error(@1, "TRAILING", "mf"); } @@ -9920,7 +9920,7 @@ function_udf: FUNCTION_UDF '(' arg_list[args] ')' { auto narg = $args->refers.size(); cbl_ffi_arg_t args[narg]; size_t i = 0; - // Pass parameters as defined by the function. + // Pass parameters as defined by the function. std::transform( $args->refers.begin(), $args->refers.end(), args, [params, &i]( cbl_refer_t& arg ) { function_descr_arg_t param = params.at(i++); @@ -10499,10 +10499,10 @@ intrinsic: function_udf ; module_type: ACTIVATING { $$ = module_activating_e; } - | CURRENT { $$ = module_current_e; } - | NESTED { $$ = module_nested_e; } - | STACK { $$ = module_stack_e; } - | TOP_LEVEL { $$ = module_toplevel_e; } + | CURRENT { $$ = module_current_e; } + | NESTED { $$ = module_nested_e; } + | STACK { $$ = module_stack_e; } + | TOP_LEVEL { $$ = module_toplevel_e; } ; convert_src: ANY @@ -10515,9 +10515,9 @@ convert_dst: convert_fmt HEX convert_fmt: ALPHANUMERIC | ANUM | NAT - | NATIONAL + | NATIONAL ; - + numval_locale: %empty { $$.is_locale = false; $$.arg2 = cbl_refer_t::empty(); @@ -10678,7 +10678,7 @@ intrinsic_I: BOOLEAN_OF_INTEGER { $$ = BOOLEAN_OF_INTEGER; | FRACTION_PART { $$ = FRACTION_PART; } | HIGHEST_ALGEBRAIC { $$ = HIGHEST_ALGEBRAIC; } | INTEGER { $$ = INTEGER; } - | INTEGER_OF_BOOLEAN { $$ = INTEGER_OF_BOOLEAN; + | INTEGER_OF_BOOLEAN { $$ = INTEGER_OF_BOOLEAN; cbl_unimplemented("INTEGER-OF-BOOLEAN"); } | INTEGER_OF_DATE { $$ = INTEGER_OF_DATE; } @@ -10708,7 +10708,7 @@ intrinsic_N: ABS { $$ = ABS; } | LOG { $$ = LOG; } | LOG10 { $$ = LOG10; } | SIN { $$ = SIN; } - | SMALLEST_ALGEBRAIC { $$ = SMALLEST_ALGEBRAIC; + | SMALLEST_ALGEBRAIC { $$ = SMALLEST_ALGEBRAIC; cbl_unimplemented("SMALLEST-ALGEBRAIC"); } | SQRT { $$ = SQRT; } @@ -10865,7 +10865,7 @@ sign: %empty | SIGN ; -start_after: %empty %prec AFTER +start_after: %empty %prec AFTER | START AFTER varg ; @@ -10937,7 +10937,7 @@ cdf_use: USE DEBUGGING on labels } | USE globally mistake procedure on filenames - { + { if( ! current.declarative_section_name() ) { error_msg(@1, "USE valid only in DECLARATIVES"); YYERROR; @@ -11009,7 +11009,7 @@ cdf_use_files: %empty { $$ = NULL; } | FILE_KW filenames { $$ = $2; } ; -io_mode: INPUT { $$ = file_mode_input_e; } +io_mode: INPUT { $$ = file_mode_input_e; } | OUTPUT { $$ = file_mode_output_e; } | IO { $$ = file_mode_io_e; } | EXTEND { $$ = file_mode_extend_e; } @@ -11107,10 +11107,10 @@ statement_begin( const YYLTYPE& loc, int token ) { // parser_print_string("statement_begin()\n"); location_set(loc); prior_statement = token; - + parser_statement_begin(); - if( token != CONTINUE ) { + if( token != CONTINUE ) { if( enabled_exceptions.size() ) { current.declaratives_evaluate(ec_none_e); cbl_enabled_exceptions_array_t enabled(enabled_exceptions); @@ -11163,9 +11163,9 @@ tokenset_t::tokenset_t() { int tokenset_t::find( const cbl_name_t name, bool include_intrinsics ) { static const cbl_name_t non_names[] = { // including CDF NAMES, and "SWITCH" - "CHECKING", "LIST", "LOCATION", "MAP", "SWITCH", + "CHECKING", "LIST", "LOCATION", "MAP", "SWITCH", }, * const eonames = non_names + COUNT_OF(non_names); - + if( std::any_of(non_names, eonames, [candidate=name](const cbl_name_t non_name) { return 0 == strcasecmp(non_name, candidate) @@ -11173,12 +11173,12 @@ tokenset_t::find( const cbl_name_t name, bool include_intrinsics ) { } ) ) { return 0; // CDF names are never ordinary tokens } - + if( dialect_ibm() ) { - static const cbl_name_t ibm_non_names[] = { - "RESUME", + static const cbl_name_t ibm_non_names[] = { + "RESUME", }, * const eonames = ibm_non_names + COUNT_OF(ibm_non_names); - + if( std::any_of(ibm_non_names, eonames, [candidate=name](const cbl_name_t non_name) { return 0 == strcasecmp(non_name, candidate) @@ -11187,7 +11187,7 @@ tokenset_t::find( const cbl_name_t name, bool include_intrinsics ) { return 0; // Names not reserved by IBM are never ordinary IBM tokens } } - + cbl_name_t lname; std::transform(name, name + strlen(name) + 1, lname, tolower); auto p = tokens.find(lname); @@ -11195,16 +11195,16 @@ tokenset_t::find( const cbl_name_t name, bool include_intrinsics ) { int token = p->second; if( token == SECTION ) yylval.number = 0; - + if( include_intrinsics ) return token; - + return intrinsic_cname(token)? 0 : token; } int keyword_tok( const char * text, bool include_intrinsics ) { - return tokens.find(text, include_intrinsics); -} + return tokens.find(text, include_intrinsics); +} static inline size_t verify_figconst( enum cbl_figconst_t figconst , size_t pos ) { @@ -11418,7 +11418,7 @@ label_add( const YYLTYPE& loc, /* * Many label names are defined statically and so are guaranteed to be in * bounds. Often they are created far away from the yacc metavariables, so - * there's no location to access. + * there's no location to access. */ static struct cbl_label_t * label_add( enum cbl_label_type_t type, const char name[], int line ) { @@ -11598,13 +11598,13 @@ current_t::udf_args_valid( const cbl_label_t *L, assert(func != udfs.end()); function_descr_t udf = *func; params = udf.linkage_fields; - + if( udf.linkage_fields.size() < args.size() ) { auto loc = symbol_field_location(field_index(args.back().field)); error_msg(loc, "too many parameters for UDF %s", L->name); return false; } - + size_t i = 0; for( cbl_refer_t arg : args ) { if( arg.field ) { // else omitted @@ -12050,10 +12050,10 @@ data_category_of( const cbl_refer_t& refer ) { return data_numeric_edited_e; case FldAlphaEdited: return data_alphanumeric_edited_e; - + case FldPointer: return data_data_pointer_e; - + case FldClass: case FldConditional: case FldForward: @@ -12159,7 +12159,7 @@ new_literal( const char initial[], enum radix_t radix ) { attr = bool_encoded_e; break; } - return new_literal(strlen(initial), initial, + return new_literal(strlen(initial), initial, cbl_field_attr_t(constant_e | attr)); } @@ -12276,7 +12276,7 @@ initialize_one( cbl_num_result_t target, bool with_filler, source.field = new_literal(ach); source.addr_of = true; } - + if( tgt.field->type == FldPointer ) { parser_set_pointers(1, &tgt, source); } else { @@ -12291,7 +12291,7 @@ initialize_one( cbl_num_result_t target, bool with_filler, /* * Either VALUE or REPLACING specified. */ - + if( value_category == data_category_all || value_category == data_category_of(tgt) ) { // apply any applicable VALUE @@ -12329,19 +12329,19 @@ initialize_one( cbl_num_result_t target, bool with_filler, } return true; - + } typedef std::pair<cbl_field_t*,cbl_field_t*> field_span_t; typedef std::pair<size_t, size_t> cbl_bytespan_t; static void -dump_spans( size_t isym, +dump_spans( size_t isym, const cbl_field_t *table, const std::list<field_span_t>& spans, size_t nrange, const cbl_bytespan_t ranges[], - size_t depth, + size_t depth, const std::list<cbl_subtable_t>& subtables ) { int i=0; @@ -12373,7 +12373,7 @@ dump_spans( size_t isym, dbgmsg("\t %02u %-20s to %02u %-20s: %3zu-%zu %s", span.first->level, span.first->name, last_level, last_name, - nrange? ranges[i].first : 1, + nrange? ranges[i].first : 1, nrange? ranges[i].second : 0, at_subtable); i++; @@ -12387,11 +12387,11 @@ dump_spans( size_t isym, } /* - * After the 1st record is initialized, copy it to the others. + * After the 1st record is initialized, copy it to the others. */ static bool initialize_table( cbl_num_result_t target, - size_t nspan, const cbl_bytespan_t spans[], + size_t nspan, const cbl_bytespan_t spans[], const std::list<cbl_subtable_t>& subtables ) { if( getenv("initialize_statement") ) { @@ -12414,7 +12414,7 @@ static cbl_refer_t synthesize_table_refer( cbl_refer_t tgt ) { // For a table, use supplied subscripts or start with 1. auto ndim( dimensions(tgt.field) ); - if( tgt.nsubscript < ndim ) { // it's an incomplete table + if( tgt.nsubscript < ndim ) { // it's an incomplete table cbl_refer_t subscripts[ndim]; for( size_t i=0; i < ndim; i++ ) { if( i < tgt.nsubscript ) { @@ -12466,7 +12466,7 @@ initialize_statement( const cbl_num_result_t& target, bool with_filler, bool fOK = true; std::list<cbl_field_t*> members; std::list<cbl_subtable_t> subtables; - + while( ++imember < eogroup ) { auto e = symbol_at(imember); if( e->type != SymField ) continue; @@ -12566,7 +12566,7 @@ initialize_statement( const cbl_num_result_t& target, bool with_filler, if( !with_filler && tgt.field->has_attr(filler_e) ) return true; cbl_num_result_t output = { target.rounded, synthesize_table_refer(tgt) }; - + bool fOK = initialize_one( output, with_filler, value_category, replacements, depth == 0 ); @@ -12597,7 +12597,7 @@ data_category_str( data_category_t category ) { case data_numeric_e: return "numeric"; case data_numeric_edited_e: return "numeric_edited"; case data_object_referenc_e: return "data_object_referenc"; - case data_program_pointer_e: return "data_program_pointer"; + case data_program_pointer_e: return "data_program_pointer"; } return "???"; } @@ -12729,7 +12729,7 @@ new_literal( const literal_t& lit, enum cbl_field_attr_t attr ) { bool zstring = lit.prefix[0] == 'Z'; if( !zstring && lit.data[lit.len] != '\0' ) { dbgmsg("%s:%d: line %d, no NUL terminator '%-*.*s'{%zu/%zu}", - __func__, __LINE__, yylineno, + __func__, __LINE__, yylineno, int(lit.len), int(lit.len), lit.data, strlen(lit.data), lit.len); } @@ -12926,7 +12926,7 @@ literal_refmod_valid( YYLTYPE loc, const cbl_refer_t& r ) { if( r.field->has_attr(any_length_e) ) return true; const cbl_span_t& refmod(r.refmod); - + if( ! is_literal(refmod.from->field) ) { if( ! refmod.len ) return true; if( ! is_literal(refmod.len->field) ) return true; @@ -12936,9 +12936,9 @@ literal_refmod_valid( YYLTYPE loc, const cbl_refer_t& r ) { } // len < 0 or not: 0 < from + len <= capacity error_msg(loc, "%s(%s:%zu) out of bounds, " - "size is %u", + "size is %u", r.field->name, - refmod.from->name(), + refmod.from->name(), size_t(refmod.len->field->data.value), static_cast<unsigned int>(r.field->data.capacity) ); return false; @@ -12952,11 +12952,11 @@ literal_refmod_valid( YYLTYPE loc, const cbl_refer_t& r ) { if( refmod.len->field->data.value > 0 ) { edge += refmod.len->field->data.value; if( --edge < r.field->data.capacity ) return true; - } + } // len < 0 or not: 0 < from + len <= capacity auto loc = symbol_field_location(field_index(r.field)); error_msg(loc, "%s(%zu:%zu) out of bounds, " - "size is %u", + "size is %u", r.field->name, size_t(refmod.from->field->data.value), size_t(refmod.len->field->data.value), @@ -12965,7 +12965,7 @@ literal_refmod_valid( YYLTYPE loc, const cbl_refer_t& r ) { } } // not: 0 < from <= capacity - error_msg(loc,"%s(%zu) out of bounds, size is %u", + error_msg(loc,"%s(%zu) out of bounds, size is %u", r.field->name, size_t(refmod.from->field->data.value), static_cast<unsigned int>(r.field->data.capacity) ); @@ -13038,7 +13038,7 @@ require_pointer( YYLTYPE loc, cbl_refer_t scalar ) { } static bool -require_numeric( YYLTYPE loc, cbl_refer_t scalar ) { +require_numeric( YYLTYPE loc, cbl_refer_t scalar ) { if( ! is_numeric(scalar.field) ) { error_msg(loc, "%s must have numeric USAGE", scalar.name()); return false; @@ -13086,7 +13086,7 @@ eval_subject_t::compatible( const cbl_field_t *object ) const { cbl_field_t * eval_subject_t::compare( int token ) { size_t tf( very_false_register() ); - + switch( token ) { case ANY: parser_logop(result, @@ -13129,7 +13129,7 @@ cbl_field_t * eval_subject_t::compare( const cbl_refer_t& object, const cbl_refer_t& object2 ) { auto subject(*pcol); - + if( ! compatible( object.field ) ) { if( yydebug ) { dbgmsg("%s:%d: failed for %s %s", @@ -13148,20 +13148,20 @@ eval_subject_t::compare( const cbl_refer_t& object, return nullptr; } } - + if( is_conditional(subject.field) ) { assert( object2.field == nullptr ); parser_logop(result, subject.field, xnor_op, object.field); return result; } - + if( object2.field ) { assert( ! is_conditional(object.field) ); assert( ! is_conditional(object2.field) ); cbl_field_t * gte = new_temporary(FldConditional); cbl_field_t * lte = new_temporary(FldConditional); - + parser_relop( gte, object, le_op, subject ); parser_relop( lte, subject, le_op, object2 ); @@ -13172,4 +13172,3 @@ eval_subject_t::compare( const cbl_refer_t& object, parser_relop(result, subject, eq_op, object); return result; } - diff --git a/gcc/cobol/scan.l b/gcc/cobol/scan.l index 2c997faa31af..7711be7cafb5 100644 --- a/gcc/cobol/scan.l +++ b/gcc/cobol/scan.l @@ -78,14 +78,14 @@ OSPC [[:space:]]* EOL \r?\n BLANK_EOL [[:blank:]]*{EOL} BLANK_OEOL [[:blank:]]*{EOL}? - + DOTSEP [.][[:space:]] DOTEOL [[:blank:]]*[.]{BLANK_EOL} SKIP [[:blank:]]*SKIP[123][[:blank:]]*[.]?{BLANK_EOL} TITLE [[:blank:]]*TITLE($|[.]|[^\n]*) - + COUNT [(][[:digit:]]+[)] N9 9+|(9{COUNT}) NP P+|(P{COUNT}) @@ -173,7 +173,7 @@ PUSH_FILE \f?[#]FILE{SPC}PUSH{SPC}[^\f]+\f POP_FILE \f?[#]FILE{SPC}POP\f LINE_DIRECTIVE [#]line{SPC}[[:alnum:]]+{SPC}[""''].+\n -%x procedure_div ident_state addr_of function classify +%x procedure_div ident_state addr_of function classify %x program_id_state comment_entries %x author_state date_state field_level field_state dot_state %x numeric_state name_state @@ -214,7 +214,7 @@ LINE_DIRECTIVE [#]line{SPC}[[:alnum:]]+{SPC}[""''].+\n } if( 0 == yyleng % 2 ) { yylval.literal.set_data( yyleng/2, hex_decode(yytext) ); - update_location_col(yytext, -3); + update_location_col(yytext, -3); return LITERAL; } dbgmsg( "hex literal '%s' " @@ -273,7 +273,7 @@ PROCEDURE{SPC}DIVISION { yy_push_state(procedure_div); [[:blank:]]*(ENVIRONMENT|DATA|PROCEDURE)[[:blank:]]+DIVISION/.+\n { yy_pop_state(); myless(0); } [[:blank:]]*AUTHOR[[:blank:].]+{EOL}? { - // Might not have an EOL, but stop on one. + // Might not have an EOL, but stop on one. yy_push_state(author_state); } {DOTEOL} @@ -869,7 +869,7 @@ ACCESS { return ACCESS; } ACCEPT { return ACCEPT; } DELETE { return DELETE; } -EJECT{DOTEOL}? { +EJECT{DOTEOL}? { if( ! dialect_ibm() ) { dialect_error(yylloc, "EJECT is not ISO syntax,", "ibm"); } @@ -960,7 +960,7 @@ USE({SPC}FOR)? { return USE; } USAGE { return USAGE; } UNBOUNDED { return UNBOUNDED; } /* use coded capacity 255 to indicate comp-x */ - COMP(UTATIONAL)?-X { return ucomputable(FldNumericBin5, 0xFF); } + COMP(UTATIONAL)?-X { return ucomputable(FldNumericBin5, 0xFF); } COMP(UTATIONAL)?-6 { return ucomputable(FldPacked, 0); } COMP(UTATIONAL)?-5 { return ucomputable(FldNumericBin5, 0); } COMP(UTATIONAL)?-4 { return scomputable(FldNumericBinary, 0); } @@ -1012,7 +1012,7 @@ USE({SPC}FOR)? { return USE; } PROCEDURE-POINTER { if( dialect_gcc() ) { error_msg(yylloc, "%s requires -dialect ibm or mf", yytext); } - yylval.field_attr = prog_ptr_e; + yylval.field_attr = prog_ptr_e; return POINTER; // return it anyway } @@ -1051,7 +1051,7 @@ USE({SPC}FOR)? { return USE; } DEPENDING { return DEPENDING; } DESCENDING { return DESCENDING; } DISPLAY { return DISPLAY; } - EJECT{DOTEOL}? { + EJECT{DOTEOL}? { if( ! dialect_ibm() ) { dialect_error(yylloc, "EJECT is not ISO syntax,", "ibm"); } @@ -1136,7 +1136,7 @@ USE({SPC}FOR)? { return USE; } PROCEDURE{SPC}DIVISION { BEGIN(procedure_div); return PROCEDURE_DIV; } - [*]>.*$ // ignore inline comment + [*]>.*$ // ignore inline comment } <numstr_state>{ @@ -1174,8 +1174,8 @@ USE({SPC}FOR)? { return USE; } * * On entry, we might have found a newline. If so, we accept any leading * blanks, and ignore blank lines. This sets up recognizing SKIP2 etc. - * - * Any blank or separator period ends terminates the picture. + * + * Any blank or separator period ends terminates the picture. */ <picture>{ ^[[:blank:]]+ @@ -1198,7 +1198,7 @@ USE({SPC}FOR)? { return USE; } {N9}/{N9}*[,.]? { yylval.number = ndigit(yyleng); return picset(NINES); } P+/[,.]?\r?\n { yylval.number = yyleng; return picset(PIC_P); } - {ALNUM}/{COUNT}({ALNUM}{COUNT}?)+ { + {ALNUM}/{COUNT}({ALNUM}{COUNT}?)+ { yy_push_state(picture_count); yylval.string = xstrdup(yytext); return picset(ALNUM); } {ALNUM}/{COUNT} { yy_push_state(picture_count); @@ -1263,10 +1263,10 @@ USE({SPC}FOR)? { return USE; } Z?['']{STRING1}[''] { auto *s = xstrdup(yytext); std::replace(s, s + strlen(s), '\'', '"'); ydflval.string = s; - update_location_col(s); + update_location_col(s); return LITERAL; } Z?[""]{STRING}[""] { ydflval.string = xstrdup(yytext); - update_location_col(yytext); + update_location_col(yytext); return LITERAL; } [=]{4} { static char nullstring[] = ""; ydflval.string = nullstring; return PSEUDOTEXT; } @@ -1277,7 +1277,7 @@ USE({SPC}FOR)? { return USE; } [^=]+[=]/[^=] { tmpstring_append(yyleng); } [^=]+/[=]{2} { yylval.string = xstrdup(tmpstring_append(yyleng)); ydflval.string = yylval.string; - update_location_col(yylval.string); + update_location_col(yylval.string); return PSEUDOTEXT; } [=]{2} { tmpstring = NULL; yy_pop_state(); } } @@ -1295,7 +1295,7 @@ USE({SPC}FOR)? { return USE; } char *s = xstrdup(tmpstring? tmpstring : "\0"); yylval.literal.set_data(strlen(s), s); ydflval.string = yylval.literal.data; - update_location_col(yylval.literal.data, -2); + update_location_col(yylval.literal.data, -2); tmpstring = NULL; pop_return LITERAL; } } @@ -1312,7 +1312,7 @@ USE({SPC}FOR)? { return USE; } char *s = xstrdup(tmpstring? tmpstring : "\0"); yylval.literal.set_data(strlen(s), s); ydflval.string = yylval.literal.data; - update_location_col(yylval.literal.data, -2); + update_location_col(yylval.literal.data, -2); tmpstring = NULL; pop_return LITERAL; } } @@ -1646,7 +1646,7 @@ USE({SPC}FOR)? { return USE; } std::transform( p, p + sizeof(name2), name2, []( char ch ) { switch(ch) { - case '-': + case '-': case '_': return ch; default: if( ISALNUM(ch) ) return ch; @@ -1654,9 +1654,9 @@ USE({SPC}FOR)? { return USE; } return '\0'; } ); symbol_elem_t *e = symbol_file(PROGRAM, name2); - /* - * For NAME IN FILENAME, we want the parser to handle it. - * For NAME IN NAME (of filename), the scanner handles it. + /* + * For NAME IN FILENAME, we want the parser to handle it. + * For NAME IN NAME (of filename), the scanner handles it. */ if( e ) { // e is an FD, but name2 could be its 01 cbl_namelist_t names = {name2, yytext}; @@ -1693,9 +1693,9 @@ USE({SPC}FOR)? { return USE; } } return NAME; } - {NAME}{OSPC}/[(] { BEGIN(subscripts); + {NAME}{OSPC}/[(] { BEGIN(subscripts); auto name = xstrdup(yytext); - char *eoname = name + strlen(name); + char *eoname = name + strlen(name); auto p = std::find_if(name, eoname, fisspace); // stop at blank, if any if( p < eoname ) *p = '\0'; @@ -1766,7 +1766,7 @@ USE({SPC}FOR)? { return USE; } case 'd': token = DATE_FMT; break; case 't': token = TIME_FMT; break; default: - dbgmsg("format must be literal"); + dbgmsg("format must be literal"); pop_return token; break; } @@ -1963,7 +1963,7 @@ BASIS { yy_push_state(basis); return BASIS; } int token = keyword_tok(null_trim(yylval.string), true); - if( token && ! symbol_field(PROGRAM, 0, yylval.string) ) { + if( token && ! symbol_field(PROGRAM, 0, yylval.string) ) { // 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); @@ -1972,7 +1972,7 @@ BASIS { yy_push_state(basis); return BASIS; } return token; // intrinsic and in repository } error_msg(yylloc, "'FUNCTION %s' required because %s " - "is not mentioned in REPOSITORY paragraph", + "is not mentioned in REPOSITORY paragraph", name, name); } @@ -2084,7 +2084,7 @@ BASIS { yy_push_state(basis); return BASIS; } RESERVE { return RESERVE; } {NAME} { ydflval.string = yylval.string = xstrdup(yytext); - pop_return NAME; + pop_return NAME; } } @@ -2417,7 +2417,7 @@ BASIS { yy_push_state(basis); return BASIS; } WITH { return WITH; } WORKING-STORAGE { return WORKING_STORAGE; } WRITE { return WRITE; } - + ZERO | ZEROES | ZEROS { return ZERO; } -- GitLab