Ignore:
Timestamp:
06/13/19 16:45:41 (5 years ago)
Author:
adurocher
Message:

trunk : Fixed GCC warnings

Fixed iso c bindings
fixed warnings with -Wall -Wno-aliasing -Wno-unused -Wno-unused-dummy-argument -Wno-maybe-uninitialized -Wno-tabs warnings
Removed all unused variables (-Wunused-variable)
vector%dot_product is now dot_product_3d to avoid compilation warning "dot_product shadows intrinsic" with GCC

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/dcmip/dcmip2016_cyclone.f90

    r548 r899  
    9595  SUBROUTINE tropical_cyclone_test(lon,lat,p,z,zcoords,u,v,t,thetav,phis,ps,rho,q) & 
    9696    BIND(c, name = "tropical_cyclone_test") 
    97  
     97    use iso_c_binding 
    9898    IMPLICIT NONE 
    9999 
     
    102102    !------------------------------------------------ 
    103103 
    104     REAL(8), INTENT(IN) ::     & 
     104    REAL(KIND=C_DOUBLE), INTENT(IN) ::     & 
    105105              lon,             &     ! Longitude (radians) 
    106106              lat                    ! Latitude (radians) 
    107107 
    108     REAL(8), INTENT(INOUT) ::  & 
     108    REAL(KIND=C_DOUBLE), INTENT(INOUT) ::  & 
    109109              p,               &     ! Pressure (Pa) 
    110110              z                      ! Height (m) 
    111111 
    112     INTEGER, INTENT(IN) :: zcoords     ! 1 if z coordinates are specified 
     112    INTEGER(KIND=C_INT32_T), INTENT(IN) :: zcoords     ! 1 if z coordinates are specified 
    113113                                     ! 0 if p coordinates are specified 
    114114 
    115     REAL(8), INTENT(OUT) ::    & 
     115    REAL(KIND=C_DOUBLE), INTENT(OUT) ::    & 
    116116              u,               &     ! Zonal wind (m s^-1) 
    117117              v,               &     ! Meridional wind (m s^-1) 
Note: See TracChangeset for help on using the changeset viewer.