Le 10/02/2015 23:35, Paul Richard Thomas a écrit :
> Dear Mikael, dear all,
> 
> Thank you for the previous review. I believe that the attached
> responds to all of your comments and correctly compiles the three
> testcases that you provided. Two of these have been included in the
> original testcase and the third appears separately.
> 
Hello Paul,

there are still some missing bits.  I updated the testcases.
Comments below.

> Index: gcc/fortran/resolve.c
> ===================================================================
> *** gcc/fortran/resolve.c     (revision 220481)
> --- gcc/fortran/resolve.c     (working copy)
> *************** resolve_function (gfc_expr *expr)
> *** 3086,3091 ****
> --- 3086,3113 ----
>       expr->ts = expr->symtree->n.sym->result->ts;
>       }
> 
> +   /* If an elemental function reference is marked as having an
> +      external array reference and this function is elemental, it
> +      should be so marked as well.  */
> +   if (gfc_elemental (NULL)

As elemental procedures can call pure procedures (or even impure ones if
they are themselves impure), I'm afraid we have to consider all
procedures, not just elemental ones.
See the case in elemental_dependency_4.f90

> +       && gfc_current_ns->proc_name->attr.function)
> +     {
> +       /* Check to see if this is a sibling function that has not yet
> +      been resolved.  */
> +       gfc_namespace *sibling = gfc_current_ns->sibling;
> +       for (; sibling; sibling = sibling->sibling)
> +     {
> +       if (sibling->proc_name == sym)
> +         {
> +           gfc_resolve (sibling);
> +           break;
> +         }
> +     }
> +
> +       if (sym->attr.array_outer_dependency)
> +     gfc_current_ns->proc_name->attr.array_outer_dependency = 1;
> +     }
> +
>     return t;
>   }
> 
> *************** resolve_variable (gfc_expr *e)
> *** 5054,5059 ****
> --- 5076,5089 ----
>                   && gfc_current_ns->parent->parent == sym->ns)))
>       sym->attr.host_assoc = 1;
> 
> +   if (sym->attr.dimension
> +       && (sym->ns != gfc_current_ns
> +       || sym->attr.use_assoc
> +       || sym->attr.in_common)
> +       && gfc_elemental (NULL)
same here.

> +       && gfc_current_ns->proc_name->attr.function)
There is also the case of subroutines which may be called from an
elemental function.  See elemental_dependency_4.f90

