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

    r548 r899  
    4040! 
    4141!======================================================================= 
    42  
    4342  IMPLICIT NONE 
    44  
     43   
    4544!======================================================================= 
    4645!    Physical constants 
     
    9998  SUBROUTINE baroclinic_wave_test(deep,moist,pertt,X,lon,lat,p,z,zcoords,u,v,t,thetav,phis,ps,rho,q) & 
    10099    BIND(c, name = "baroclinic_wave_test") 
    101   
     100    use iso_c_binding 
    102101    IMPLICIT NONE 
    103102 
     
    105104!     input/output params parameters at given location 
    106105!----------------------------------------------------------------------- 
    107     INTEGER, INTENT(IN)  :: & 
     106    INTEGER(KIND=C_INT32_T), INTENT(IN)  :: & 
    108107                deep,       & ! Deep (1) or Shallow (0) test case 
    109108                moist,      & ! Moist (1) or Dry (0) test case 
    110109                pertt         ! Perturbation type 
    111110 
    112     REAL(8), INTENT(IN)  :: & 
     111    REAL(KIND=C_DOUBLE), INTENT(IN)  :: & 
    113112                lon,        & ! Longitude (radians) 
    114113                lat,        & ! Latitude (radians) 
    115114                X             ! Earth scaling parameter 
    116115 
    117     REAL(8), INTENT(INOUT) :: & 
     116    REAL(KIND=C_DOUBLE), INTENT(INOUT) :: & 
    118117                p,            & ! Pressure (Pa) 
    119118                z               ! Altitude (m) 
    120119 
    121     INTEGER, INTENT(IN) :: zcoords     ! 1 if z coordinates are specified 
     120    INTEGER(KIND=C_INT32_T), INTENT(IN) :: zcoords     ! 1 if z coordinates are specified 
    122121                                       ! 0 if p coordinates are specified 
    123122 
    124     REAL(8), INTENT(OUT) :: & 
     123    REAL(KIND=C_DOUBLE), INTENT(OUT) :: & 
    125124                u,          & ! Zonal wind (m s^-1) 
    126125                v,          & ! Meridional wind (m s^-1) 
     
    138137    REAL(8) :: T0, constH, constC, scaledZ, inttau2, rratio 
    139138    REAL(8) :: inttermU, bigU, rcoslat, omegarcoslat 
    140     REAL(8) :: eta, qratio, qnum, qden 
     139    REAL(8) :: eta 
    141140 
    142141    !------------------------------------------------ 
Note: See TracChangeset for help on using the changeset viewer.