diff gcc/testsuite/gfortran.dg/unreferenced_use_assoc_1.f90 @ 111:04ced10e8804

gcc 7
author kono
date Fri, 27 Oct 2017 22:46:09 +0900
parents
children
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/gcc/testsuite/gfortran.dg/unreferenced_use_assoc_1.f90	Fri Oct 27 22:46:09 2017 +0900
@@ -0,0 +1,39 @@
+! { dg-do compile }
+! Tests the  fix for PR31424.
+!
+module InternalCompilerError
+
+   type Byte
+      private 
+      character(len=1)     :: singleByte
+   end type
+
+   type (Byte)             :: BytesPrototype(1)
+
+   type UserType
+      real :: r
+   end type
+
+contains
+
+   function UserTypeToBytes(user) result (bytes) 
+      type(UserType) :: user 
+      type(Byte)     :: bytes(size(transfer(user, BytesPrototype)))
+      bytes = transfer(user, BytesPrototype) 
+   end function
+
+   subroutine DoSomethingWithBytes(bytes)
+      type(Byte), intent(in)     :: bytes(:)
+   end subroutine
+
+end module
+
+
+program main
+   use InternalCompilerError
+   type (UserType) :: user 
+
+   ! The following line caused the ICE 
+   call DoSomethingWithBytes( UserTypeToBytes(user) )
+
+end program