view gcc/testsuite/gfortran.dg/multiple_allocation_2.f90 @ 144:8f4e72ab4e11

fix segmentation fault caused by nothing next cur_op to end
author Takahiro SHIMIZU <anatofuz@cr.ie.u-ryukyu.ac.jp>
date Sun, 23 Dec 2018 21:23:56 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do run }
! PR 27470: This used fail because of confusion between
!           mol (allocatable) and mol(1)%array(:) (pointer).
!           Derived from a test case by FX Coudert.
PROGRAM MAIN
  TYPE foo
    INTEGER, DIMENSION(:), POINTER :: array
  END TYPE foo

  type(foo),allocatable,dimension(:) :: mol

  ALLOCATE (mol(1))
  ALLOCATE (mol(1)%array(5))
  ALLOCATE (mol(1)%array(5))

  END