https://gcc.gnu.org/bugzilla/show_bug.cgi?id=81937

            Bug ID: 81937
           Summary: stack-buffer-overflow on memcpy in
                    libgfortran/io/unix.c on character(kind=4)
           Product: gcc
           Version: 8.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: libfortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: zeccav at gmail dot com
  Target Milestone: ---
              Host: x86_64-pc-linux-gnu
             Build: trunk 251201

! dtio_14.f90 test case 
! compiled with -fsanitize=address -g
! stack-buffer-overflow on memcpy in libgfortran/io/unix.c on character(kind=4)
MODULE p
  TYPE :: person
    CHARACTER (LEN=20) :: name
    INTEGER(4) :: age
    CONTAINS
      procedure :: pwf
      procedure :: prf
      GENERIC :: WRITE(FORMATTED) => pwf
      GENERIC :: READ(FORMATTED) => prf
  END TYPE person
CONTAINS
  SUBROUTINE pwf (dtv,unit,iotype,vlist,iostat,iomsg)
    CLASS(person), INTENT(IN) :: dtv
    INTEGER, INTENT(IN) :: unit
    CHARACTER (LEN=*), INTENT(IN) :: iotype
    INTEGER, INTENT(IN) :: vlist(:)
    INTEGER, INTENT(OUT) :: iostat
    CHARACTER (LEN=*), INTENT(INOUT) :: iomsg
    WRITE(unit, FMT = *, IOSTAT=iostat) dtv%name, dtv%age
  END SUBROUTINE pwf

  SUBROUTINE prf (dtv,unit,iotype,vlist,iostat,iomsg)
    CLASS(person), INTENT(INOUT) :: dtv
    INTEGER, INTENT(IN) :: unit
    CHARACTER (LEN=*), INTENT(IN) :: iotype
    INTEGER, INTENT(IN) :: vlist(:)
    INTEGER, INTENT(OUT) :: iostat
    CHARACTER (LEN=*), INTENT(INOUT) :: iomsg
    READ (UNIT = UNIT, FMT = *) dtv%name, dtv%age
  END SUBROUTINE prf
END MODULE p

PROGRAM test
  USE p
  TYPE (person) :: chairman, answer
  character(kind=1,len=80) :: str1
  character(kind=4,len=80) :: str4
  str1 = ""
  str4 = 4_""
  chairman%name="Charlie"
  chairman%age=62
  answer = chairman
! KIND=1 test
  write (str1, *) chairman
  if (trim(str1).ne."  Charlie                       62") call abort
  chairman%name="Bogus"
  chairman%age=99
  read (str1, *) chairman
  if (chairman%name.ne.answer%name) call abort
  if (chairman%age.ne.answer%age) call abort
! KIND=4 test
  write (str4, *) chairman
  if (trim(str4).ne.4_"  Charlie                       62") call abort
  chairman%name="Bogus"
  chairman%age=99
  read (str4, *) chairman
  if (chairman%name.ne.answer%name) call abort
  if (chairman%age.ne.answer%age) call abort
