OpenCores
URL https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk

Subversion Repositories openrisc_me

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [default_initialization_2.f90] - Diff between revs 149 and 154

Only display areas with differences | Details | Blame | View Log

Rev 149 Rev 154
! { dg-do compile }
! { dg-do compile }
! This tests the patch for PR29098, in which the presence of the default
! This tests the patch for PR29098, in which the presence of the default
! initializer would cause allocate to fail because the latter uses
! initializer would cause allocate to fail because the latter uses
! the interface assignment.  This, in its turn was failing because
! the interface assignment.  This, in its turn was failing because
! no expressions were found for the other components; and a FAILURE
! no expressions were found for the other components; and a FAILURE
! was returned from resolve_structure_cons.
! was returned from resolve_structure_cons.
!
!
! Contributed by Olav Vahtras  
! Contributed by Olav Vahtras  
!
!
 MODULE MAT
 MODULE MAT
   TYPE BAS
   TYPE BAS
      INTEGER :: R = 0,C = 0
      INTEGER :: R = 0,C = 0
   END TYPE BAS
   END TYPE BAS
   TYPE BLOCK
   TYPE BLOCK
      INTEGER, DIMENSION(:), POINTER ::  R,C
      INTEGER, DIMENSION(:), POINTER ::  R,C
      TYPE(BAS), POINTER, DIMENSION(:) :: NO => NULL()
      TYPE(BAS), POINTER, DIMENSION(:) :: NO => NULL()
   END TYPE BLOCK
   END TYPE BLOCK
   INTERFACE ASSIGNMENT(=)
   INTERFACE ASSIGNMENT(=)
      MODULE PROCEDURE BLASSIGN
      MODULE PROCEDURE BLASSIGN
   END INTERFACE
   END INTERFACE
   CONTAINS
   CONTAINS
      SUBROUTINE BLASSIGN(A,B)
      SUBROUTINE BLASSIGN(A,B)
      TYPE(BLOCK), INTENT(IN) :: B
      TYPE(BLOCK), INTENT(IN) :: B
      TYPE(BLOCK), INTENT(INOUT) :: A
      TYPE(BLOCK), INTENT(INOUT) :: A
      INTEGER I,N
      INTEGER I,N
      ! ...
      ! ...
      END SUBROUTINE BLASSIGN
      END SUBROUTINE BLASSIGN
 END MODULE MAT
 END MODULE MAT
PROGRAM TEST
PROGRAM TEST
USE MAT
USE MAT
TYPE(BLOCK) MATRIX
TYPE(BLOCK) MATRIX
POINTER MATRIX
POINTER MATRIX
ALLOCATE(MATRIX)
ALLOCATE(MATRIX)
END
END
! { dg-final { cleanup-modules "mat" } }
! { dg-final { cleanup-modules "mat" } }
 
 

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.