> +     gfc_current_ns->proc_name->attr.array_outer_dependency = 1;
> +
>   resolve_procedure:
>     if (t && !resolve_procedure_expression (e))
>       t = false;
> Index: gcc/fortran/trans-array.c
> ===================================================================
> *** gcc/fortran/trans-array.c (revision 220482)
> --- gcc/fortran/trans-array.c (working copy)
> *************** gfc_walk_function_expr (gfc_ss * ss, gfc
> *** 9096,9104 ****
>     /* Walk the parameters of an elemental function.  For now we always pass
>        by reference.  */
>     if (sym->attr.elemental || (comp && comp->attr.elemental))
> !     return gfc_walk_elemental_function_args (ss, 
> expr->value.function.actual,
>                                            gfc_get_proc_ifc_for_expr (expr),
>                                            GFC_SS_REFERENCE);
> 
>     /* Scalar functions are OK as these are evaluated outside the 
> scalarization
>        loop.  Pass back and let the caller deal with it.  */
> --- 9102,9115 ----
>     /* Walk the parameters of an elemental function.  For now we always pass
>        by reference.  */
>     if (sym->attr.elemental || (comp && comp->attr.elemental))
> !     {
> !       ss = gfc_walk_elemental_function_args (ss, 
> expr->value.function.actual,
>                                            gfc_get_proc_ifc_for_expr (expr),
>                                            GFC_SS_REFERENCE);
> +       if (sym->attr.array_outer_dependency
There is also the case of typebound procedures, see
elemental_dependency_5.f90.
I also tried to generate a case with procedure pointers, but didn't
manage to.

> +       && ss != gfc_ss_terminator)

gfc_ss_terminator is a special case; one should compare the old value vs
the new value of SS.
See the case in elemental_dependency_4.f90, this should not need a
temporary:
      array = index + Henry2(0)


> +     ss->info->array_outer_dependency = 1;
> +     }
> 
>     /* Scalar functions are OK as these are evaluated outside the 
> scalarization
>        loop.  Pass back and let the caller deal with it.  */


Mikael
! { dg-do run }
!
! Tests the fix for PR64952, in which the assignment to 'array' should
! have generated a temporary because of the references to the lhs in
! the function 'Fred'.
!
! Original report, involving function 'Nick'
! Contributed by Nick Maclaren  <n...@cam.ac.uk> on clf
! https://groups.google.com/forum/#!topic/comp.lang.fortran/TvVY5j3GPmg
!
! Other tests are due to Mikael Morin  <mikael.mo...@sfr.fr>
!
MODULE M
    INTEGER, PRIVATE :: i
    REAL :: arraym(5) = (/ (i+0.0, i = 1,5) /)
CONTAINS
    ELEMENTAL FUNCTION Bill (n, x)
        REAL :: Bill
        INTEGER, INTENT(IN) :: n
        REAL, INTENT(IN) :: x
        Bill = x+SUM(arraym(:n-1))+SUM(arraym(n+1:))
     END FUNCTION Bill
END MODULE M

ELEMENTAL FUNCTION Peter(n, x)
    USE M
    REAL :: Peter
    INTEGER, INTENT(IN) :: n
    REAL, INTENT(IN) :: x
    Peter = Bill(n, x)
END FUNCTION Peter

PROGRAM Main
    use M
    INTEGER :: i, index(5) = (/ (i, i = 1,5) /)
    REAL :: array(5) = (/ (i+0.0, i = 1,5) /)

    INTERFACE
        ELEMENTAL FUNCTION Peter(n, x)
            REAL :: Peter
            INTEGER, INTENT(IN) :: n
            REAL, INTENT(IN) :: x
        END FUNCTION Peter
    END INTERFACE

    PROCEDURE(Robert2), POINTER :: missme => Null()

! Original testcase
    array = Nick(index,array)
    If (any (array .ne. array(1))) call abort

! Check use association of the function works correctly.
    arraym = Bill(index,arraym)
    if (any (arraym .ne. arraym(1))) call abort

! Check siblings interact correctly.
    array = (/ (i+0.0, i = 1,5) /)
    array = Henry(index)
    if (any (array .ne. array(1))) call abort

    ! This should not create a temporary
    array = (/ (i+0.0, i = 1,5) /)
    array = index + Henry2(0) - array
    if (any (array .ne. 15.0)) call abort

    arraym = (/ (i+0.0, i = 1,5) /)
    arraym = Peter(index, arraym)
    print *, arraym
    !if (any (arraym .ne. 15.0)) call abort

    array = (/ (i+0.0, i = 1,5) /)
    array = Robert(index)
    print *, array
    !if (any (arraym .ne. 15.0)) call abort

    missme => Robert2
    array = (/ (i+0.0, i = 1,5) /)
    array = David(index)
    print *, array
    !if (any (arraym .ne. 15.0)) call abort

    array = (/ (i+0.0, i = 1,5) /)
    array = James(index)
    print *, array
    !if (any (arraym .ne. 15.0)) call abort

    array = (/ (i+0.0, i = 1,5) /)
    array = Romeo(index)
    print *, array
    !if (any (arraym .ne. 15.0)) call abort

CONTAINS
    ELEMENTAL FUNCTION Nick (n, x)
        REAL :: Nick
        INTEGER, INTENT(IN) :: n
        REAL, INTENT(IN) :: x
        Nick = x+SUM(array(:n-1))+SUM(array(n+1:))
    END FUNCTION Nick

! Note that the inverse order of Henry and Henry2 is trivial.
! This way round, Henry2 has to be resolved before Henry can
! be marked as having an inherited external array reference.
    ELEMENTAL FUNCTION Henry2 (n)
        REAL :: Henry2
        INTEGER, INTENT(IN) :: n
        Henry2 = n + SUM(array(:n-1))+SUM(array(n+1:))
    END FUNCTION Henry2

    ELEMENTAL FUNCTION Henry (n)
        REAL :: Henry
        INTEGER, INTENT(IN) :: n
        Henry = Henry2(n)
    END FUNCTION Henry

    PURE FUNCTION Robert2(n)
        REAL :: Robert2
        INTEGER, INTENT(IN) :: n
        Robert2 = Henry(n)
    END FUNCTION Robert2

    ELEMENTAL FUNCTION Robert(n)
        REAL :: Robert
        INTEGER, INTENT(IN) :: n
        Robert = Robert2(n)
    END FUNCTION Robert

    ELEMENTAL FUNCTION David (n)
        REAL :: David
        INTEGER, INTENT(IN) :: n
        David = missme(n)
    END FUNCTION David

    ELEMENTAL SUBROUTINE James2 (o, i)
        REAL, INTENT(OUT) :: o
        INTEGER, INTENT(IN) :: i
        o = Henry(i)
    END SUBROUTINE James2

    ELEMENTAL FUNCTION James(n)
        REAL :: James
        INTEGER, INTENT(IN) :: n
        CALL James2(James, n)
    END FUNCTION James

    FUNCTION Romeo2(n)
        REAL :: Romeo2
        INTEGER, INTENT(in) :: n
        Romeo2 = Henry(n)
    END FUNCTION Romeo2

    IMPURE ELEMENTAL FUNCTION Romeo(n)
        REAL :: Romeo
        INTEGER, INTENT(IN) :: n
        Romeo = Romeo2(n)
    END FUNCTION Romeo
END PROGRAM Main
! { dg-do run }
!
! Tests the fix for PR64952.
!
! Original report by Nick Maclaren  <n...@cam.ac.uk> on clf
! https://groups.google.com/forum/#!topic/comp.lang.fortran/TvVY5j3GPmg
! See elemental_dependency_4.f90
!
! This test contributed by Mikael Morin  <mikael.mo...@sfr.fr>
!
MODULE M
    INTEGER, PRIVATE :: i

    TYPE, ABSTRACT :: t
      REAL :: f
    CONTAINS
      PROCEDURE(Fred_ifc), DEFERRED, PASS :: tbp
    END TYPE t
    TYPE, EXTENDS(t) :: t2
    CONTAINS
      PROCEDURE :: tbp => Fred
    END TYPE t2

    TYPE(t2) :: array(5) = (/ (t2(i+0.0), i = 1,5) /)

    INTERFACE
        ELEMENTAL FUNCTION Fred_ifc (x, n)
            IMPORT
            REAL :: Fred
            CLASS(T), INTENT(IN) :: x
            INTEGER, INTENT(IN) :: n
        END FUNCTION Fred_ifc
    END INTERFACE

CONTAINS
    ELEMENTAL FUNCTION Fred (x, n)
        REAL :: Fred
        CLASS(T2), INTENT(IN) :: x
        INTEGER, INTENT(IN) :: n
        Fred = x%f+SUM(array(:n-1)%f)+SUM(array(n+1:)%f)
     END FUNCTION Fred
END MODULE M

PROGRAM Main
    USE M
    INTEGER :: i, index(5) = (/ (i, i = 1,5) /)
    
    array%f = array%tbp(index)
    if (any (array%f .ne. array(1)%f)) call abort

    array%f = index
    call Jack(array)
  CONTAINS
    SUBROUTINE Jack(dummy)
        CLASS(t) :: dummy(:)
        dummy%f = dummy%tbp(index)
        print *, dummy%f
        !if (any (dummy%f .ne. 15.0)) call abort
    END SUBROUTINE
END PROGRAM Main

Reply via email to