From 0c133211da84ca416cbb02d4a48b1597e6db8077 Mon Sep 17 00:00:00 2001 From: Tobias Burnus <burnus@net-b.de> Date: Fri, 17 Feb 2012 11:51:10 +0100 Subject: [PATCH] re PR translation/52232 (translatable string typos: "conindexed" (should be "coindexed")) 2012-02-17 Tobias Burnus <burnus@net-b.de> Roland Stigge <stigge@antcom.de> PR translation/52232 PR translation/52234 PR translation/52245 PR translation/52246 PR translation/52262 PR translation/52273 * io.c (gfc_match_open): Fix typo. * interface.c (compare_actual_formal): Ditto. * lang.opt (freal-4-real-8, freal-4-real-16, freal-8-real-16): * Ditto. * match.c (alloc_opt_list, gfc_match_nullify): Ditto. * check.c (gfc_check_associated, gfc_check_null): Ditto. 2012-02-17 Tobias Burnus <burnus@net-b.de> PR translation/52232 PR translation/52234 PR translation/52245 PR translation/52246 PR translation/52262 PR translation/52273 * gfortran.dg/coarray_22.f90: Update dg-error. * gfortran.dg/allocate_alloc_opt_4.f90: Ditto. Co-Authored-By: Roland Stigge <stigge@antcom.de> From-SVN: r184331 --- gcc/fortran/ChangeLog | 15 +++++++++++++++ gcc/fortran/check.c | 6 +++--- gcc/fortran/interface.c | 4 ++-- gcc/fortran/io.c | 2 +- gcc/fortran/lang.opt | 6 +++--- gcc/fortran/match.c | 4 ++-- gcc/testsuite/ChangeLog | 11 +++++++++++ .../gfortran.dg/allocate_alloc_opt_4.f90 | 2 +- gcc/testsuite/gfortran.dg/coarray_22.f90 | 8 ++++---- 9 files changed, 42 insertions(+), 16 deletions(-) diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog index defca3f3512b..ef54b83d8766 100644 --- a/gcc/fortran/ChangeLog +++ b/gcc/fortran/ChangeLog @@ -1,3 +1,18 @@ +2012-02-17 Tobias Burnus <burnus@net-b.de> + Roland Stigge <stigge@antcom.de> + + PR translation/52232 + PR translation/52234 + PR translation/52245 + PR translation/52246 + PR translation/52262 + PR translation/52273 + * io.c (gfc_match_open): Fix typo. + * interface.c (compare_actual_formal): Ditto. + * lang.opt (freal-4-real-8, freal-4-real-16, freal-8-real-16): Ditto. + * match.c (alloc_opt_list, gfc_match_nullify): Ditto. + * check.c (gfc_check_associated, gfc_check_null): Ditto. + 2012-02-12 Mikael Morin <mikael@gcc.gnu.org> PR fortran/50981 diff --git a/gcc/fortran/check.c b/gcc/fortran/check.c index 4b72a5fb0b34..afeb653a5a8f 100644 --- a/gcc/fortran/check.c +++ b/gcc/fortran/check.c @@ -908,7 +908,7 @@ gfc_check_associated (gfc_expr *pointer, gfc_expr *target) if (attr1.pointer && gfc_is_coindexed (pointer)) { gfc_error ("'%s' argument of '%s' intrinsic at %L shall not be " - "conindexed", gfc_current_intrinsic_arg[0]->name, + "coindexed", gfc_current_intrinsic_arg[0]->name, gfc_current_intrinsic, &pointer->where); return FAILURE; } @@ -944,7 +944,7 @@ gfc_check_associated (gfc_expr *pointer, gfc_expr *target) if (attr1.pointer && gfc_is_coindexed (target)) { gfc_error ("'%s' argument of '%s' intrinsic at %L shall not be " - "conindexed", gfc_current_intrinsic_arg[1]->name, + "coindexed", gfc_current_intrinsic_arg[1]->name, gfc_current_intrinsic, &target->where); return FAILURE; } @@ -2851,7 +2851,7 @@ gfc_check_null (gfc_expr *mold) if (gfc_is_coindexed (mold)) { gfc_error ("'%s' argument of '%s' intrinsic at %L shall not be " - "conindexed", gfc_current_intrinsic_arg[0]->name, + "coindexed", gfc_current_intrinsic_arg[0]->name, gfc_current_intrinsic, &mold->where); return FAILURE; } diff --git a/gcc/fortran/interface.c b/gcc/fortran/interface.c index 9acd1fb9627d..7b5f445f208d 100644 --- a/gcc/fortran/interface.c +++ b/gcc/fortran/interface.c @@ -2305,7 +2305,7 @@ compare_actual_formal (gfc_actual_arglist **ap, gfc_formal_arglist *formal, && a->expr->ts.type == BT_CHARACTER) { if (where) - gfc_error ("Actual argument argument at %L to allocatable or " + gfc_error ("Actual argument at %L to allocatable or " "pointer dummy argument '%s' must have a deferred " "length type parameter if and only if the dummy has one", &a->expr->where, f->sym->name); @@ -2429,7 +2429,7 @@ compare_actual_formal (gfc_actual_arglist **ap, gfc_formal_arglist *formal, { if (where) gfc_error ("Coindexed ASYNCHRONOUS or VOLATILE actual argument at " - "at %L requires that dummy %s' has neither " + "at %L requires that dummy '%s' has neither " "ASYNCHRONOUS nor VOLATILE", &a->expr->where, f->sym->name); return 0; diff --git a/gcc/fortran/io.c b/gcc/fortran/io.c index 88f7a249e001..b7eac6c9be19 100644 --- a/gcc/fortran/io.c +++ b/gcc/fortran/io.c @@ -2016,7 +2016,7 @@ gfc_match_open (void) /* Checks on the ROUND specifier. */ if (open->round) { - if (gfc_notify_std (GFC_STD_F2003, "Fortran F2003: ROUND= at %C " + if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ROUND= at %C " "not allowed in Fortran 95") == FAILURE) goto cleanup; diff --git a/gcc/fortran/lang.opt b/gcc/fortran/lang.opt index c27b58e4b549..56c589c6bdf0 100644 --- a/gcc/fortran/lang.opt +++ b/gcc/fortran/lang.opt @@ -500,7 +500,7 @@ Enable range checking during compilation freal-4-real-8 Fortran RejectNegative -Interpret any REAl(4) as a REAL(8) +Interpret any REAL(4) as a REAL(8) freal-4-real-10 Fortran RejectNegative @@ -508,7 +508,7 @@ Interpret any REAL(4) as a REAL(10) freal-4-real-16 Fortran RejectNegative -Interpret any REAL(4) as a REAl(16) +Interpret any REAL(4) as a REAL(16) freal-8-real-4 Fortran RejectNegative @@ -520,7 +520,7 @@ Interpret any REAL(8) as a REAL(10) freal-8-real-16 Fortran RejectNegative -Interpret any REAL(8) as a REAl(16) +Interpret any REAL(8) as a REAL(16) frealloc-lhs Fortran diff --git a/gcc/fortran/match.c b/gcc/fortran/match.c index 89b59bc8036d..14381608c907 100644 --- a/gcc/fortran/match.c +++ b/gcc/fortran/match.c @@ -3661,7 +3661,7 @@ alloc_opt_list: if (head->next && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: SOURCE tag at %L" - " with more than a single allocate objects", + " with more than a single allocate object", &tmp->where) == FAILURE) goto cleanup; @@ -3787,7 +3787,7 @@ gfc_match_nullify (void) /* F2008, C1242. */ if (gfc_is_coindexed (p)) { - gfc_error ("Pointer object at %C shall not be conindexed"); + gfc_error ("Pointer object at %C shall not be coindexed"); goto cleanup; } diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog index 7c5081541fd3..1c813f180023 100644 --- a/gcc/testsuite/ChangeLog +++ b/gcc/testsuite/ChangeLog @@ -1,3 +1,14 @@ +2012-02-17 Tobias Burnus <burnus@net-b.de> + + PR translation/52232 + PR translation/52234 + PR translation/52245 + PR translation/52246 + PR translation/52262 + PR translation/52273 + * gfortran.dg/coarray_22.f90: Update dg-error. + * gfortran.dg/allocate_alloc_opt_4.f90: Ditto. + 2012-02-17 Rainer Orth <ro@CeBiTec.Uni-Bielefeld.DE> PR target/51753 diff --git a/gcc/testsuite/gfortran.dg/allocate_alloc_opt_4.f90 b/gcc/testsuite/gfortran.dg/allocate_alloc_opt_4.f90 index ed035b570922..ee6c3635912d 100644 --- a/gcc/testsuite/gfortran.dg/allocate_alloc_opt_4.f90 +++ b/gcc/testsuite/gfortran.dg/allocate_alloc_opt_4.f90 @@ -17,7 +17,7 @@ program a allocate(integer(4) :: i(4), source=n) ! { dg-error "conflicts with the typespec" } - allocate(i(4), j(n), source=n) ! { dg-error "Fortran 2008: SOURCE tag at .1. with more than a single allocate objects" } + allocate(i(4), j(n), source=n) ! { dg-error "Fortran 2008: SOURCE tag at .1. with more than a single allocate object" } allocate(x(4), source=n) ! { dg-error "type incompatible with" } diff --git a/gcc/testsuite/gfortran.dg/coarray_22.f90 b/gcc/testsuite/gfortran.dg/coarray_22.f90 index b09dfe382873..7860c3030dfb 100644 --- a/gcc/testsuite/gfortran.dg/coarray_22.f90 +++ b/gcc/testsuite/gfortran.dg/coarray_22.f90 @@ -15,14 +15,14 @@ type(t) :: x[*], y[*] if (associated(x%ptr)) stop 0 if (associated(x%ptr,y%ptr)) stop 0 -if (associated(x[1]%ptr)) stop 0 ! { dg-error "shall not be conindexed" } -if (associated(x%ptr,y[1]%ptr)) stop 0 ! { dg-error "shall not be conindexed" } +if (associated(x[1]%ptr)) stop 0 ! { dg-error "shall not be coindexed" } +if (associated(x%ptr,y[1]%ptr)) stop 0 ! { dg-error "shall not be coindexed" } nullify (x%ptr) -nullify (x[1]%ptr) ! { dg-error "shall not be conindexed" } +nullify (x[1]%ptr) ! { dg-error "shall not be coindexed" } x%ptr => null(x%ptr) -x%ptr => null(x[1]%ptr) ! { dg-error "shall not be conindexed" } +x%ptr => null(x[1]%ptr) ! { dg-error "shall not be coindexed" } x[1]%ptr => null(x%ptr) ! { dg-error "shall not have a coindex" } allocate(x%ptr) -- GitLab