public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* [Bug fortran/52846] [F2008] Support submodules - part 3/3
@ 2015-07-23  8:37 Paul Richard Thomas
  2015-07-23  8:42 ` Damian Rouson
  2015-07-23 16:35 ` Mikael Morin
  0 siblings, 2 replies; 23+ messages in thread
From: Paul Richard Thomas @ 2015-07-23  8:37 UTC (permalink / raw)
  To: Bader, Reinhold, fortran, gcc-patches, Damian Rouson,
	salvatore.filippone

[-- Attachment #1: Type: text/plain, Size: 4528 bytes --]

Dear All,

This is the third and final patch to implement submodules in gfortran.
It is the part that deals with private module entities. Unfortunately,
it is the most invasive and I would either like to have strong support
for it to be committed or a bright idea as to how to do it otherwise.

Since all the private entities in a module have to be transmitted to
their descendant submodules, whilst keeping them hidden from normal
use statements, I have chosen to write the module file as usual and
add a second part that contains the private entities. This latter is
only read when processing submodule statements.

I looked into encrypting the second part but could not find a way to
obtain the compression ratios that gzipping the module file affords,
largely from the repetition of attribute keywords. It was tempting to
reform completely the format of module files such that the symbol tree
is represented in binary format rather than in text. However, being
able to gunzip the files is very helpful from the diagnostic point of
view. Perhaps this is a suitable future upgrade for 6.0.0? That said,
I do not regard it as being high priority nor necessarily useful.

The other significant change is in respect of making module variable,
string length and procedure pointer declarations unconditionally
TREE_PUBLIC, whilst recycling the conditions to set DECL_VISIBILITY to
VISIBILITY_HIDDEN. This was a suggestion from Richard Biener, which
seems to do what is needed in libraries. This affects two existing
testcases: public_private_module_[2,6].f90, where xfails have been
added, where assembler symbols should be optimized away. These tests
can be removed if the above changes prove to be robust and acceptable
but I was reluctant to do this right away.

The rest of the patch is concerned with signaling to module.c that a
submodule statement is being processed.

It does cross my mind that all of this part of the submodule
implementation could be subject to the condition that a compiler
option is set. I am struck by the notion that making private module
entities available to submodules is an unnecessary complication and
that it amounts to be an error in the standard. This is why I am
suggesting the possibility of a specific compiler option.

The new testcase submodule_10.f08 is a near verbatim contribution from
Salvatore Filippone, for which thanks are due.

The remaining tasks are to try to fix PR66762, where submodule_6.f08
fails with -fto, and to update the documentation.

Bootstraps and regtests on FC21/x86_64 - OK for trunk?

Cheers

Paul

2015-07-23  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/52846
    * match.h : Add bool argument to gfc_use_modules so that it can
    signal to module.c that a submodule statement is being
    processed.
    * module.c (read_module): Add new module_locus, 'end_module'.
    Set it at the end of the public part of the module file. Then go
    there once the public part has been processed, ready to read
    the private part of the module file.
    (check_access): Change original to 'check_access1' and call it
    from 'check_access'. This latter inverts the result, according
    to whether or not static 'invert_access' is true.
    (gfc_dump_module): Write the public part of the module file as
    before and then follow it with the private part, obtained by
    setting 'invert_access' true. Once done, this is reset.
    (gfc_use_module): Read the public part of the module file. If
    this is a submodule and static 'submodule_stmt' is true, then
    read the private part. This permits the private part of module
    files to be respected with conventional use statements.
    (gfc_use_modules): 'submodule_stmt' set true if the ancestor
    module file is being used in processing submodule statement.
    * parse.c (use_modules): Introduce 'using_ancestor_modules' as
    a boolean argument. All calls set this argument false, except;
    (parse_module): Call use_modules with 'using_ancestor_modules'
    set true to signal the processing of a submodule statement.
    * trans-decl.c (gfc_finish_var_decl, gfc_build_qualified_array,
    get_proc_pointer_decl): Set TREE_PUBLIC unconditionally and use
    the conditions to set DECL_VISIBILITY as hidden and to set as
    true DECL_VISIBILITY_SPECIFIED.

2015-07-23  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/52846

    * gfortran.dg/public_private_module_2.f90: Add two XFAILS.
    * gfortran.dg/public_private_module_6.f90: Add an XFAIL.
    * gfortran.dg/submodule_10.f08: New test

[-- Attachment #2: private_final.diff --]
[-- Type: text/plain, Size: 18767 bytes --]

Index: gcc/fortran/match.h
===================================================================
*** gcc/fortran/match.h	(revision 226054)
--- gcc/fortran/match.h	(working copy)
*************** match gfc_match_expr (gfc_expr **);
*** 293,299 ****
  /* module.c.  */
  match gfc_match_use (void);
  match gfc_match_submodule (void);
! void gfc_use_modules (void);
  
  #endif  /* GFC_MATCH_H  */
  
--- 293,299 ----
  /* module.c.  */
  match gfc_match_use (void);
  match gfc_match_submodule (void);
! void gfc_use_modules (bool);
  
  #endif  /* GFC_MATCH_H  */
  
Index: gcc/fortran/module.c
===================================================================
*** gcc/fortran/module.c	(revision 226054)
--- gcc/fortran/module.c	(working copy)
*************** check_for_ambiguous (gfc_symtree *st, po
*** 4942,4948 ****
  static void
  read_module (void)
  {
!   module_locus operator_interfaces, user_operators, omp_udrs;
    const char *p;
    char name[GFC_MAX_SYMBOL_LEN + 1];
    int i;
--- 4942,4948 ----
  static void
  read_module (void)
  {
!   module_locus operator_interfaces, user_operators, omp_udrs, end_module;
    const char *p;
    char name[GFC_MAX_SYMBOL_LEN + 1];
    int i;
*************** read_module (void)
*** 5192,5197 ****
--- 5192,5198 ----
      }
  
    mio_rparen ();
+   get_module_locus (&end_module);
  
    /* Load intrinsic operator interfaces.  */
    set_module_locus (&operator_interfaces);
*************** read_module (void)
*** 5274,5279 ****
--- 5275,5284 ----
       to hidden symbols.  */
  
    read_cleanup (pi_root);
+ 
+   /* Go to the end so that we are ready to read the private entities
+      for submodules.  */
+   set_module_locus (&end_module);
  }
  
  
*************** read_module (void)
*** 5282,5290 ****
     element is declared as PUBLIC, then it is public; if declared 
     PRIVATE, then private, and otherwise it is public unless the default
     access in this context has been declared PRIVATE.  */
  
  static bool
! check_access (gfc_access specific_access, gfc_access default_access)
  {
    if (specific_access == ACCESS_PUBLIC)
      return TRUE;
--- 5287,5296 ----
     element is declared as PUBLIC, then it is public; if declared 
     PRIVATE, then private, and otherwise it is public unless the default
     access in this context has been declared PRIVATE.  */
+ static bool invert_access = false;
  
  static bool
! check_access1 (gfc_access specific_access, gfc_access default_access)
  {
    if (specific_access == ACCESS_PUBLIC)
      return TRUE;
*************** check_access (gfc_access specific_access
*** 5298,5303 ****
--- 5304,5320 ----
  }
  
  
+ static bool
+ check_access (gfc_access specific_access, gfc_access default_access)
+ {
+   bool res;
+   res = check_access1 (specific_access, default_access);
+   if (invert_access)
+     res = res ? false : true;
+   return res;
+ }
+ 
+ 
  bool
  gfc_check_symbol_access (gfc_symbol *sym)
  {
*************** gfc_dump_module (const char *name, int d
*** 6024,6035 ****
    /* Write the module itself.  */
    iomode = IO_OUTPUT;
  
    init_pi_tree ();
- 
    write_module ();
  
    free_pi_tree (pi_root);
    pi_root = NULL;
  
    write_char ('\n');
  
--- 6041,6061 ----
    /* Write the module itself.  */
    iomode = IO_OUTPUT;
  
+   /* Write the public part of the module.  */
    init_pi_tree ();
    write_module ();
+   free_pi_tree (pi_root);
+   pi_root = NULL;
  
+   /* Now write the private part for submodules.  */
+   write_char ('\n');
+   write_char ('\n');
+   init_pi_tree ();
+   invert_access = true;
+   write_module ();
    free_pi_tree (pi_root);
    pi_root = NULL;
+   invert_access = false;
  
    write_char ('\n');
  
*************** use_iso_fortran_env_module (void)
*** 6732,6737 ****
--- 6758,6764 ----
  
  
  /* Process a USE directive.  */
+ static bool submodule_stmt;
  
  static void
  gfc_use_module (gfc_use_list *module)
*************** gfc_use_module (gfc_use_list *module)
*** 6888,6903 ****
        gfc_fatal_error ("Can't USE the same %smodule we're building!",
  		       p->state == COMP_SUBMODULE ? "sub" : "");
  
    init_pi_tree ();
    init_true_name_tree ();
- 
    read_module ();
- 
    free_true_name (true_name_root);
    true_name_root = NULL;
  
    free_pi_tree (pi_root);
    pi_root = NULL;
  
    XDELETEVEC (module_content);
    module_content = NULL;
--- 6915,6941 ----
        gfc_fatal_error ("Can't USE the same %smodule we're building!",
  		       p->state == COMP_SUBMODULE ? "sub" : "");
  
+   /* Do the normal module read.  */
    init_pi_tree ();
    init_true_name_tree ();
    read_module ();
    free_true_name (true_name_root);
    true_name_root = NULL;
+   free_pi_tree (pi_root);
+   pi_root = NULL;
  
+   /* Read the private entities into submodules.  */
+   if (gfc_state_stack->state == COMP_SUBMODULE
+       && submodule_stmt)
+     {
+       init_pi_tree ();
+       init_true_name_tree ();
+       read_module ();
+       free_true_name (true_name_root);
+       true_name_root = NULL;
    free_pi_tree (pi_root);
    pi_root = NULL;
+     }
  
    XDELETEVEC (module_content);
    module_content = NULL;
*************** rename_list_remove_duplicate (gfc_use_re
*** 6936,6948 ****
  }
  
  
! /* Process all USE directives.  */
  
  void
! gfc_use_modules (void)
  {
    gfc_use_list *next, *seek, *last;
  
    for (next = module_list; next; next = next->next)
      {
        bool non_intrinsic = next->non_intrinsic;
--- 6974,6990 ----
  }
  
  
! /* Process all USE directives. 'using_ancestor_modules' flags up that
!    the SUBMODULE statement is being processed and so all objects that
!    are PRIVATE in the ancestor module must be read.  */
  
  void
! gfc_use_modules (bool using_ancestor_modules)
  {
    gfc_use_list *next, *seek, *last;
  
+   submodule_stmt = using_ancestor_modules;
+ 
    for (next = module_list; next; next = next->next)
      {
        bool non_intrinsic = next->non_intrinsic;
Index: gcc/fortran/parse.c
===================================================================
*** gcc/fortran/parse.c	(revision 226054)
--- gcc/fortran/parse.c	(working copy)
*************** match_word_omp_simd (const char *str, ma
*** 103,118 ****
  }
  
  
! /* Load symbols from all USE statements encountered in this scoping unit.  */
  
  static void
! use_modules (void)
  {
    gfc_error_buffer old_error;
  
    gfc_push_error (&old_error);
    gfc_buffer_error (false);
!   gfc_use_modules ();
    gfc_buffer_error (true);
    gfc_pop_error (&old_error);
    gfc_commit_symbols ();
--- 103,121 ----
  }
  
  
! /* Load symbols from all USE statements encountered in this scoping unit.
!    'using_ancestor_modules' flags up that the SUBMODULE statement is
!    being processed and so all objects that are PRIVATE in the ancestor
!    module must be read.  */
  
  static void
! use_modules (bool using_ancestor_modules)
  {
    gfc_error_buffer old_error;
  
    gfc_push_error (&old_error);
    gfc_buffer_error (false);
!   gfc_use_modules (using_ancestor_modules);
    gfc_buffer_error (true);
    gfc_pop_error (&old_error);
    gfc_commit_symbols ();
*************** decode_specification_statement (void)
*** 167,173 ****
      {
        undo_new_statement ();
        if (last_was_use_stmt)
! 	use_modules ();
      }
  
    match ("import", gfc_match_import, ST_IMPORT);
--- 170,176 ----
      {
        undo_new_statement ();
        if (last_was_use_stmt)
! 	use_modules (false);
      }
  
    match ("import", gfc_match_import, ST_IMPORT);
*************** decode_statement (void)
*** 328,334 ****
      }
  
    if (last_was_use_stmt)
!     use_modules ();
  
    /* Try matching a data declaration or function declaration. The
        input "REALFUNCTIONA(N)" can mean several things in different
--- 331,337 ----
      }
  
    if (last_was_use_stmt)
!     use_modules (false);
  
    /* Try matching a data declaration or function declaration. The
        input "REALFUNCTIONA(N)" can mean several things in different
*************** verify_token_free (const char* token, in
*** 923,929 ****
    gcc_assert (gfc_is_whitespace(c));
    gfc_gobble_whitespace ();
    if (last_was_use_stmt)
!     use_modules ();
  }
  
  /* Get the next statement in free form source.  */
--- 926,932 ----
    gcc_assert (gfc_is_whitespace(c));
    gfc_gobble_whitespace ();
    if (last_was_use_stmt)
!     use_modules (false);
  }
  
  /* Get the next statement in free form source.  */
*************** verify_token_fixed (const char *token, i
*** 1077,1083 ****
        return false;
      }
    if (last_was_use_stmt)
!     use_modules ();
  
    return true;
  }
--- 1080,1086 ----
        return false;
      }
    if (last_was_use_stmt)
!     use_modules (false);
  
    return true;
  }
*************** parse_module (void)
*** 5321,5327 ****
       inherits and to set (most) of the symbols as host associated.  */
    if (gfc_current_state () == COMP_SUBMODULE)
      {
!       use_modules ();
        gfc_traverse_ns (gfc_current_ns, set_syms_host_assoc);
      }
  
--- 5324,5330 ----
       inherits and to set (most) of the symbols as host associated.  */
    if (gfc_current_state () == COMP_SUBMODULE)
      {
!       use_modules (true);
        gfc_traverse_ns (gfc_current_ns, set_syms_host_assoc);
      }
  
Index: gcc/fortran/trans-decl.c
===================================================================
*** gcc/fortran/trans-decl.c	(revision 226054)
--- gcc/fortran/trans-decl.c	(working copy)
*************** gfc_finish_var_decl (tree decl, gfc_symb
*** 596,601 ****
--- 596,606 ----
  	 both, of course.) (J3/04-007, section 15.3).  */
        TREE_PUBLIC(decl) = 1;
        DECL_COMMON(decl) = 1;
+       if (sym->attr.access == ACCESS_PRIVATE && !sym->attr.public_used)
+ 	{
+ 	  DECL_VISIBILITY (decl) = VISIBILITY_HIDDEN;
+ 	  DECL_VISIBILITY_SPECIFIED (decl) = true;
+ 	}
      }
  
    /* If a variable is USE associated, it's always external.  */
*************** gfc_finish_var_decl (tree decl, gfc_symb
*** 609,615 ****
        /* TODO: Don't set sym->module for result or dummy variables.  */
        gcc_assert (current_function_decl == NULL_TREE || sym->result == sym);
  
-       if (sym->attr.access != ACCESS_PRIVATE || sym->attr.public_used)
  	TREE_PUBLIC (decl) = 1;
        TREE_STATIC (decl) = 1;
      }
--- 614,619 ----
*************** gfc_build_qualified_array (tree decl, gf
*** 837,845 ****
  	  else
  	    TREE_STATIC (token) = 1;
  
! 	  if (sym->attr.use_assoc || sym->attr.access != ACCESS_PRIVATE ||
! 	      sym->attr.public_used)
! 	    TREE_PUBLIC (token) = 1;
  	}
        else
  	{
--- 841,853 ----
  	  else
  	    TREE_STATIC (token) = 1;
  
! 	  TREE_PUBLIC (token) = 1;
! 
! 	  if (sym->attr.access == ACCESS_PRIVATE && !sym->attr.public_used)
! 	    {
! 	      DECL_VISIBILITY (token) = VISIBILITY_HIDDEN;
! 	      DECL_VISIBILITY_SPECIFIED (token) = true;
! 	    }
  	}
        else
  	{
*************** get_proc_pointer_decl (gfc_symbol *sym)
*** 1747,1755 ****
    else if (sym->module && sym->ns->proc_name->attr.flavor == FL_MODULE)
      {
        /* This is the declaration of a module variable.  */
!       if (sym->ns->proc_name->attr.flavor == FL_MODULE
! 	  && (sym->attr.access != ACCESS_PRIVATE || sym->attr.public_used))
! 	TREE_PUBLIC (decl) = 1;
        TREE_STATIC (decl) = 1;
      }
  
--- 1755,1766 ----
    else if (sym->module && sym->ns->proc_name->attr.flavor == FL_MODULE)
      {
        /* This is the declaration of a module variable.  */
!       TREE_PUBLIC (decl) = 1;
!       if (sym->attr.access == ACCESS_PRIVATE && !sym->attr.public_used)
! 	{
! 	  DECL_VISIBILITY (decl) = VISIBILITY_HIDDEN;
! 	  DECL_VISIBILITY_SPECIFIED (decl) = true;
! 	}
        TREE_STATIC (decl) = 1;
      }
  
Index: gcc/testsuite/gfortran.dg/public_private_module_2.f90
===================================================================
*** gcc/testsuite/gfortran.dg/public_private_module_2.f90	(revision 226054)
--- gcc/testsuite/gfortran.dg/public_private_module_2.f90	(working copy)
***************
*** 18,29 ****
          integer, bind(C,name='') :: qq
        end module mod
  
        ! { dg-final { scan-assembler "__mod_MOD_aa" } }
!       ! { dg-final { scan-assembler-not "iii" } }
        ! { dg-final { scan-assembler "jj" } }
        ! { dg-final { scan-assembler "lll" } }
        ! { dg-final { scan-assembler-not "kk" } }
!       ! { dg-final { scan-assembler-not "mmmm" } }
        ! { dg-final { scan-assembler "nnn" } }
        ! { dg-final { scan-assembler "oo" } }
        ! { dg-final { scan-assembler "__mod_MOD_qq" } }
--- 18,32 ----
          integer, bind(C,name='') :: qq
        end module mod
  
+ ! The two xfails below have appeared with the introduction of submodules. 'iii' and
+ ! 'mmm' now are TREE_PUBLIC but has DECL_VISIBILITY (decl) = VISIBILITY_HIDDEN set.
+ 
        ! { dg-final { scan-assembler "__mod_MOD_aa" } }
!       ! { dg-final { scan-assembler-not "iii" { xfail *-*-* } } }
        ! { dg-final { scan-assembler "jj" } }
        ! { dg-final { scan-assembler "lll" } }
        ! { dg-final { scan-assembler-not "kk" } }
!       ! { dg-final { scan-assembler-not "mmmm" { xfail *-*-* } } }
        ! { dg-final { scan-assembler "nnn" } }
        ! { dg-final { scan-assembler "oo" } }
        ! { dg-final { scan-assembler "__mod_MOD_qq" } }
Index: gcc/testsuite/gfortran.dg/public_private_module_6.f90
===================================================================
*** gcc/testsuite/gfortran.dg/public_private_module_6.f90	(revision 226054)
--- gcc/testsuite/gfortran.dg/public_private_module_6.f90	(working copy)
*************** module m
*** 11,14 ****
    integer, save :: aaaa
  end module m
  
! ! { dg-final { scan-assembler-not "aaaa" } }
--- 11,17 ----
    integer, save :: aaaa
  end module m
  
! ! The xfail below has appeared with the introduction of submodules. 'aaaa'
! ! now is TREE_PUBLIC but has DECL_VISIBILITY (decl) = VISIBILITY_HIDDEN set.
! 
! ! { dg-final { scan-assembler-not "aaaa" { xfail *-*-* } } }
Index: gcc/testsuite/gfortran.dg/submodule_10.f08
===================================================================
*** gcc/testsuite/gfortran.dg/submodule_10.f08	(revision 0)
--- gcc/testsuite/gfortran.dg/submodule_10.f08	(working copy)
***************
*** 0 ****
--- 1,170 ----
+ ! { dg-do compile }
+ !
+ ! Checks that PRIVATE enities are visible to submodules.
+ !
+ ! Contributed by Salvatore Filippone  <salvatore.filippone@uniroma2.it>
+ !
+ module const_mod
+   integer, parameter  :: ndig=8
+   integer, parameter  :: ipk_ = selected_int_kind(ndig)
+   integer, parameter  :: longndig=12
+   integer, parameter  :: long_int_k_ = selected_int_kind(longndig)
+   integer, parameter  :: mpik_ = kind(1)
+ 
+   integer(ipk_), parameter, public :: success_=0
+ 
+ end module const_mod
+ 
+ 
+ module error_mod
+   use const_mod
+ 
+   integer(ipk_), parameter, public :: act_ret_=0
+   integer(ipk_), parameter, public :: act_print_=1
+   integer(ipk_), parameter, public :: act_abort_=2
+ 
+   integer(ipk_), parameter, public ::  no_err_ = 0
+ 
+   public error, errcomm, get_numerr, &
+        & error_handler, &
+        & ser_error_handler, par_error_handler
+ 
+ 
+   interface error_handler
+     module subroutine ser_error_handler(err_act)
+       integer(ipk_), intent(inout) ::  err_act
+     end subroutine ser_error_handler
+     module subroutine par_error_handler(ictxt,err_act)
+       integer(mpik_), intent(in) ::  ictxt
+       integer(ipk_), intent(in) ::  err_act
+     end subroutine par_error_handler
+   end interface
+ 
+   interface error
+     module subroutine serror()
+     end subroutine serror
+     module subroutine perror(ictxt,abrt)
+       integer(mpik_), intent(in) ::  ictxt
+       logical, intent(in), optional  :: abrt
+     end subroutine perror
+   end interface
+ 
+ 
+   interface error_print_stack
+     module subroutine par_error_print_stack(ictxt)
+       integer(mpik_), intent(in) ::  ictxt
+     end subroutine par_error_print_stack
+     module subroutine ser_error_print_stack()
+     end subroutine ser_error_print_stack
+   end interface
+ 
+   interface errcomm
+     module subroutine errcomm(ictxt, err)
+       integer(mpik_), intent(in)   :: ictxt
+       integer(ipk_), intent(inout):: err
+     end subroutine errcomm
+   end interface errcomm
+ 
+ 
+   private
+ 
+   type errstack_node
+ 
+     integer(ipk_) ::   err_code=0
+     character(len=20)        ::   routine=''
+     integer(ipk_),dimension(5)     ::   i_err_data=0
+     character(len=40)        ::   a_err_data=''
+     type(errstack_node), pointer :: next
+ 
+   end type errstack_node
+ 
+ 
+   type errstack
+     type(errstack_node), pointer :: top => null()
+     integer(ipk_) :: n_elems=0
+   end type errstack
+ 
+ 
+   type(errstack), save  :: error_stack
+   integer(ipk_), save   :: error_status    = no_err_
+   integer(ipk_), save   :: verbosity_level = 1
+   integer(ipk_), save   :: err_action      = act_abort_
+   integer(ipk_), save   :: debug_level     = 0, debug_unit, serial_debug_level=0
+ 
+ contains
+ end module error_mod
+ 
+ submodule (error_mod) error_impl_mod
+   use const_mod
+ contains
+   ! checks whether an error has occurred on one of the processes in the execution pool
+   subroutine errcomm(ictxt, err)
+     integer(mpik_), intent(in)   :: ictxt
+     integer(ipk_), intent(inout):: err
+ 
+ 
+   end subroutine errcomm
+ 
+   subroutine ser_error_handler(err_act)
+     implicit none
+     integer(ipk_), intent(inout) ::  err_act
+ 
+     if (err_act /= act_ret_)     &
+          &  call error()
+     if (err_act == act_abort_) stop
+ 
+     return
+   end subroutine ser_error_handler
+ 
+   subroutine par_error_handler(ictxt,err_act)
+     implicit none
+     integer(mpik_), intent(in) ::  ictxt
+     integer(ipk_), intent(in) ::  err_act
+ 
+     if (err_act == act_print_)     &
+          &  call error(ictxt, abrt=.false.)
+     if (err_act == act_abort_)      &
+          &  call error(ictxt, abrt=.true.)
+ 
+     return
+ 
+   end subroutine par_error_handler
+ 
+   subroutine par_error_print_stack(ictxt)
+     integer(mpik_), intent(in) ::  ictxt
+ 
+     call error(ictxt, abrt=.false.)
+ 
+   end subroutine par_error_print_stack
+ 
+   subroutine ser_error_print_stack()
+ 
+     call error()
+   end subroutine ser_error_print_stack
+ 
+   subroutine serror()
+ 
+     implicit none
+ 
+   end subroutine serror
+ 
+   subroutine perror(ictxt,abrt)
+     use const_mod
+     implicit none
+     integer(mpik_), intent(in) :: ictxt
+     logical, intent(in), optional  :: abrt
+ 
+   end subroutine perror
+ 
+ end submodule error_impl_mod
+ 
+ program testlk
+   use error_mod
+   implicit none
+ 
+   call error()
+ 
+   stop
+ end program testlk
+ 
+ 

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-07-23  8:37 [Bug fortran/52846] [F2008] Support submodules - part 3/3 Paul Richard Thomas
@ 2015-07-23  8:42 ` Damian Rouson
  2015-07-23  8:46   ` Paul Richard Thomas
  2015-07-23 16:35 ` Mikael Morin
  1 sibling, 1 reply; 23+ messages in thread
From: Damian Rouson @ 2015-07-23  8:42 UTC (permalink / raw)
  To: Paul Richard Thomas
  Cc: Bader, Reinhold, fortran, gcc-patches, Salvatore Filippone



> On Jul 23, 2015, at 12:46 AM, Paul Richard Thomas <paul.richard.thomas@gmail.com> wrote:
> 
> Since all the private entities in a module have to be transmitted to
> their descendant submodules, whilst keeping them hidden from normal
> use statements, I have chosen to write the module file as usual and
> add a second part that contains the private entities. This latter is
> only read when processing submodule statements.

Hi Paul,

Could you comment on whether this approach alleviates compilation cascades as 
seems to have been envisioned when submodules were added to the standard?  My 
guess is that a developer could adopt a policy of putting only public information in a
module and reserving all private information for submodules, which would mitigate
against unnecessary compilation cascades and would be consistent with putting
the interface in the module and the implementation in a submodule.. 

> It does cross my mind that all of this part of the submodule
> implementation could be subject to the condition that a compiler
> option is set. I am struck by the notion that making private module
> entities available to submodules is an unnecessary complication and
> that it amounts to be an error in the standard. This is why I am
> suggesting the possibility of a specific compiler option.

I strongly advocate against having to pass flags to force standard-compliant behavior 
(I happened to have just posted to c.l.f on a frustrating way in which two compilers
currently require flags to comply with the standard), although it sounds like it might 
not matter in this case if one adopts the aforementioned policy 
of putting only pubic information in modules.

Damian

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-07-23  8:42 ` Damian Rouson
@ 2015-07-23  8:46   ` Paul Richard Thomas
  0 siblings, 0 replies; 23+ messages in thread
From: Paul Richard Thomas @ 2015-07-23  8:46 UTC (permalink / raw)
  To: Damian Rouson; +Cc: Bader, Reinhold, fortran, gcc-patches, Salvatore Filippone

Dear Damian,

I do not think that there is any effect on compilation cascades. As
long as the private part of the module file remains unchanged, it will
not be recompiled if a descendant submodule is modified. Naturally,
the size of the module file is increased but, if one is careful, this
is not a big deal. A gotcha, which I will have to emphasize in the
documentation occurs if another module file is used and its symbols
are not exposed by public statements. If there are large numbers of
symbols this can have a big effect on the size of the module file. I
noticed this, when examining one of gfortran's testcases where the
ISO_C_BINDING intrinsic module is used. Generous sprinklings of USE
ONLYs are required to keep the module file sizes under control.

I am not over enthusiastic about using compilation flags to uphold
standards either.

Cheers

Paul

On 23 July 2015 at 10:22, Damian Rouson <damian@sourceryinstitute.org> wrote:
>
>
>> On Jul 23, 2015, at 12:46 AM, Paul Richard Thomas <paul.richard.thomas@gmail.com> wrote:
>>
>> Since all the private entities in a module have to be transmitted to
>> their descendant submodules, whilst keeping them hidden from normal
>> use statements, I have chosen to write the module file as usual and
>> add a second part that contains the private entities. This latter is
>> only read when processing submodule statements.
>
> Hi Paul,
>
> Could you comment on whether this approach alleviates compilation cascades as
> seems to have been envisioned when submodules were added to the standard?  My
> guess is that a developer could adopt a policy of putting only public information in a
> module and reserving all private information for submodules, which would mitigate
> against unnecessary compilation cascades and would be consistent with putting
> the interface in the module and the implementation in a submodule..
>
>> It does cross my mind that all of this part of the submodule
>> implementation could be subject to the condition that a compiler
>> option is set. I am struck by the notion that making private module
>> entities available to submodules is an unnecessary complication and
>> that it amounts to be an error in the standard. This is why I am
>> suggesting the possibility of a specific compiler option.
>
> I strongly advocate against having to pass flags to force standard-compliant behavior
> (I happened to have just posted to c.l.f on a frustrating way in which two compilers
> currently require flags to comply with the standard), although it sounds like it might
> not matter in this case if one adopts the aforementioned policy
> of putting only pubic information in modules.
>
> Damian



-- 
Outside of a dog, a book is a man's best friend. Inside of a dog it's
too dark to read.

Groucho Marx

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-07-23  8:37 [Bug fortran/52846] [F2008] Support submodules - part 3/3 Paul Richard Thomas
  2015-07-23  8:42 ` Damian Rouson
@ 2015-07-23 16:35 ` Mikael Morin
  2015-07-24  8:08   ` Paul Richard Thomas
  1 sibling, 1 reply; 23+ messages in thread
From: Mikael Morin @ 2015-07-23 16:35 UTC (permalink / raw)
  To: Paul Richard Thomas, Bader, Reinhold, fortran, gcc-patches,
	Damian Rouson, salvatore.filippone

Hello Paul,

Le 23/07/2015 09:46, Paul Richard Thomas a écrit :
> Since all the private entities in a module have to be transmitted to
> their descendant submodules, whilst keeping them hidden from normal
> use statements, I have chosen to write the module file as usual and
> add a second part that contains the private entities. This latter is
> only read when processing submodule statements.
>
why not write them to the/a .smod file?  It was its primary purpose, 
wasn't it?
[Sorry, I followed the submodule stuff very remotely].

It's probably bad practice to put private entities in module files, at 
least now that submodules are supported.  Nevertheless with your change, 
modifications made to private entities produce recompilation cascades, 
even though the public interfaces are left unchanged.

Mikael

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-07-23 16:35 ` Mikael Morin
@ 2015-07-24  8:08   ` Paul Richard Thomas
  2015-07-24  8:09     ` Damian Rouson
  0 siblings, 1 reply; 23+ messages in thread
From: Paul Richard Thomas @ 2015-07-24  8:08 UTC (permalink / raw)
  To: Mikael Morin
  Cc: Bader, Reinhold, fortran, gcc-patches, Damian Rouson,
	salvatore.filippone

Dear Mikael,

It had crossed my mind also that a .mod and a .smod file could be
written. Normally, the .smod files are produced by the submodules
themselves, so that their descendants can pick up the symbols that
they generate. There is no reason at all why this could not be
implemented; early on in the development I did just this, although I
think that it would now be easier to modify this patch.

One huge advantage of proceeding in this way is that any resulting
library can be distributed with the .mod file alone so that the
private entities are never exposed. The penalty is that a second file
is output.

With best regards

Paul

On 23 July 2015 at 17:42, Mikael Morin <mikael.morin@sfr.fr> wrote:
> Hello Paul,
>
> Le 23/07/2015 09:46, Paul Richard Thomas a écrit :
>>
>> Since all the private entities in a module have to be transmitted to
>> their descendant submodules, whilst keeping them hidden from normal
>> use statements, I have chosen to write the module file as usual and
>> add a second part that contains the private entities. This latter is
>> only read when processing submodule statements.
>>
> why not write them to the/a .smod file?  It was its primary purpose, wasn't
> it?
> [Sorry, I followed the submodule stuff very remotely].
>
> It's probably bad practice to put private entities in module files, at least
> now that submodules are supported.  Nevertheless with your change,
> modifications made to private entities produce recompilation cascades, even
> though the public interfaces are left unchanged.
>
> Mikael



-- 
Outside of a dog, a book is a man's best friend. Inside of a dog it's
too dark to read.

Groucho Marx

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-07-24  8:08   ` Paul Richard Thomas
@ 2015-07-24  8:09     ` Damian Rouson
  2015-07-24 12:10       ` Paul Richard Thomas
  2015-07-29 15:32       ` Paul Richard Thomas
  0 siblings, 2 replies; 23+ messages in thread
From: Damian Rouson @ 2015-07-24  8:09 UTC (permalink / raw)
  To: Paul Richard Thomas
  Cc: Mikael Morin, Bader, Reinhold, fortran, gcc-patches, salvatore.filippone

I love this idea and had similar thoughts as well.  

:D 

Sent from my iPhone

> On Jul 24, 2015, at 1:06 AM, Paul Richard Thomas <paul.richard.thomas@gmail.com> wrote:
> 
> Dear Mikael,
> 
> It had crossed my mind also that a .mod and a .smod file could be
> written. Normally, the .smod files are produced by the submodules
> themselves, so that their descendants can pick up the symbols that
> they generate. There is no reason at all why this could not be
> implemented; early on in the development I did just this, although I
> think that it would now be easier to modify this patch.
> 
> One huge advantage of proceeding in this way is that any resulting
> library can be distributed with the .mod file alone so that the
> private entities are never exposed. The penalty is that a second file
> is output.
> 
> With best regards
> 
> Paul
> 
>> On 23 July 2015 at 17:42, Mikael Morin <mikael.morin@sfr.fr> wrote:
>> Hello Paul,
>> 
>> Le 23/07/2015 09:46, Paul Richard Thomas a écrit :
>>> 
>>> Since all the private entities in a module have to be transmitted to
>>> their descendant submodules, whilst keeping them hidden from normal
>>> use statements, I have chosen to write the module file as usual and
>>> add a second part that contains the private entities. This latter is
>>> only read when processing submodule statements.
>> why not write them to the/a .smod file?  It was its primary purpose, wasn't
>> it?
>> [Sorry, I followed the submodule stuff very remotely].
>> 
>> It's probably bad practice to put private entities in module files, at least
>> now that submodules are supported.  Nevertheless with your change,
>> modifications made to private entities produce recompilation cascades, even
>> though the public interfaces are left unchanged.
>> 
>> Mikael
> 
> 
> 
> -- 
> Outside of a dog, a book is a man's best friend. Inside of a dog it's
> too dark to read.
> 
> Groucho Marx

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-07-24  8:09     ` Damian Rouson
@ 2015-07-24 12:10       ` Paul Richard Thomas
  2015-07-29 15:32       ` Paul Richard Thomas
  1 sibling, 0 replies; 23+ messages in thread
From: Paul Richard Thomas @ 2015-07-24 12:10 UTC (permalink / raw)
  To: Damian Rouson
  Cc: Mikael Morin, Bader, Reinhold, fortran, gcc-patches, salvatore.filippone

Dear All,

In the words of Jean-Luc Picard, "I will make it so.... "

Paul

On 24 July 2015 at 10:08, Damian Rouson <damian@sourceryinstitute.org> wrote:
> I love this idea and had similar thoughts as well.
>
> :D
>
> Sent from my iPhone
>
>> On Jul 24, 2015, at 1:06 AM, Paul Richard Thomas <paul.richard.thomas@gmail.com> wrote:
>>
>> Dear Mikael,
>>
>> It had crossed my mind also that a .mod and a .smod file could be
>> written. Normally, the .smod files are produced by the submodules
>> themselves, so that their descendants can pick up the symbols that
>> they generate. There is no reason at all why this could not be
>> implemented; early on in the development I did just this, although I
>> think that it would now be easier to modify this patch.
>>
>> One huge advantage of proceeding in this way is that any resulting
>> library can be distributed with the .mod file alone so that the
>> private entities are never exposed. The penalty is that a second file
>> is output.
>>
>> With best regards
>>
>> Paul
>>
>>> On 23 July 2015 at 17:42, Mikael Morin <mikael.morin@sfr.fr> wrote:
>>> Hello Paul,
>>>
>>> Le 23/07/2015 09:46, Paul Richard Thomas a écrit :
>>>>
>>>> Since all the private entities in a module have to be transmitted to
>>>> their descendant submodules, whilst keeping them hidden from normal
>>>> use statements, I have chosen to write the module file as usual and
>>>> add a second part that contains the private entities. This latter is
>>>> only read when processing submodule statements.
>>> why not write them to the/a .smod file?  It was its primary purpose, wasn't
>>> it?
>>> [Sorry, I followed the submodule stuff very remotely].
>>>
>>> It's probably bad practice to put private entities in module files, at least
>>> now that submodules are supported.  Nevertheless with your change,
>>> modifications made to private entities produce recompilation cascades, even
>>> though the public interfaces are left unchanged.
>>>
>>> Mikael
>>
>>
>>
>> --
>> Outside of a dog, a book is a man's best friend. Inside of a dog it's
>> too dark to read.
>>
>> Groucho Marx



-- 
Outside of a dog, a book is a man's best friend. Inside of a dog it's
too dark to read.

Groucho Marx

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-07-24  8:09     ` Damian Rouson
  2015-07-24 12:10       ` Paul Richard Thomas
@ 2015-07-29 15:32       ` Paul Richard Thomas
  2015-07-29 15:36         ` Marek Polacek
  2015-08-03 10:45         ` Mikael Morin
  1 sibling, 2 replies; 23+ messages in thread
From: Paul Richard Thomas @ 2015-07-29 15:32 UTC (permalink / raw)
  To: Damian Rouson
  Cc: Mikael Morin, Bader, Reinhold, fortran, gcc-patches, salvatore.filippone

[-- Attachment #1: Type: text/plain, Size: 2566 bytes --]

Dear All,

On 24 July 2015 at 10:08, Damian Rouson <damian@sourceryinstitute.org> wrote:
> I love this idea and had similar thoughts as well.
>
> :D
>
> Sent from my iPhone
>
>> On Jul 24, 2015, at 1:06 AM, Paul Richard Thomas <paul.richard.thomas@gmail.com> wrote:
>>
>> Dear Mikael,
>>
>> It had crossed my mind also that a .mod and a .smod file could be
>> written. Normally, the .smod files are produced by the submodules
>> themselves, so that their descendants can pick up the symbols that
>> they generate. There is no reason at all why this could not be
>> implemented; early on in the development I did just this, although I
>> think that it would now be easier to modify this patch.
>>
>> One huge advantage of proceeding in this way is that any resulting
>> library can be distributed with the .mod file alone so that the
>> private entities are never exposed. The penalty is that a second file
>> is output.
>>
>> With best regards
>>
>> Paul
>>

Please find attached the implementation of this suggestion.

Bootstraps and regtests on FC21/x86_64 - OK for trunk or is the
original preferred?

Cheers

Paul

2015-07-29  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/52846
    * module.c (check_access): Return true if new static flag
    'dump_smod' is true..
    (gfc_dump_module): Rename original 'dump_module' and call from
    new version. Use 'dump_smod' rather than the stack state to
    determine if a submodule is being processed. The new version of
    this procedure sets 'dump_smod' depending on the stack state and
    then writes both the mod and smod files if a module is being
    processed or just the smod for a submodule.
    (gfc_use_module): Eliminate the check for module_name and
    submodule_name being the same.
    * trans-decl.c (gfc_finish_var_decl, gfc_build_qualified_array,
    get_proc_pointer_decl): Set TREE_PUBLIC unconditionally and use
    the conditions to set DECL_VISIBILITY as hidden and to set as
    true DECL_VISIBILITY_SPECIFIED.

2015-07-29  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/52846

    * lib/fortran-modules.exp: Call cleanup-submodules from
    cleanup-modules.
    * gfortran.dg/public_private_module_2.f90: Add two XFAILS to
    cover the cases where private entities are no longer optimized
    away.
    * gfortran.dg/public_private_module_6.f90: Add an XFAIL for the
    same reason.
    * gfortran.dg/submodule_1.f08: Change cleanup module names.
    * gfortran.dg/submodule_5.f08: The same.
    * gfortran.dg/submodule_9.f08: The same.
    * gfortran.dg/submodule_10.f08: New test

[-- Attachment #2: private-alternative.diff --]
[-- Type: text/plain, Size: 15882 bytes --]

Index: gcc/fortran/module.c
===================================================================
*** gcc/fortran/module.c	(revision 226054)
--- gcc/fortran/module.c	(working copy)
*************** read_module (void)
*** 5283,5291 ****
--- 5283,5296 ----
     PRIVATE, then private, and otherwise it is public unless the default
     access in this context has been declared PRIVATE.  */

+ static bool dump_smod = false;
+
  static bool
  check_access (gfc_access specific_access, gfc_access default_access)
  {
+   if (dump_smod)
+     return true;
+
    if (specific_access == ACCESS_PUBLIC)
      return TRUE;
    if (specific_access == ACCESS_PRIVATE)
*************** read_crc32_from_module_file (const char*
*** 5961,5968 ****
     processing the module, dump_flag will be set to zero and we delete
     the module file, even if it was already there.  */

! void
! gfc_dump_module (const char *name, int dump_flag)
  {
    int n;
    char *filename, *filename_tmp;
--- 5966,5973 ----
     processing the module, dump_flag will be set to zero and we delete
     the module file, even if it was already there.  */

! static void
! dump_module (const char *name, int dump_flag)
  {
    int n;
    char *filename, *filename_tmp;
*************** gfc_dump_module (const char *name, int d
*** 5970,5976 ****

    module_name = gfc_get_string (name);

!   if (gfc_state_stack->state == COMP_SUBMODULE)
      {
        name = submodule_name;
        n = strlen (name) + strlen (SUBMODULE_EXTENSION) + 1;
--- 5975,5981 ----

    module_name = gfc_get_string (name);

!   if (dump_smod)
      {
        name = submodule_name;
        n = strlen (name) + strlen (SUBMODULE_EXTENSION) + 1;
*************** gfc_dump_module (const char *name, int d
*** 5991,5997 ****
        strcpy (filename, name);
      }

!   if (gfc_state_stack->state == COMP_SUBMODULE)
      strcat (filename, SUBMODULE_EXTENSION);
    else
    strcat (filename, MODULE_EXTENSION);
--- 5996,6002 ----
        strcpy (filename, name);
      }

!   if (dump_smod)
      strcat (filename, SUBMODULE_EXTENSION);
    else
    strcat (filename, MODULE_EXTENSION);
*************** gfc_dump_module (const char *name, int d
*** 6060,6065 ****
--- 6065,6091 ----
  }


+ void
+ gfc_dump_module (const char *name, int dump_flag)
+ {
+   if (gfc_state_stack->state == COMP_SUBMODULE)
+     dump_smod = true;
+   else
+     dump_smod =false;
+
+   dump_module (name, dump_flag);
+
+   if (dump_smod)
+     return;
+
+   /* Write a submodule file from a module.  The 'dump_smod' flag switches
+      off the check for PRIVATE entities.  */
+   dump_smod = true;
+   submodule_name = module_name;
+   dump_module (name, dump_flag);
+   dump_smod = false;
+ }
+
  static void
  create_intrinsic_function (const char *name, int id,
  			   const char *modname, intmod_id module,
*************** gfc_use_module (gfc_use_list *module)
*** 6754,6761 ****
  		     "USE statement at %C has no ONLY qualifier");

    if (gfc_state_stack->state == COMP_MODULE
!       || module->submodule_name == NULL
!       || strcmp (module_name, module->submodule_name) == 0)
      {
        filename = XALLOCAVEC (char, strlen (module_name)
  				   + strlen (MODULE_EXTENSION) + 1);
--- 6780,6786 ----
  		     "USE statement at %C has no ONLY qualifier");

    if (gfc_state_stack->state == COMP_MODULE
!       || module->submodule_name == NULL)
      {
        filename = XALLOCAVEC (char, strlen (module_name)
  				   + strlen (MODULE_EXTENSION) + 1);
Index: gcc/fortran/trans-decl.c
===================================================================
*** gcc/fortran/trans-decl.c	(revision 226054)
--- gcc/fortran/trans-decl.c	(working copy)
*************** gfc_finish_var_decl (tree decl, gfc_symb
*** 596,601 ****
--- 596,606 ----
  	 both, of course.) (J3/04-007, section 15.3).  */
        TREE_PUBLIC(decl) = 1;
        DECL_COMMON(decl) = 1;
+       if (sym->attr.access == ACCESS_PRIVATE && !sym->attr.public_used)
+ 	{
+ 	  DECL_VISIBILITY (decl) = VISIBILITY_HIDDEN;
+ 	  DECL_VISIBILITY_SPECIFIED (decl) = true;
+ 	}
      }

    /* If a variable is USE associated, it's always external.  */
*************** gfc_finish_var_decl (tree decl, gfc_symb
*** 609,617 ****
        /* TODO: Don't set sym->module for result or dummy variables.  */
        gcc_assert (current_function_decl == NULL_TREE || sym->result == sym);

-       if (sym->attr.access != ACCESS_PRIVATE || sym->attr.public_used)
  	TREE_PUBLIC (decl) = 1;
        TREE_STATIC (decl) = 1;
      }

    /* Derived types are a bit peculiar because of the possibility of
--- 614,626 ----
        /* TODO: Don't set sym->module for result or dummy variables.  */
        gcc_assert (current_function_decl == NULL_TREE || sym->result == sym);

        TREE_PUBLIC (decl) = 1;
        TREE_STATIC (decl) = 1;
+       if (sym->attr.access == ACCESS_PRIVATE && !sym->attr.public_used)
+ 	{
+ 	  DECL_VISIBILITY (decl) = VISIBILITY_HIDDEN;
+ 	  DECL_VISIBILITY_SPECIFIED (decl) = true;
+ 	}
      }

    /* Derived types are a bit peculiar because of the possibility of
*************** gfc_build_qualified_array (tree decl, gf
*** 837,845 ****
  	  else
  	    TREE_STATIC (token) = 1;

- 	  if (sym->attr.use_assoc || sym->attr.access != ACCESS_PRIVATE ||
- 	      sym->attr.public_used)
  	    TREE_PUBLIC (token) = 1;
  	}
        else
  	{
--- 846,858 ----
  	  else
  	    TREE_STATIC (token) = 1;

  	  TREE_PUBLIC (token) = 1;
+
+ 	  if (sym->attr.access == ACCESS_PRIVATE && !sym->attr.public_used)
+ 	    {
+ 	      DECL_VISIBILITY (token) = VISIBILITY_HIDDEN;
+ 	      DECL_VISIBILITY_SPECIFIED (token) = true;
+ 	    }
  	}
        else
  	{
*************** get_proc_pointer_decl (gfc_symbol *sym)
*** 1747,1755 ****
    else if (sym->module && sym->ns->proc_name->attr.flavor == FL_MODULE)
      {
        /* This is the declaration of a module variable.  */
-       if (sym->ns->proc_name->attr.flavor == FL_MODULE
- 	  && (sym->attr.access != ACCESS_PRIVATE || sym->attr.public_used))
  	TREE_PUBLIC (decl) = 1;
        TREE_STATIC (decl) = 1;
      }

--- 1760,1771 ----
    else if (sym->module && sym->ns->proc_name->attr.flavor == FL_MODULE)
      {
        /* This is the declaration of a module variable.  */
        TREE_PUBLIC (decl) = 1;
+       if (sym->attr.access == ACCESS_PRIVATE && !sym->attr.public_used)
+ 	{
+ 	  DECL_VISIBILITY (decl) = VISIBILITY_HIDDEN;
+ 	  DECL_VISIBILITY_SPECIFIED (decl) = true;
+ 	}
        TREE_STATIC (decl) = 1;
      }

Index: gcc/testsuite/lib/fortran-modules.exp
===================================================================
*** gcc/testsuite/lib/fortran-modules.exp	(revision 226054)
--- gcc/testsuite/lib/fortran-modules.exp	(working copy)
***************
*** 17,22 ****
--- 17,23 ----
  # helper to deal with fortran modules

  # Remove files for specified Fortran modules.
+ # This includes both .mod and .smod files.
  proc cleanup-modules { modlist } {
      global clean
      foreach mod [concat $modlist $clean] {
*************** proc cleanup-modules { modlist } {
*** 27,32 ****
--- 28,34 ----
  	}
  	remote_file build delete $m
      }
+     cleanup-submodules $modlist
  }

  # Remove files for specified Fortran submodules.
Index: gcc/testsuite/gfortran.dg/public_private_module_2.f90
===================================================================
*** gcc/testsuite/gfortran.dg/public_private_module_2.f90	(revision 226054)
--- gcc/testsuite/gfortran.dg/public_private_module_2.f90	(working copy)
***************
*** 18,29 ****
          integer, bind(C,name='') :: qq
        end module mod

        ! { dg-final { scan-assembler "__mod_MOD_aa" } }
!       ! { dg-final { scan-assembler-not "iii" } }
        ! { dg-final { scan-assembler "jj" } }
        ! { dg-final { scan-assembler "lll" } }
        ! { dg-final { scan-assembler-not "kk" } }
!       ! { dg-final { scan-assembler-not "mmmm" } }
        ! { dg-final { scan-assembler "nnn" } }
        ! { dg-final { scan-assembler "oo" } }
        ! { dg-final { scan-assembler "__mod_MOD_qq" } }
--- 18,32 ----
          integer, bind(C,name='') :: qq
        end module mod

+ ! The two xfails below have appeared with the introduction of submodules. 'iii' and
+ ! 'mmm' now are TREE_PUBLIC but has DECL_VISIBILITY (decl) = VISIBILITY_HIDDEN set.
+
        ! { dg-final { scan-assembler "__mod_MOD_aa" } }
!       ! { dg-final { scan-assembler-not "iii" { xfail *-*-* } } }
        ! { dg-final { scan-assembler "jj" } }
        ! { dg-final { scan-assembler "lll" } }
        ! { dg-final { scan-assembler-not "kk" } }
!       ! { dg-final { scan-assembler-not "mmmm" { xfail *-*-* } } }
        ! { dg-final { scan-assembler "nnn" } }
        ! { dg-final { scan-assembler "oo" } }
        ! { dg-final { scan-assembler "__mod_MOD_qq" } }
Index: gcc/testsuite/gfortran.dg/public_private_module_6.f90
===================================================================
*** gcc/testsuite/gfortran.dg/public_private_module_6.f90	(revision 226054)
--- gcc/testsuite/gfortran.dg/public_private_module_6.f90	(working copy)
*************** module m
*** 11,14 ****
    integer, save :: aaaa
  end module m

! ! { dg-final { scan-assembler-not "aaaa" } }
--- 11,17 ----
    integer, save :: aaaa
  end module m

! ! The xfail below has appeared with the introduction of submodules. 'aaaa'
! ! now is TREE_PUBLIC but has DECL_VISIBILITY (decl) = VISIBILITY_HIDDEN set.
!
! ! { dg-final { scan-assembler-not "aaaa" { xfail *-*-* } } }
Index: gcc/testsuite/gfortran.dg/submodule_1.f08
===================================================================
*** gcc/testsuite/gfortran.dg/submodule_1.f08	(revision 226054)
--- gcc/testsuite/gfortran.dg/submodule_1.f08	(working copy)
***************
*** 170,175 ****
       message2 = ""
     end subroutine
   end program
! ! { dg-final { cleanup-submodules "foo_interface_son" } }
! ! { dg-final { cleanup-submodules "foo_interface_grandson" } }
! ! { dg-final { cleanup-submodules "foo_interface_daughter" } }
--- 170,175 ----
       message2 = ""
     end subroutine
   end program
! ! { dg-final { cleanup-submodules "foo_interface@foo_interface_son" } }
! ! { dg-final { cleanup-submodules "foo_interface@foo_interface_grandson" } }
! ! { dg-final { cleanup-submodules "foo_interface@foo_interface_daughter" } }
Index: gcc/testsuite/gfortran.dg/submodule_10.f08
===================================================================
*** gcc/testsuite/gfortran.dg/submodule_10.f08	(revision 0)
--- gcc/testsuite/gfortran.dg/submodule_10.f08	(working copy)
***************
*** 0 ****
--- 1,170 ----
+ ! { dg-do compile }
+ !
+ ! Checks that PRIVATE enities are visible to submodules.
+ !
+ ! Contributed by Salvatore Filippone  <salvatore.filippone@uniroma2.it>
+ !
+ module const_mod
+   integer, parameter  :: ndig=8
+   integer, parameter  :: ipk_ = selected_int_kind(ndig)
+   integer, parameter  :: longndig=12
+   integer, parameter  :: long_int_k_ = selected_int_kind(longndig)
+   integer, parameter  :: mpik_ = kind(1)
+
+   integer(ipk_), parameter, public :: success_=0
+
+ end module const_mod
+
+
+ module error_mod
+   use const_mod
+
+   integer(ipk_), parameter, public :: act_ret_=0
+   integer(ipk_), parameter, public :: act_print_=1
+   integer(ipk_), parameter, public :: act_abort_=2
+
+   integer(ipk_), parameter, public ::  no_err_ = 0
+
+   public error, errcomm, get_numerr, &
+        & error_handler, &
+        & ser_error_handler, par_error_handler
+
+
+   interface error_handler
+     module subroutine ser_error_handler(err_act)
+       integer(ipk_), intent(inout) ::  err_act
+     end subroutine ser_error_handler
+     module subroutine par_error_handler(ictxt,err_act)
+       integer(mpik_), intent(in) ::  ictxt
+       integer(ipk_), intent(in) ::  err_act
+     end subroutine par_error_handler
+   end interface
+
+   interface error
+     module subroutine serror()
+     end subroutine serror
+     module subroutine perror(ictxt,abrt)
+       integer(mpik_), intent(in) ::  ictxt
+       logical, intent(in), optional  :: abrt
+     end subroutine perror
+   end interface
+
+
+   interface error_print_stack
+     module subroutine par_error_print_stack(ictxt)
+       integer(mpik_), intent(in) ::  ictxt
+     end subroutine par_error_print_stack
+     module subroutine ser_error_print_stack()
+     end subroutine ser_error_print_stack
+   end interface
+
+   interface errcomm
+     module subroutine errcomm(ictxt, err)
+       integer(mpik_), intent(in)   :: ictxt
+       integer(ipk_), intent(inout):: err
+     end subroutine errcomm
+   end interface errcomm
+
+
+   private
+
+   type errstack_node
+
+     integer(ipk_) ::   err_code=0
+     character(len=20)        ::   routine=''
+     integer(ipk_),dimension(5)     ::   i_err_data=0
+     character(len=40)        ::   a_err_data=''
+     type(errstack_node), pointer :: next
+
+   end type errstack_node
+
+
+   type errstack
+     type(errstack_node), pointer :: top => null()
+     integer(ipk_) :: n_elems=0
+   end type errstack
+
+
+   type(errstack), save  :: error_stack
+   integer(ipk_), save   :: error_status    = no_err_
+   integer(ipk_), save   :: verbosity_level = 1
+   integer(ipk_), save   :: err_action      = act_abort_
+   integer(ipk_), save   :: debug_level     = 0, debug_unit, serial_debug_level=0
+
+ contains
+ end module error_mod
+
+ submodule (error_mod) error_impl_mod
+   use const_mod
+ contains
+   ! checks whether an error has occurred on one of the processes in the execution pool
+   subroutine errcomm(ictxt, err)
+     integer(mpik_), intent(in)   :: ictxt
+     integer(ipk_), intent(inout):: err
+
+
+   end subroutine errcomm
+
+   subroutine ser_error_handler(err_act)
+     implicit none
+     integer(ipk_), intent(inout) ::  err_act
+
+     if (err_act /= act_ret_)     &
+          &  call error()
+     if (err_act == act_abort_) stop
+
+     return
+   end subroutine ser_error_handler
+
+   subroutine par_error_handler(ictxt,err_act)
+     implicit none
+     integer(mpik_), intent(in) ::  ictxt
+     integer(ipk_), intent(in) ::  err_act
+
+     if (err_act == act_print_)     &
+          &  call error(ictxt, abrt=.false.)
+     if (err_act == act_abort_)      &
+          &  call error(ictxt, abrt=.true.)
+
+     return
+
+   end subroutine par_error_handler
+
+   subroutine par_error_print_stack(ictxt)
+     integer(mpik_), intent(in) ::  ictxt
+
+     call error(ictxt, abrt=.false.)
+
+   end subroutine par_error_print_stack
+
+   subroutine ser_error_print_stack()
+
+     call error()
+   end subroutine ser_error_print_stack
+
+   subroutine serror()
+
+     implicit none
+
+   end subroutine serror
+
+   subroutine perror(ictxt,abrt)
+     use const_mod
+     implicit none
+     integer(mpik_), intent(in) :: ictxt
+     logical, intent(in), optional  :: abrt
+
+   end subroutine perror
+
+ end submodule error_impl_mod
+
+ program testlk
+   use error_mod
+   implicit none
+
+   call error()
+
+   stop
+ end program testlk
+ ! { dg-final { cleanup-submodules "error_mod@error_impl_mod" } }
+
Index: gcc/testsuite/gfortran.dg/submodule_5.f08
===================================================================
*** gcc/testsuite/gfortran.dg/submodule_5.f08	(revision 226054)
--- gcc/testsuite/gfortran.dg/submodule_5.f08	(working copy)
*************** contains
*** 49,51 ****
--- 49,52 ----
  end SUBMODULE foo_interface_daughter

  end
+ ! { dg-final { cleanup-submodules "foo_interface@foo_interface_daughter" } }
Index: gcc/testsuite/gfortran.dg/submodule_9.f08
===================================================================
*** gcc/testsuite/gfortran.dg/submodule_9.f08	(revision 226054)
--- gcc/testsuite/gfortran.dg/submodule_9.f08	(working copy)
*************** program a_s
*** 38,40 ****
--- 38,41 ----
    implicit none
    call p()
  end program
+ ! { dg-final { cleanup-submodules "mod_a@b" } }

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-07-29 15:32       ` Paul Richard Thomas
@ 2015-07-29 15:36         ` Marek Polacek
  2015-07-29 16:15           ` FX
  2015-08-03 10:45         ` Mikael Morin
  1 sibling, 1 reply; 23+ messages in thread
From: Marek Polacek @ 2015-07-29 15:36 UTC (permalink / raw)
  To: Paul Richard Thomas
  Cc: Damian Rouson, Mikael Morin, Bader, Reinhold, fortran,
	gcc-patches, salvatore.filippone

On Wed, Jul 29, 2015 at 05:08:19PM +0200, Paul Richard Thomas wrote:
> Index: gcc/fortran/module.c
> ===================================================================
> *** gcc/fortran/module.c	(revision 226054)
> --- gcc/fortran/module.c	(working copy)
> *************** read_module (void)
> *** 5283,5291 ****
> --- 5283,5296 ----
>      PRIVATE, then private, and otherwise it is public unless the default
>      access in this context has been declared PRIVATE.  */
> 
> + static bool dump_smod = false;

Why do you initialize a static variable to false?

	Marek

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-07-29 15:36         ` Marek Polacek
@ 2015-07-29 16:15           ` FX
  2015-07-29 16:25             ` Marek Polacek
  2015-07-29 16:45             ` Paul Richard Thomas
  0 siblings, 2 replies; 23+ messages in thread
From: FX @ 2015-07-29 16:15 UTC (permalink / raw)
  To: Marek Polacek
  Cc: Paul Richard Thomas, Damian Rouson, Mikael Morin, Bader,
	Reinhold, fortran, gcc-patches, salvatore.filippone

> Why do you initialize a static variable to false?

You mean because false is equal to zero and it will be the default initialization anyway?
I quite like that the default value is explicit.

FX

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-07-29 16:15           ` FX
@ 2015-07-29 16:25             ` Marek Polacek
  2015-07-29 16:45             ` Paul Richard Thomas
  1 sibling, 0 replies; 23+ messages in thread
From: Marek Polacek @ 2015-07-29 16:25 UTC (permalink / raw)
  To: FX
  Cc: Paul Richard Thomas, Damian Rouson, Mikael Morin, Bader,
	Reinhold, fortran, gcc-patches, salvatore.filippone

On Wed, Jul 29, 2015 at 05:31:57PM +0200, FX wrote:
> > Why do you initialize a static variable to false?
> 
> You mean because false is equal to zero and it will be the default initialization anyway?

Yes.

> I quite like that the default value is explicit.

Ok then. 

	Marek

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-07-29 16:15           ` FX
  2015-07-29 16:25             ` Marek Polacek
@ 2015-07-29 16:45             ` Paul Richard Thomas
  1 sibling, 0 replies; 23+ messages in thread
From: Paul Richard Thomas @ 2015-07-29 16:45 UTC (permalink / raw)
  To: FX
  Cc: Marek Polacek, Damian Rouson, Mikael Morin, Bader, Reinhold,
	fortran, gcc-patches, salvatore.filippone

Dear All,

My reply is the same as FX's. However, I am perfectly happy to
eliminate the initialization. The correct state is ensured by
gfc_dump_module.

Cheers

Paul

On 29 July 2015 at 17:31, FX <fxcoudert@gmail.com> wrote:
>> Why do you initialize a static variable to false?
>
> You mean because false is equal to zero and it will be the default initialization anyway?
> I quite like that the default value is explicit.
>
> FX



-- 
Outside of a dog, a book is a man's best friend. Inside of a dog it's
too dark to read.

Groucho Marx

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-07-29 15:32       ` Paul Richard Thomas
  2015-07-29 15:36         ` Marek Polacek
@ 2015-08-03 10:45         ` Mikael Morin
  2015-08-03 12:36           ` Paul Richard Thomas
  1 sibling, 1 reply; 23+ messages in thread
From: Mikael Morin @ 2015-08-03 10:45 UTC (permalink / raw)
  To: Paul Richard Thomas, Damian Rouson
  Cc: Bader, Reinhold, fortran, gcc-patches, salvatore.filippone

Le 29/07/2015 17:08, Paul Richard Thomas a écrit :
> Dear All,
>
> On 24 July 2015 at 10:08, Damian Rouson <damian@sourceryinstitute.org> wrote:
>> I love this idea and had similar thoughts as well.
>>
>> :D
>>
>> Sent from my iPhone
>>
>>> On Jul 24, 2015, at 1:06 AM, Paul Richard Thomas <paul.richard.thomas@gmail.com> wrote:
>>>
>>> Dear Mikael,
>>>
>>> It had crossed my mind also that a .mod and a .smod file could be
>>> written. Normally, the .smod files are produced by the submodules
>>> themselves, so that their descendants can pick up the symbols that
>>> they generate. There is no reason at all why this could not be
>>> implemented; early on in the development I did just this, although I
>>> think that it would now be easier to modify this patch.
>>>
>>> One huge advantage of proceeding in this way is that any resulting
>>> library can be distributed with the .mod file alone so that the
>>> private entities are never exposed. The penalty is that a second file
>>> is output.
>>>
>>> With best regards
>>>
>>> Paul
>>>
>
> Please find attached the implementation of this suggestion.
>
> Bootstraps and regtests on FC21/x86_64 - OK for trunk or is the
> original preferred?
>
There hasn't been a lot of voices about this among the other active and 
less active team members.
I prefer this "private members to separate smod" variant.
It's OK for trunk as far as I'm concerned.
Thanks.

Mikael

PS: Regarding redundant initializations: rather have too many than too 
few. ;-)

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-08-03 10:45         ` Mikael Morin
@ 2015-08-03 12:36           ` Paul Richard Thomas
  2015-08-03 15:40             ` Mikael Morin
  2015-08-10 18:09             ` Toon Moene
  0 siblings, 2 replies; 23+ messages in thread
From: Paul Richard Thomas @ 2015-08-03 12:36 UTC (permalink / raw)
  To: Mikael Morin
  Cc: Damian Rouson, Bader, Reinhold, fortran, gcc-patches,
	salvatore.filippone

Dear Mikael,

Thanks for your green light!

I have been mulling over the trans-decl part of the patch and having
been wondering if it is necessary. Without optimization, private
entities can be linked to. Given the discussion concerning the
combination of submodules and private entities, I wonder if this is
not sufficient? Within submodule scope, an advisory could be given for
undefined references to suggest recompiling the module without
optimization or making the entities public.

Cheers

Paul

On 3 August 2015 at 12:44, Mikael Morin <mikael.morin@sfr.fr> wrote:
> Le 29/07/2015 17:08, Paul Richard Thomas a écrit :
>>
>> Dear All,
>>
>> On 24 July 2015 at 10:08, Damian Rouson <damian@sourceryinstitute.org>
>> wrote:
>>>
>>> I love this idea and had similar thoughts as well.
>>>
>>> :D
>>>
>>> Sent from my iPhone
>>>
>>>> On Jul 24, 2015, at 1:06 AM, Paul Richard Thomas
>>>> <paul.richard.thomas@gmail.com> wrote:
>>>>
>>>> Dear Mikael,
>>>>
>>>> It had crossed my mind also that a .mod and a .smod file could be
>>>> written. Normally, the .smod files are produced by the submodules
>>>> themselves, so that their descendants can pick up the symbols that
>>>> they generate. There is no reason at all why this could not be
>>>> implemented; early on in the development I did just this, although I
>>>> think that it would now be easier to modify this patch.
>>>>
>>>> One huge advantage of proceeding in this way is that any resulting
>>>> library can be distributed with the .mod file alone so that the
>>>> private entities are never exposed. The penalty is that a second file
>>>> is output.
>>>>
>>>> With best regards
>>>>
>>>> Paul
>>>>
>>
>> Please find attached the implementation of this suggestion.
>>
>> Bootstraps and regtests on FC21/x86_64 - OK for trunk or is the
>> original preferred?
>>
> There hasn't been a lot of voices about this among the other active and less
> active team members.
> I prefer this "private members to separate smod" variant.
> It's OK for trunk as far as I'm concerned.
> Thanks.
>
> Mikael
>
> PS: Regarding redundant initializations: rather have too many than too few.
> ;-)



-- 
Outside of a dog, a book is a man's best friend. Inside of a dog it's
too dark to read.

Groucho Marx

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-08-03 12:36           ` Paul Richard Thomas
@ 2015-08-03 15:40             ` Mikael Morin
  2015-08-04  9:40               ` Paul Richard Thomas
  2015-08-10 18:09             ` Toon Moene
  1 sibling, 1 reply; 23+ messages in thread
From: Mikael Morin @ 2015-08-03 15:40 UTC (permalink / raw)
  To: Paul Richard Thomas
  Cc: Damian Rouson, Bader, Reinhold, fortran, gcc-patches,
	salvatore.filippone

Le 03/08/2015 14:36, Paul Richard Thomas a écrit :
> Dear Mikael,
>
> Thanks for your green light!
>
> I have been mulling over the trans-decl part of the patch and having
> been wondering if it is necessary.
You mean marking entities as public?  Or setting the hidden visibility 
attribute?  Or both?
I think both are necessary.

> Without optimization, private
> entities can be linked to. Given the discussion concerning the
> combination of submodules and private entities, I wonder if this is
> not sufficient? Within submodule scope, an advisory could be given for
> undefined references to suggest recompiling the module without
> optimization or making the entities public.
>
About recompiling without optimization:
If the module contains no code, I guess that would be OK.
But otherwise, it would be pretty bad.
And one would have to do the same for submodules of a submodule: the 
parent submodule would be compiled without optimization. :-(

About making the entities public:
I think the goal of submodules is providing a way to specify a 
(hopefully) stable interface free of any internal implementation details 
that users would start playing with if the opportunity was given to 
them.  Making all entities public would go against that.


I've been reading about the hidden visibility attribute since you 
submitted the 3/3 patch(es).  I think it's the right thing. :-)

Mikael

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-08-03 15:40             ` Mikael Morin
@ 2015-08-04  9:40               ` Paul Richard Thomas
  2015-08-05 12:09                 ` Paul Richard Thomas
  0 siblings, 1 reply; 23+ messages in thread
From: Paul Richard Thomas @ 2015-08-04  9:40 UTC (permalink / raw)
  To: Mikael Morin
  Cc: Damian Rouson, Bader, Reinhold, fortran, gcc-patches,
	salvatore.filippone

Dear Mikael,

Thanks for your comments. I will commit the patch tonight. If folk get
steamed up about .smod files appearing when they compile their
favourite non-submodule-based code, I guess that we can put in a
compilation flag to suppress them. We have plenty of time to tweak
this before the release of 6 branch.

Once committed, I will get on with the documentation and updating of
gfortran wiki.

Cheers

Paul

On 3 August 2015 at 17:39, Mikael Morin <mikael.morin@sfr.fr> wrote:
> Le 03/08/2015 14:36, Paul Richard Thomas a écrit :
>>
>> Dear Mikael,
>>
>> Thanks for your green light!
>>
>> I have been mulling over the trans-decl part of the patch and having
>> been wondering if it is necessary.
>
> You mean marking entities as public?  Or setting the hidden visibility
> attribute?  Or both?
> I think both are necessary.
>
>> Without optimization, private
>> entities can be linked to. Given the discussion concerning the
>> combination of submodules and private entities, I wonder if this is
>> not sufficient? Within submodule scope, an advisory could be given for
>> undefined references to suggest recompiling the module without
>> optimization or making the entities public.
>>
> About recompiling without optimization:
> If the module contains no code, I guess that would be OK.
> But otherwise, it would be pretty bad.
> And one would have to do the same for submodules of a submodule: the parent
> submodule would be compiled without optimization. :-(
>
> About making the entities public:
> I think the goal of submodules is providing a way to specify a (hopefully)
> stable interface free of any internal implementation details that users
> would start playing with if the opportunity was given to them.  Making all
> entities public would go against that.
>
>
> I've been reading about the hidden visibility attribute since you submitted
> the 3/3 patch(es).  I think it's the right thing. :-)
>
> Mikael



-- 
Outside of a dog, a book is a man's best friend. Inside of a dog it's
too dark to read.

Groucho Marx

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-08-04  9:40               ` Paul Richard Thomas
@ 2015-08-05 12:09                 ` Paul Richard Thomas
  0 siblings, 0 replies; 23+ messages in thread
From: Paul Richard Thomas @ 2015-08-05 12:09 UTC (permalink / raw)
  To: Mikael Morin
  Cc: Damian Rouson, Bader, Reinhold, fortran, gcc-patches,
	salvatore.filippone

Dear All,

I had some unexpected regressions, which turned out to be associated
with mulling over FX's problem with intrinsic IEEE modules.

Sending        gcc/fortran/ChangeLog
Sending        gcc/fortran/module.c
Sending        gcc/fortran/trans-decl.c
Sending        gcc/testsuite/ChangeLog
Sending        gcc/testsuite/gfortran.dg/public_private_module_2.f90
Sending        gcc/testsuite/gfortran.dg/public_private_module_6.f90
Sending        gcc/testsuite/gfortran.dg/submodule_1.f08
Adding         gcc/testsuite/gfortran.dg/submodule_10.f08
Sending        gcc/testsuite/gfortran.dg/submodule_5.f08
Sending        gcc/testsuite/gfortran.dg/submodule_9.f08
Sending        gcc/testsuite/lib/fortran-modules.exp
Transmitting file data ...........
Committed revision 226622.

The final step is documentation and wiki updates.

Cheers

Paul

On 4 August 2015 at 11:40, Paul Richard Thomas
<paul.richard.thomas@gmail.com> wrote:
> Dear Mikael,
>
> Thanks for your comments. I will commit the patch tonight. If folk get
> steamed up about .smod files appearing when they compile their
> favourite non-submodule-based code, I guess that we can put in a
> compilation flag to suppress them. We have plenty of time to tweak
> this before the release of 6 branch.
>
> Once committed, I will get on with the documentation and updating of
> gfortran wiki.
>
> Cheers
>
> Paul
>
> On 3 August 2015 at 17:39, Mikael Morin <mikael.morin@sfr.fr> wrote:
>> Le 03/08/2015 14:36, Paul Richard Thomas a écrit :
>>>
>>> Dear Mikael,
>>>
>>> Thanks for your green light!
>>>
>>> I have been mulling over the trans-decl part of the patch and having
>>> been wondering if it is necessary.
>>
>> You mean marking entities as public?  Or setting the hidden visibility
>> attribute?  Or both?
>> I think both are necessary.
>>
>>> Without optimization, private
>>> entities can be linked to. Given the discussion concerning the
>>> combination of submodules and private entities, I wonder if this is
>>> not sufficient? Within submodule scope, an advisory could be given for
>>> undefined references to suggest recompiling the module without
>>> optimization or making the entities public.
>>>
>> About recompiling without optimization:
>> If the module contains no code, I guess that would be OK.
>> But otherwise, it would be pretty bad.
>> And one would have to do the same for submodules of a submodule: the parent
>> submodule would be compiled without optimization. :-(
>>
>> About making the entities public:
>> I think the goal of submodules is providing a way to specify a (hopefully)
>> stable interface free of any internal implementation details that users
>> would start playing with if the opportunity was given to them.  Making all
>> entities public would go against that.
>>
>>
>> I've been reading about the hidden visibility attribute since you submitted
>> the 3/3 patch(es).  I think it's the right thing. :-)
>>
>> Mikael
>
>
>
> --
> Outside of a dog, a book is a man's best friend. Inside of a dog it's
> too dark to read.
>
> Groucho Marx



-- 
Outside of a dog, a book is a man's best friend. Inside of a dog it's
too dark to read.

Groucho Marx

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-08-03 12:36           ` Paul Richard Thomas
  2015-08-03 15:40             ` Mikael Morin
@ 2015-08-10 18:09             ` Toon Moene
  2015-08-10 18:57               ` AW: " Bader, Reinhold
  1 sibling, 1 reply; 23+ messages in thread
From: Toon Moene @ 2015-08-10 18:09 UTC (permalink / raw)
  To: Paul Richard Thomas, Mikael Morin
  Cc: Damian Rouson, Bader, Reinhold, fortran, gcc-patches,
	salvatore.filippone

[-- Attachment #1: Type: text/plain, Size: 2793 bytes --]

On 08/03/2015 02:36 PM, Paul Richard Thomas wrote:
> Dear Mikael,
>
> Thanks for your green light!
>
> I have been mulling over the trans-decl part of the patch and having
> been wondering if it is necessary. Without optimization, private
> entities can be linked to. Given the discussion concerning the
> combination of submodules and private entities, I wonder if this is
> not sufficient? Within submodule scope, an advisory could be given for
> undefined references to suggest recompiling the module without
> optimization or making the entities public.
>
> Cheers
>
> Paul
>
> On 3 August 2015 at 12:44, Mikael Morin <mikael.morin@sfr.fr> wrote:
>> Le 29/07/2015 17:08, Paul Richard Thomas a écrit :
>>>
>>> Dear All,
>>>
>>> On 24 July 2015 at 10:08, Damian Rouson <damian@sourceryinstitute.org>
>>> wrote:
>>>>
>>>> I love this idea and had similar thoughts as well.
>>>>
>>>> :D
>>>>
>>>> Sent from my iPhone
>>>>
>>>>> On Jul 24, 2015, at 1:06 AM, Paul Richard Thomas
>>>>> <paul.richard.thomas@gmail.com> wrote:
>>>>>
>>>>> Dear Mikael,
>>>>>
>>>>> It had crossed my mind also that a .mod and a .smod file could be
>>>>> written. Normally, the .smod files are produced by the submodules
>>>>> themselves, so that their descendants can pick up the symbols that
>>>>> they generate. There is no reason at all why this could not be
>>>>> implemented; early on in the development I did just this, although I
>>>>> think that it would now be easier to modify this patch.
>>>>>
>>>>> One huge advantage of proceeding in this way is that any resulting
>>>>> library can be distributed with the .mod file alone so that the
>>>>> private entities are never exposed. The penalty is that a second file
>>>>> is output.
>>>>>
>>>>> With best regards
>>>>>
>>>>> Paul
>>>>>
>>>
>>> Please find attached the implementation of this suggestion.
>>>
>>> Bootstraps and regtests on FC21/x86_64 - OK for trunk or is the
>>> original preferred?
>>>
>> There hasn't been a lot of voices about this among the other active and less
>> active team members.
>> I prefer this "private members to separate smod" variant.
>> It's OK for trunk as far as I'm concerned.
>> Thanks.
>>
>> Mikael
>>
>> PS: Regarding redundant initializations: rather have too many than too few.
>> ;-)

Although I do not immediately know if this is relevant for *this* 
debate, J3 passed the following (attached) interpretation on submodules 
the past week (it still has to go to several mail ballots, but still), 
overwhelmingly prefering option 3:

[attached]

Kind regards,

-- 
Toon Moene - e-mail: toon@moene.org - phone: +31 346 214290
Saturnushof 14, 3738 XG  Maartensdijk, The Netherlands
At home: http://moene.org/~toon/; weather: http://moene.org/~hirlam/
Progress of GNU Fortran: http://gcc.gnu.org/wiki/GFortran#news

[-- Attachment #2: 15-208.txt --]
[-- Type: text/plain, Size: 7316 bytes --]

                                                     J3/15-208
To: J3
From: Malcolm Cohen
Subject: Interp of USE and submodules
Date: 2015 August 06


1. Introduction

Three options are provided for the answer to this interp:

Option 1: Basically what the actual text of the standard says now.
          Accessing a PROTECTED item by a USE statement will hide the
          host association, and therefore the item will be protected.

Option 2: Continue to allow a submodule to USE its ancestor, but say
          that PROTECTED has no effect in this case.

Option 3: Decide that it was a mistake to allow a submodule to access
          its ancestor module by use association, and forbid it.

2. The interpretation request

----------------------------------------------------------------------

NUMBER: F08/0128
TITLE: Is recursive USE within a submodule permitted?
KEYWORDS: SUBMODULE, USE
DEFECT TYPE: Erratum
STATUS: J3 consideration in progress

QUESTION:

Consider
  Module m1
    Real x
  End Module
  Submodule(m1) subm1
    Use m1
  End Submodule

Q1. The module m1 is referenced from within one of its own
    submodules.  Is this standard-conforming?

Note that the "submodule TR", Technical Report 19767 contains, an edit
with the normative requirement:
  "A submodule shall not reference its ancestor module by use
   association, either directly or indirectly."
along with a note which says
  "It is possible for submodules with different ancestor modules to
   access each other's ancestor modules by use association."
It also contains an edit to insert the direct reference prohibition
as a constraint.

However, none of this text appears in ISO/IEC 1539-1:2010.

The Introduction simply comments that submodules are available, but
not that they have been extended beyond the Technical Report that
created them.

Also, consider

  Module m2
    Real, Private :: a
    Real, Protected :: b
    ...
  End Module
  Submodule(m2) subm2
  Contains
    Subroutine s
      Use m2
      Implicit None
      a = 3
      b = 4
    End Subroutine
  End Submodule

In submodule SUBM2, procedure S references M2 by use association.
Use association does not make "A" accessible.

Q2. Is "A" still accessible by host association?

Also, procedure S attempts to assign a value to B, which is accessed
by use association, but has the PROTECTED attribute.  Normally, this
attribute prevents assignment to variables accessed by use
association.

Q3. Is the assignment to "B" standard-conforming?

DISCUSSION:

The requirement appears in the early drafts of Fortran 2008, up to
08-007r1, then it was modified by paper 08-154r1 creating a UTI
(because the modification was broken), and finally the requirement was
completely removed by paper 09-141.

ANSWER OPTION 1:

A1. Yes, the example is conforming.  An edit is supplied to add this
    extension to the Introduction, and to add normative text to clause
    11 to make this completely unambiguous.

A2. Yes, A is still accessible by host association.
    Subclause 16.5.1.4 paragraph 2 states
      "If an entity that is accessed by use association has the same
       nongeneric name as a host entity, the host entity is
       inaccessible by that name."
    This does not apply since A is not being accessed by use
    association (because it is PRIVATE), therefore A can still be
    accessed by host association.
{J3 note: no edit necessary here.}

A3. No, the assignment to B is not conforming as it violates
    constraint C551 which states
      "A nonpointer object that has the PROTECTED attribute and is
       accessed by use association shall not appear in a variable
       definition context..."
    An edit is provided to add an explanation of this.

ANSWER OPTION 2:

A1. Yes, the example is conforming.  An edit is supplied to add this
    extension to the Introduction, and to add normative text to clause
    11 to make this completely unambiguous.

A2. Yes, A is still accessible by host association.
    Subclause 16.5.1.4 paragraph 2 states
      "If an entity that is accessed by use association has the same
       nongeneric name as a host entity, the host entity is
       inaccessible by that name."
    This does not apply since A is not being accessed by use
    association (because it is PRIVATE), therefore A can still be
    accessed by host association.
{J3 note: no edit necessary here.}

A3. The assignment to B was intended to be conforming.
    An edit is provided to correct constraint C551 to permit this.

ANSWER OPTION 3:

A1. No, the example was not intended to be conforming.  Permission for
    a submodule to access its ancestor module by use associated was a
    mistake.  An edit is provided to correct this error.

A2. Moot.

A3. Moot.

EDITS OPTION 1:

[xv] Introduction, p2, first bullet,
  After "Submodules provide ... for modules."
  Insert new sentence
    "A submodule can reference its ancestor module by use
     association."

[100:12] 5.3.15 PROTECTED attribute, insert this text immediately after
         the word "descendants" (i.e. before the comma)
         "where it is accessed by host association".

[272:23] 11.2.2 The USE statement and use association, p1,
  After
    "A module shall not reference itself, either directly or
     indirectly."
  Append to paragraph
    "A submodule is permitted to reference its ancestor module by
     use association.  "

[273:2+4] Same subclause, NOTE 11.7, append
  "If a submodule accesses a PROTECTED entity from its ancestor
   module by use association, use of that entity is constrained by
   the PROTECTED attribute, e.g. if it is not a pointer it cannot
   appear in a variable definition context.".

EDITS OPTION 2:

[xv] Introduction, p2, first bullet,
  After "Submodules provide ... for modules."
  Insert new sentence
    "A submodule can reference its ancestor module by use
     association."

[100:6] 5.3.15 PROTECTED attribute, C551,
  After "and is accessed by use association"
  insert "from a scoping unit that is not within a submodule
          of the module containing the definition of the
          PROTECTED entity"
{Remove PROTECTED effect from ancestor module variables.}

[100:9] same subclause, C552,
        same edit.
{Remove PROTECTED effect from ancestor module pointers.}

[272:23] 11.2.2 The USE statement and use association, p1,
  After
    "A module shall not reference itself, either directly or
     indirectly."
  Append to paragraph
    "A submodule is permitted to reference its ancestor module by
     use association.  "

EDITS OPTION 3:

[275:9+] 11.2.3 Submodules,
         "A submodule shall not reference its ancestor module by
          use association, either directly or indirectly."
{NOTE TO J3: This could be inserted at [272:23] if that is thought
 to be a better place.}

SUBMITTED BY: Malcolm Cohen

HISTORY: 15-134    m206  F08/0128 submitted
         15-134r1  m206  Revised edits - passed by J3 meeting
         15-187    m207  Failed J3 letter ballot 15-159
         15-nnn    m207  Revised with 3 options

----------------------------------------------------------------------

^ permalink raw reply	[flat|nested] 23+ messages in thread

* AW: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-08-10 18:09             ` Toon Moene
@ 2015-08-10 18:57               ` Bader, Reinhold
  2015-08-11 10:28                 ` Paul Richard Thomas
  0 siblings, 1 reply; 23+ messages in thread
From: Bader, Reinhold @ 2015-08-10 18:57 UTC (permalink / raw)
  To: Toon Moene, Paul Richard Thomas, Mikael Morin
  Cc: Damian Rouson, fortran, gcc-patches, salvatore.filippone

[-- Attachment #1: Type: text/plain, Size: 2549 bytes --]

Hello Toon, all else, 

a bit unfortunate, in my opinion (I was present at the discussion). 
I've in the meantime taken some effort to implement what the design pattern 
experts might call an "abstract factory with full dependency inversion" as 
a bare-bones framework and have attached an archive with three variants:

* pre_interp contains the code that is presently valid (and indeed compiles fine
   with both gfortran and ifort), but would become invalid due to indirect
   parent module access
* post_interp contains a variant that uses a helper module (mod_glue) to avoid
   the indirect ancestor use access (if there is a more concise way to do this, 
   I'd like to know ... up to now this is the best I can do)
* post_interp_v2 another shorter variant that pushes the extension types into a submodule
   (with the disadvantage that these types are not really reusable, and
    that the monster module problem is shifted to a monster submodule, or a chain of
    submodules)
You may need to edit the Makefiles to build. 

I would of course like to know how people feel about reintroducing this restriction, 
especially since the only reason given was that ancestor module access and its
use association overriding host association would confuse users ... which is a 
problem which in my opinion could have been dealt with in a slightly different
manner without removing the  permission for indirect parent module-referencing 
use statements. It is not clear to me whether *implementations* other than 
gfortran have problems with this, though.

More germane to this thread's discussion actually is another interp that was also passed, 
and which appears entirely uncontroversial:
http://j3-fortran.org/doc/meeting/207/15-209.txt 
It seems to me that this would permit avoiding generation of the .smod files for
modules that do not specify an separate module procedure interface.

Cheers
Reinhold
 
> -----Ursprüngliche Nachricht-----
> 
> Although I do not immediately know if this is relevant for *this*
> debate, J3 passed the following (attached) interpretation on submodules
> the past week (it still has to go to several mail ballots, but still),
> overwhelmingly prefering option 3:
> 
> [attached]
> 
> Kind regards,
> 
> --
> Toon Moene - e-mail: toon@moene.org - phone: +31 346 214290
> Saturnushof 14, 3738 XG  Maartensdijk, The Netherlands
> At home: http://moene.org/~toon/; weather: http://moene.org/~hirlam/
> Progress of GNU Fortran: http://gcc.gnu.org/wiki/GFortran#news

[-- Attachment #2: examples.tgz --]
[-- Type: application/x-compressed, Size: 1631 bytes --]

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-08-10 18:57               ` AW: " Bader, Reinhold
@ 2015-08-11 10:28                 ` Paul Richard Thomas
  2015-08-11 11:17                   ` AW: " Bader, Reinhold
  0 siblings, 1 reply; 23+ messages in thread
From: Paul Richard Thomas @ 2015-08-11 10:28 UTC (permalink / raw)
  To: Bader, Reinhold
  Cc: Toon Moene, Mikael Morin, Damian Rouson, fortran, gcc-patches,
	salvatore.filippone

Dear All,

Has this been occasioned by this thread or have other makes
encountered the same difficulty in implementation?

Cheers

Paul

On 10 August 2015 at 20:57, Bader, Reinhold <Reinhold.Bader@lrz.de> wrote:
> Hello Toon, all else,
>
> a bit unfortunate, in my opinion (I was present at the discussion).
> I've in the meantime taken some effort to implement what the design pattern
> experts might call an "abstract factory with full dependency inversion" as
> a bare-bones framework and have attached an archive with three variants:
>
> * pre_interp contains the code that is presently valid (and indeed compiles fine
>    with both gfortran and ifort), but would become invalid due to indirect
>    parent module access
> * post_interp contains a variant that uses a helper module (mod_glue) to avoid
>    the indirect ancestor use access (if there is a more concise way to do this,
>    I'd like to know ... up to now this is the best I can do)
> * post_interp_v2 another shorter variant that pushes the extension types into a submodule
>    (with the disadvantage that these types are not really reusable, and
>     that the monster module problem is shifted to a monster submodule, or a chain of
>     submodules)
> You may need to edit the Makefiles to build.
>
> I would of course like to know how people feel about reintroducing this restriction,
> especially since the only reason given was that ancestor module access and its
> use association overriding host association would confuse users ... which is a
> problem which in my opinion could have been dealt with in a slightly different
> manner without removing the  permission for indirect parent module-referencing
> use statements. It is not clear to me whether *implementations* other than
> gfortran have problems with this, though.
>
> More germane to this thread's discussion actually is another interp that was also passed,
> and which appears entirely uncontroversial:
> http://j3-fortran.org/doc/meeting/207/15-209.txt
> It seems to me that this would permit avoiding generation of the .smod files for
> modules that do not specify an separate module procedure interface.
>
> Cheers
> Reinhold
>
>> -----Ursprüngliche Nachricht-----
>>
>> Although I do not immediately know if this is relevant for *this*
>> debate, J3 passed the following (attached) interpretation on submodules
>> the past week (it still has to go to several mail ballots, but still),
>> overwhelmingly prefering option 3:
>>
>> [attached]
>>
>> Kind regards,
>>
>> --
>> Toon Moene - e-mail: toon@moene.org - phone: +31 346 214290
>> Saturnushof 14, 3738 XG  Maartensdijk, The Netherlands
>> At home: http://moene.org/~toon/; weather: http://moene.org/~hirlam/
>> Progress of GNU Fortran: http://gcc.gnu.org/wiki/GFortran#news



-- 
Outside of a dog, a book is a man's best friend. Inside of a dog it's
too dark to read.

Groucho Marx

^ permalink raw reply	[flat|nested] 23+ messages in thread

* AW: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-08-11 10:28                 ` Paul Richard Thomas
@ 2015-08-11 11:17                   ` Bader, Reinhold
  2015-08-11 11:36                     ` Paul Richard Thomas
  0 siblings, 1 reply; 23+ messages in thread
From: Bader, Reinhold @ 2015-08-11 11:17 UTC (permalink / raw)
  To: Paul Richard Thomas
  Cc: Toon Moene, Mikael Morin, Damian Rouson, fortran, gcc-patches,
	salvatore.filippone

Hello Paul, 

To my knowledge, the J3 interp F08/128 was triggered by a question coming from Bill Long from Cray. 
The interp's text was written by the Fortran standard's editor. So there is no direct relation to this thread.

F08/0142 (useless submodules) was in turn triggered by the example given for F08/128, by Daniel Chen from IBM.
And indeed this seems to have caused some grief to other implementors.

Cheers
Reinhold

> -----Ursprüngliche Nachricht-----
> Von: Paul Richard Thomas [mailto:paul.richard.thomas@gmail.com]
> Gesendet: Dienstag, 11. August 2015 12:28
> An: Bader, Reinhold <Reinhold.Bader@lrz.de>
> Cc: Toon Moene <toon@moene.org>; Mikael Morin <mikael.morin@sfr.fr>;
> Damian Rouson <damian@sourceryinstitute.org>; fortran@gcc.gnu.org; gcc-
> patches <gcc-patches@gcc.gnu.org>; salvatore.filippone@uniroma2.it
> Betreff: Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
> 
> Dear All,
> 
> Has this been occasioned by this thread or have other makes encountered the
> same difficulty in implementation?
> 
> Cheers
> 
> Paul
> 
> On 10 August 2015 at 20:57, Bader, Reinhold <Reinhold.Bader@lrz.de> wrote:
> > Hello Toon, all else,
> >
> > a bit unfortunate, in my opinion (I was present at the discussion).
> > I've in the meantime taken some effort to implement what the design
> > pattern experts might call an "abstract factory with full dependency
> > inversion" as a bare-bones framework and have attached an archive with three
> variants:
> >
> > * pre_interp contains the code that is presently valid (and indeed compiles fine
> >    with both gfortran and ifort), but would become invalid due to indirect
> >    parent module access
> > * post_interp contains a variant that uses a helper module (mod_glue) to avoid
> >    the indirect ancestor use access (if there is a more concise way to do this,
> >    I'd like to know ... up to now this is the best I can do)
> > * post_interp_v2 another shorter variant that pushes the extension types into
> a submodule
> >    (with the disadvantage that these types are not really reusable, and
> >     that the monster module problem is shifted to a monster submodule, or a
> chain of
> >     submodules)
> > You may need to edit the Makefiles to build.
> >
> > I would of course like to know how people feel about reintroducing
> > this restriction, especially since the only reason given was that
> > ancestor module access and its use association overriding host
> > association would confuse users ... which is a problem which in my
> > opinion could have been dealt with in a slightly different manner
> > without removing the  permission for indirect parent
> > module-referencing use statements. It is not clear to me whether
> *implementations* other than gfortran have problems with this, though.
> >
> > More germane to this thread's discussion actually is another interp
> > that was also passed, and which appears entirely uncontroversial:
> > http://j3-fortran.org/doc/meeting/207/15-209.txt
> > It seems to me that this would permit avoiding generation of the .smod
> > files for modules that do not specify an separate module procedure interface.
> >
> > Cheers
> > Reinhold
> >
> >> -----Ursprüngliche Nachricht-----
> >>
> >> Although I do not immediately know if this is relevant for *this*
> >> debate, J3 passed the following (attached) interpretation on
> >> submodules the past week (it still has to go to several mail ballots,
> >> but still), overwhelmingly prefering option 3:
> >>
> >> [attached]
> >>
> >> Kind regards,
> >>
> >> --
> >> Toon Moene - e-mail: toon@moene.org - phone: +31 346 214290
> >> Saturnushof 14, 3738 XG  Maartensdijk, The Netherlands At home:
> >> http://moene.org/~toon/; weather: http://moene.org/~hirlam/ Progress
> >> of GNU Fortran: http://gcc.gnu.org/wiki/GFortran#news
> 
> 
> 
> --
> Outside of a dog, a book is a man's best friend. Inside of a dog it's too dark to
> read.
> 
> Groucho Marx

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
  2015-08-11 11:17                   ` AW: " Bader, Reinhold
@ 2015-08-11 11:36                     ` Paul Richard Thomas
  0 siblings, 0 replies; 23+ messages in thread
From: Paul Richard Thomas @ 2015-08-11 11:36 UTC (permalink / raw)
  To: Bader, Reinhold
  Cc: Toon Moene, Mikael Morin, Damian Rouson, fortran, gcc-patches,
	salvatore.filippone

Dear Reinhold,

I am glad that it was not just me being anxious about the issue!

For a day or two, I am somewhat distracted by loading up a new Lenovo
workstation and installing a xeon phi on it. Given the current insane
low price of the BC31S1P, I thought to see how best to allow gfortran
to make use of the Knight's Corner vector processor. I will start with
a vector class and associated methods. Combined with coarrays, it
should be possible to get a reasonable performance out of the phi.
After that, well we will see...

Cheers

Paul



On 11 August 2015 at 13:17, Bader, Reinhold <Reinhold.Bader@lrz.de> wrote:
> Hello Paul,
>
> To my knowledge, the J3 interp F08/128 was triggered by a question coming from Bill Long from Cray.
> The interp's text was written by the Fortran standard's editor. So there is no direct relation to this thread.
>
> F08/0142 (useless submodules) was in turn triggered by the example given for F08/128, by Daniel Chen from IBM.
> And indeed this seems to have caused some grief to other implementors.
>
> Cheers
> Reinhold
>
>> -----Ursprüngliche Nachricht-----
>> Von: Paul Richard Thomas [mailto:paul.richard.thomas@gmail.com]
>> Gesendet: Dienstag, 11. August 2015 12:28
>> An: Bader, Reinhold <Reinhold.Bader@lrz.de>
>> Cc: Toon Moene <toon@moene.org>; Mikael Morin <mikael.morin@sfr.fr>;
>> Damian Rouson <damian@sourceryinstitute.org>; fortran@gcc.gnu.org; gcc-
>> patches <gcc-patches@gcc.gnu.org>; salvatore.filippone@uniroma2.it
>> Betreff: Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
>>
>> Dear All,
>>
>> Has this been occasioned by this thread or have other makes encountered the
>> same difficulty in implementation?
>>
>> Cheers
>>
>> Paul
>>
>> On 10 August 2015 at 20:57, Bader, Reinhold <Reinhold.Bader@lrz.de> wrote:
>> > Hello Toon, all else,
>> >
>> > a bit unfortunate, in my opinion (I was present at the discussion).
>> > I've in the meantime taken some effort to implement what the design
>> > pattern experts might call an "abstract factory with full dependency
>> > inversion" as a bare-bones framework and have attached an archive with three
>> variants:
>> >
>> > * pre_interp contains the code that is presently valid (and indeed compiles fine
>> >    with both gfortran and ifort), but would become invalid due to indirect
>> >    parent module access
>> > * post_interp contains a variant that uses a helper module (mod_glue) to avoid
>> >    the indirect ancestor use access (if there is a more concise way to do this,
>> >    I'd like to know ... up to now this is the best I can do)
>> > * post_interp_v2 another shorter variant that pushes the extension types into
>> a submodule
>> >    (with the disadvantage that these types are not really reusable, and
>> >     that the monster module problem is shifted to a monster submodule, or a
>> chain of
>> >     submodules)
>> > You may need to edit the Makefiles to build.
>> >
>> > I would of course like to know how people feel about reintroducing
>> > this restriction, especially since the only reason given was that
>> > ancestor module access and its use association overriding host
>> > association would confuse users ... which is a problem which in my
>> > opinion could have been dealt with in a slightly different manner
>> > without removing the  permission for indirect parent
>> > module-referencing use statements. It is not clear to me whether
>> *implementations* other than gfortran have problems with this, though.
>> >
>> > More germane to this thread's discussion actually is another interp
>> > that was also passed, and which appears entirely uncontroversial:
>> > http://j3-fortran.org/doc/meeting/207/15-209.txt
>> > It seems to me that this would permit avoiding generation of the .smod
>> > files for modules that do not specify an separate module procedure interface.
>> >
>> > Cheers
>> > Reinhold
>> >
>> >> -----Ursprüngliche Nachricht-----
>> >>
>> >> Although I do not immediately know if this is relevant for *this*
>> >> debate, J3 passed the following (attached) interpretation on
>> >> submodules the past week (it still has to go to several mail ballots,
>> >> but still), overwhelmingly prefering option 3:
>> >>
>> >> [attached]
>> >>
>> >> Kind regards,
>> >>
>> >> --
>> >> Toon Moene - e-mail: toon@moene.org - phone: +31 346 214290
>> >> Saturnushof 14, 3738 XG  Maartensdijk, The Netherlands At home:
>> >> http://moene.org/~toon/; weather: http://moene.org/~hirlam/ Progress
>> >> of GNU Fortran: http://gcc.gnu.org/wiki/GFortran#news
>>
>>
>>
>> --
>> Outside of a dog, a book is a man's best friend. Inside of a dog it's too dark to
>> read.
>>
>> Groucho Marx



-- 
Outside of a dog, a book is a man's best friend. Inside of a dog it's
too dark to read.

Groucho Marx

^ permalink raw reply	[flat|nested] 23+ messages in thread

* Re: [Bug fortran/52846] [F2008] Support submodules - part 3/3
@ 2015-07-23 12:20 Salvatore Filippone
  0 siblings, 0 replies; 23+ messages in thread
From: Salvatore Filippone @ 2015-07-23 12:20 UTC (permalink / raw)
  To: Paul Richard Thomas
  Cc: Damian Rouson, Bader, Reinhold, Fortran List, gcc-patches

I agree with Paul that this is orthogonal to the compilation cascade
phenomenon.

In my opinion, putting PRIVATE entities in a module does not make much
sense (yes, I know my example does it, but it is a quick adaptation of
an existing code, not a clean design). If the main MODULE only contains
the public interfaces, then all those PRIVATE entities really belong to
the submodule together with the implementation(s) that use them. Even
though within the submodule they can  not formally have the PRIVATE
attribute, they would still be invisible outside the submodule,
therefore the end result would be the same.

I have not yet enough experience to say whether I am totally comfortable
with submodules as they are; however it seems to me that most of the
doubts voiced so far  depend more on programmer's discipline than on
language facilities.


Salvatore


Il giorno gio, 23/07/2015 alle 10.37 +0200, Paul Richard Thomas ha
scritto:
> Dear Damian,
>
> I do not think that there is any effect on compilation cascades. As
> long as the private part of the module file remains unchanged, it will
> not be recompiled if a descendant submodule is modified. Naturally,
> the size of the module file is increased but, if one is careful, this
> is not a big deal. A gotcha, which I will have to emphasize in the
> documentation occurs if another module file is used and its symbols
> are not exposed by public statements. If there are large numbers of
> symbols this can have a big effect on the size of the module file. I
> noticed this, when examining one of gfortran's testcases where the
> ISO_C_BINDING intrinsic module is used. Generous sprinklings of USE
> ONLYs are required to keep the module file sizes under control.
>
> I am not over enthusiastic about using compilation flags to uphold
> standards either.
>
> Cheers
>
> Paul

^ permalink raw reply	[flat|nested] 23+ messages in thread

end of thread, other threads:[~2015-08-11 11:36 UTC | newest]

Thread overview: 23+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2015-07-23  8:37 [Bug fortran/52846] [F2008] Support submodules - part 3/3 Paul Richard Thomas
2015-07-23  8:42 ` Damian Rouson
2015-07-23  8:46   ` Paul Richard Thomas
2015-07-23 16:35 ` Mikael Morin
2015-07-24  8:08   ` Paul Richard Thomas
2015-07-24  8:09     ` Damian Rouson
2015-07-24 12:10       ` Paul Richard Thomas
2015-07-29 15:32       ` Paul Richard Thomas
2015-07-29 15:36         ` Marek Polacek
2015-07-29 16:15           ` FX
2015-07-29 16:25             ` Marek Polacek
2015-07-29 16:45             ` Paul Richard Thomas
2015-08-03 10:45         ` Mikael Morin
2015-08-03 12:36           ` Paul Richard Thomas
2015-08-03 15:40             ` Mikael Morin
2015-08-04  9:40               ` Paul Richard Thomas
2015-08-05 12:09                 ` Paul Richard Thomas
2015-08-10 18:09             ` Toon Moene
2015-08-10 18:57               ` AW: " Bader, Reinhold
2015-08-11 10:28                 ` Paul Richard Thomas
2015-08-11 11:17                   ` AW: " Bader, Reinhold
2015-08-11 11:36                     ` Paul Richard Thomas
2015-07-23 12:20 Salvatore Filippone

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).