Mercurial > hg > CbC > CbC_gcc
view gcc/testsuite/gfortran.dg/winapi.f90 @ 132:d34655255c78
update gcc-8.2
author | mir3636 |
---|---|
date | Thu, 25 Oct 2018 10:21:07 +0900 |
parents | 84e7813d76e9 |
children |
line wrap: on
line source
! { dg-do run { target *-*-cygwin* *-*-mingw* } } ! { dg-options "-lkernel32" } ! Test case provided by Dennis Wassel. PROGRAM winapi USE, INTRINSIC :: iso_c_binding IMPLICIT NONE INTERFACE ! Specifically select the lstrlenA version for ASCII. FUNCTION lstrlen(string) BIND(C, name = "lstrlenA") USE, INTRINSIC :: iso_c_binding IMPLICIT NONE !GCC$ ATTRIBUTES STDCALL :: lstrlen INTEGER (C_INT) :: lstrlen CHARACTER(KIND=C_CHAR), INTENT(in) :: string(*) END FUNCTION lstrlen END INTERFACE IF (lstrlen(C_CHAR_"winapi"//C_NULL_CHAR) /= 6) STOP 1 END PROGRAM winapi