OSDN Git Service

fortran/
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / pointer_intent_1.f90
1 ! { dg-run }
2 ! { dg-options "-std=f2003 -fall-intrinsics" }
3 ! Pointer intent test
4 ! PR fortran/29624
5 !
6 ! Valid program
7 program test
8  implicit none
9  type myT
10    integer          :: x
11    integer, pointer :: point
12  end type myT
13  integer, pointer :: p
14  type(myT), pointer :: t
15  type(myT) :: t2
16  allocate(p,t)
17  allocate(t%point)
18  t%point = 55
19  p = 33
20  call a(p,t)
21  deallocate(p)
22  nullify(p)
23  call a(p,t)
24  call nonpointer(t2)
25 contains
26   subroutine a(p,t)
27     integer, pointer,intent(in)    :: p
28     type(myT), pointer, intent(in) :: t
29     integer, pointer :: tmp
30     if(.not.associated(p)) return
31     if(p /= 33) call abort()
32     p = 7
33     if (associated(t)) then
34       ! allocating is valid as we don't change the status
35       ! of the pointer "t", only of it's target
36       t%x = -15
37       if(.not.associated(t%point)) call abort()
38       if(t%point /= 55) call abort()
39       nullify(t%point)
40       allocate(tmp)
41       t%point => tmp
42       deallocate(t%point)
43       t%point => null(t%point)
44       tmp => null(tmp)
45       allocate(t%point)
46       t%point = 27
47       if(t%point /= 27) call abort()
48       if(t%x     /= -15) call abort()
49       call foo(t)
50       if(t%x     /=  32) call abort()
51       if(t%point /= -98) call abort()
52     end if
53     call b(p)
54     if(p /= 5) call abort()
55   end subroutine
56   subroutine b(v)
57     integer, intent(out) :: v
58     v = 5
59   end subroutine b
60   subroutine foo(comp)
61     type(myT), intent(inout) :: comp
62     if(comp%x     /= -15) call abort()
63     !if(comp%point /=  27) call abort()
64     comp%x     = 32
65     comp%point = -98
66   end subroutine foo
67   subroutine nonpointer(t)
68      type(myT), intent(in) :: t
69      t%point = 7
70   end subroutine nonpointer
71 end program