END PROGRAM test
!=================================================================
!==4920==ERROR: AddressSanitizer: stack-buffer-overflow on address
0x7fff4c186e30 at pc 0x2ad600909b22 bp 0x7fff4c186170 sp 0x7fff4c185920
!READ of size 4 at 0x7fff4c186e30 thread T0
!    #0 0x2ad600909b21 in __interceptor_memcpy
../../../../gcc/libsanitizer/asan/asan_interceptors.cc:456
!    #1 0x2ad601a5b07b in mem_read4 ../../../gcc/libgfortran/io/unix.c:856
!    #2 0x2ad601a4b9c3 in sread ../../../gcc/libgfortran/io/unix.h:53
!    #3 0x2ad601a4b9c3 in next_char_internal
../../../gcc/libgfortran/io/list_read.c:271
!    #4 0x2ad601a4b3f8 in eat_spaces
../../../gcc/libgfortran/io/list_read.c:420
!    #5 0x2ad601a4b46d in eat_separator
../../../gcc/libgfortran/io/list_read.c:465
!    #6 0x2ad601a4c08a in read_integer
../../../gcc/libgfortran/io/list_read.c:1101
!    #7 0x2ad601a4efda in list_formatted_read_scalar
../../../gcc/libgfortran/io/list_read.c:2168
!    #8 0x2ad601a505f9 in _gfortrani_list_formatted_read
../../../gcc/libgfortran/io/list_read.c:2332
!    #9 0x40164e in __p_MOD_prf
/home/vitti/1tb/vitti/test/gcc/gcc/testsuite/gfortran.dg/p.f90:32
!    #10 0x2ad601a4eefd in list_formatted_read_scalar
../../../gcc/libgfortran/io/list_read.c:2222
!    #11 0x2ad601a505f9 in _gfortrani_list_formatted_read
../../../gcc/libgfortran/io/list_read.c:2332
!    #12 0x40291a in test
/home/vitti/1tb/vitti/test/gcc/gcc/testsuite/gfortran.dg/p.f90:59
!    #13 0x402a8c in main
/home/vitti/1tb/vitti/test/gcc/gcc/testsuite/gfortran.dg/p.f90:37
!    #14 0x2ad60242f509 in __libc_start_main (/usr/lib64/libc.so.6+0x20509)
!    #15 0x4011f9 in _start
(/home/vitti/1tb/vitti/test/gcc-251201/gcc/testsuite/gfortran.dg/a.out+0x4011f9)

!Address 0x7fff4c186e30 is located in stack of thread T0 at offset 992 in frame
!    #0 0x401ad0 in test
/home/vitti/1tb/vitti/test/gcc/gcc/testsuite/gfortran.dg/p.f90:36

!  This frame has 14 object(s):
!    [32, 36) 'len.7'
!    [96, 100) 'len.13'
!    [160, 168) 'pstr.6'
!    [224, 232) 'pstr.12'
!    [288, 304) 'class.5'
!    [352, 368) 'class.9'
!    [416, 432) 'class.11'
!    [480, 496) 'class.15'
!    [544, 624) 'str1'
!    [672, 992) 'str4' <== Memory access at offset 992 overflows this variable
!    [1024, 1504) 'dt_parm.4'
!    [1536, 2016) 'dt_parm.8'
!    [2048, 2528) 'dt_parm.10'
!    [2560, 3040) 'dt_parm.14'
!HINT: this may be a false positive if your program uses some custom stack
unwind mechanism or swapcontext
!     (longjmp and C++ exceptions *are* supported)
!SUMMARY: AddressSanitizer: stack-buffer-overflow
../../../../gcc/libsanitizer/asan/asan_interceptors.cc:456 in
__interceptor_memcpy
!Shadow bytes around the buggy address:
!  0x100069828d70: f2 f2 f2 f2 f2 f2 00 00 f2 f2 f2 f2 f2 f2 00 00
!  0x100069828d80: f2 f2 f2 f2 f2 f2 00 00 f2 f2 f2 f2 f2 f2 00 00
!  0x100069828d90: 00 00 00 00 00 00 00 00 f2 f2 f2 f2 f2 f2 00 00
!  0x100069828da0: 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
!  0x100069828db0: 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
!=>0x100069828dc0: 00 00 00 00 00 00[f2]f2 f2 f2 00 00 00 00 00 00
!  0x100069828dd0: 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
!  0x100069828de0: 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
!  0x100069828df0: 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
!  0x100069828e00: 00 00 00 00 00 00 f2 f2 f2 f2 00 00 00 00 00 00
!  0x100069828e10: 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
!Shadow byte legend (one shadow byte represents 8 application bytes):
!  Addressable:           00
!  Partially addressable: 01 02 03 04 05 06 07
!  Heap left redzone:       fa
!  Freed heap region:       fd
!  Stack left redzone:      f1
!  Stack mid redzone:       f2
!  Stack right redzone:     f3
!  Stack after return:      f5
!  Stack use after scope:   f8
!  Global redzone:          f9
!  Global init order:       f6
!  Poisoned by user:        f7
!  Container overflow:      fc
!  Array cookie:            ac
!  Intra object redzone:    bb
!  ASan internal:           fe
!  Left alloca redzone:     ca
!  Right alloca redzone:    cb
!==4920==ABORTING

Reply via email to