------- Comment #5 from pault at gcc dot gnu dot org  2008-01-03 17:58 -------

I'm taking a look at how it might be done.

This allows compilation to proceed:

Index: gcc/fortran/trans-decl.c
===================================================================
*** gcc/fortran/trans-decl.c    (revision 131237)
--- gcc/fortran/trans-decl.c    (working copy)
*************** gfc_get_symbol_decl (gfc_symbol * sym)
*** 951,956 ****
--- 951,970 ----
          sym->backend_decl = decl;
        }

+       if (sym->attr.subref_array_pointer)
+       {
+         tree span;
+         GFC_DECL_SUBREF_ARRAY_P (sym->backend_decl) = 1;
+         span = build_decl (VAR_DECL, create_tmp_var_name ("span"),
+                            gfc_array_index_type);
+         gfc_allocate_lang_decl (sym->backend_decl);
+         gfc_finish_var_decl (span, sym);
+         TREE_STATIC (span) = 1;
+         DECL_INITIAL (span) = build_int_cst (NULL_TREE, 0);
+
+         GFC_DECL_SPAN (sym->backend_decl) = span;
+       }
+
        TREE_USED (sym->backend_decl) = 1;
        if (sym->attr.assign && GFC_DECL_ASSIGN (sym->backend_decl) == 0)
        {

but the span is not passed back to the actual argument, as this demonstrates:

MODULE test
  IMPLICIT NONE
  TYPE :: my_type
    INTEGER :: value = 99
    INTEGER :: spacer = 199
  END TYPE
CONTAINS
  SUBROUTINE get_values(values, d)
    INTEGER,POINTER :: values(:)
    TYPE(my_type),POINTER :: d(:)
    values => d(:)%value
    print *, "in get_values  ", values
  END SUBROUTINE
END MODULE

  use test
  TYPE(my_type),POINTER :: d(:)
  INTEGER,POINTER :: values(:)
  allocate (d(2))
  call get_values (values, d)
  print *, "in MAIN        ", values
  deallocate (d)
end

I'll have to figure out how this can be done.  No doubt 'span' will have to be
added to the parent scope and the assignment performed on function entry and
return.  Hmmm!!  Better still would be to copy in and copy out.

Back to PR34431 and friends - I'll do this next.

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|ASSIGNED                    |WAITING


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=34640

Reply via email to