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/initial/etat0_dcmip1.f90

    r548 r899  
    1515!$OMP THREADPRIVATE(lon0) 
    1616  REAL(rstd), SAVE  :: lat0=0.0 
    17 !$OMP THREADPRIVATE(lat0) 
    18   REAL(rstd), SAVE  :: alpha=0.0 
    19 !$OMP THREADPRIVATE(alpha) 
     17  !$OMP THREADPRIVATE(lat0) 
    2018  REAL(rstd), SAVE  :: R0  
    2119!$OMP THREADPRIVATE(R0) 
    22   REAL(rstd), SAVE  :: lat1=0. 
    23 !$OMP THREADPRIVATE(lat1) 
    24   REAL(rstd), SAVE  :: lat2=0. 
    25 !$OMP THREADPRIVATE(lat2) 
    26   REAL(rstd), SAVE  :: lon1=pi/6 
    27 !$OMP THREADPRIVATE(lon1) 
    28   REAL(rstd), SAVE  :: lon2=-pi/6 
    29 !$OMP THREADPRIVATE(lon2) 
    3020  REAL(rstd), SAVE  :: latc1=0. 
    3121!$OMP THREADPRIVATE(latc1) 
     
    113103  REAL(rstd) :: pr 
    114104  !  REAL(rstd) :: lon, lat 
    115   INTEGER :: n,l 
     105  INTEGER :: l 
    116106   
    117107  DO l=1, llm+1 
     
    158148    SUBROUTINE cosine_bell_1(hx) 
    159149    REAL(rstd) :: hx(ngrid,llm) 
    160     REAL(rstd) :: rr1,rr2   
     150    REAL(rstd) :: rr1  
    161151    INTEGER :: n,l 
    162152    DO l=ll_begin,ll_end  
     
    241231      REAL(rstd)::hx(ngrid,llm)  
    242232      REAL(rstd),PARAMETER:: zz1=2000.,zz2=5000.,zz0=0.5*(zz1+zz2) 
    243       INTEGER :: n,l 
     233      INTEGER :: l 
    244234       
    245235      DO l=ll_begin,ll_end 
Note: See TracChangeset for help on using the changeset viewer.