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_supercell.f90

    r548 r899  
    148148 
    149149    ! Variables for calculation of equatorial profile 
    150     REAL(8) :: exnereqs, p, T, qvs, qv 
    151  
    152     ! Error metric 
    153     REAL(8) :: err 
     150    REAL(8) :: exnereqs, p, T, qvs 
    154151 
    155152    ! Loop indices 
     
    349346  SUBROUTINE supercell_test(lon,lat,p,z,zcoords,u,v,t,thetav,ps,rho,q,pert) & 
    350347    BIND(c, name = "supercell_test") 
    351   
     348    use iso_c_binding 
    352349    IMPLICIT NONE 
    353350 
     
    355352    !   Input / output parameters 
    356353    !------------------------------------------------ 
    357     REAL(8), INTENT(IN)  :: & 
     354    REAL(KIND=c_double), INTENT(IN)  :: & 
    358355                lon,        & ! Longitude (radians) 
    359356                lat           ! Latitude (radians) 
    360357 
    361     REAL(8), INTENT(INOUT) :: & 
     358    REAL(KIND=c_double), INTENT(INOUT) :: & 
    362359                p,            & ! Pressure (Pa) 
    363360                z               ! Altitude (m) 
    364361 
    365     INTEGER, INTENT(IN) :: zcoords     ! 1 if z coordinates are specified 
     362    INTEGER(KIND=c_int32_t), INTENT(IN) :: zcoords     ! 1 if z coordinates are specified 
    366363                                       ! 0 if p coordinates are specified 
    367364 
    368     REAL(8), INTENT(OUT) :: & 
     365    REAL(KIND=c_double), INTENT(OUT) :: & 
    369366                u,          & ! Zonal wind (m s^-1) 
    370367                v,          & ! Meridional wind (m s^-1) 
     
    375372                q             ! water vapor mixing ratio (kg/kg) 
    376373 
    377     INTEGER, INTENT(IN) :: pert  ! 1 if perturbation should be included 
     374    INTEGER(KIND=c_int32_t), INTENT(IN) :: pert  ! 1 if perturbation should be included 
    378375                                 ! 0 if no perturbation should be included 
    379376 
Note: See TracChangeset for help on using the changeset viewer.