Changeset 2391


Ignore:
Timestamp:
Nov 10, 2015, 9:51:52 AM (9 years ago)
Author:
Ehouarn Millour
Message:

Fix some minor anomalies spotted by the xlf compiler:

  • infotrac : wrongly giving integer values to logicals
  • surf_ocean_mod and yamada_c : should be a space between "stop" and message; but avoid using stop, use abort_physic routine instead.
  • readchlorophyll: using isnan() is not standard; compare the variable to itself instead (will return .false. if NaN).

While at it, also added some missing "only" clauses when using modules.

EM

Location:
LMDZ5/trunk/libf
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d_common/infotrac.F90

    r2372 r2391  
    5959
    6060  SUBROUTINE infotrac_init
    61     USE control_mod
     61    USE control_mod, ONLY: planet_type, config_inca
    6262#ifdef REPROBUS
    6363    USE CHEM_REP, ONLY : Init_chem_rep_trac
     
    276276             ! Y-a-t-il 1 ou 2 noms de traceurs? -> On regarde s'il y a un
    277277             ! espace ou pas au milieu de la chaine.
    278              continu=1
    279              nouveau_traceurdef=0
     278             continu=.true.
     279             nouveau_traceurdef=.false.
    280280             iiq=1
    281281             do while (continu)
    282282                if (tchaine(iiq:iiq).eq.' ') then
    283                   nouveau_traceurdef=1
    284                   continu=0
     283                  nouveau_traceurdef=.true.
     284                  continu=.false.
    285285                else if (iiq.lt.LEN_TRIM(tchaine)) then
    286286                  iiq=iiq+1
    287287                else
    288                   continu=0     
     288                  continu=.false.
    289289                endif
    290290             enddo
  • LMDZ5/trunk/libf/phylmd/readchlorophyll.F90

    r2346 r2391  
    1313                                 grid2dto1d_glo
    1414    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    15     USE mod_phys_lmdz_para
    16     USE phys_state_var_mod
    17     USE phys_local_var_mod
    18     USE dimphy
     15    USE mod_phys_lmdz_para, ONLY: scatter
     16    USE phys_state_var_mod, ONLY: chl_con
    1917
    2018    implicit none
     
    9391    CALL nf95_inq_varid(ncid_in, "CHL", varid)
    9492    ncerr = nf90_get_var(ncid_in, varid, chlorocon)
    95     print *,'code erreur readaerosolstrato=', ncerr, varid
     93    print *,'code erreur readchlorophyll=', ncerr, varid
    9694
    9795    CALL nf95_close(ncid_in)
     
    9997!---select the correct month
    10098    IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN
    101       print *,'probleme avec le mois dans readaerosolstrat =', mth_cur
     99      print *,'probleme avec le mois dans readchlorophyll =', mth_cur
    102100    ENDIF
    103101    chlorocon_mois(:,:) = chlorocon(:,:,mth_cur)
     
    109107    print*,"chrolophyll current month",mth_cur
    110108    do i=1,klon_glo
    111       if(isnan(chlorocon_mois_glo(i)))then
     109!      if(isnan(chlorocon_mois_glo(i)))then ! isnan() is not in the Fortran standard...
     110!      Another way to check for NaN:
     111       if(chlorocon_mois_glo(i).ne.chlorocon_mois_glo(i)) then
    112112         chlorocon_mois_glo(i)=0.
    113113      endif
  • LMDZ5/trunk/libf/phylmd/surf_ocean_mod.F90

    r2322 r2391  
    2121
    2222  use albedo, only: alboc, alboc_cd
    23   USE dimphy
     23  USE dimphy, ONLY: klon, zmasq
    2424  USE surface_data, ONLY     : type_ocean
    2525  USE ocean_forced_mod, ONLY : ocean_forced_noice
    2626  USE ocean_slab_mod, ONLY   : ocean_slab_noice
    2727  USE ocean_cpl_mod, ONLY    : ocean_cpl_noice
    28   USE indice_sol_mod
     28  USE indice_sol_mod, ONLY : nbsrf, is_oce
    2929!
    3030! This subroutine will make a call to ocean_XXX_noice according to the ocean mode (force,
     
    9292    REAL, DIMENSION(klon) :: radsol
    9393    REAL, DIMENSION(klon) :: cdragq ! Cdrag pour l'evaporation
     94    CHARACTER(len=20),PARAMETER :: modname="surf_ocean"
    9495
    9596! End definition
     
    217218    ENDDO
    218219ELSE
    219        STOP'version non prevue'
     220       CALL abort_physic(modname,'version non prevue',1)
    220221ENDIF
    221222!
  • LMDZ5/trunk/libf/phylmd/yamada_c.F90

    r2346 r2391  
    55     &   ,pu,pv,pt,d_u,d_v,d_t,cd,q2,km,kn,kq,d_t_diss,ustar &
    66     &   ,iflag_pbl,okiophys)
    7       use dimphy
     7      USE dimphy, ONLY: klon, klev
    88      USE print_control_mod, ONLY: prt_level
    99      IMPLICIT NONE
     
    113113      real w2yam(klon,klev),t2yam(klon,klev)
    114114      logical,save :: firstcall=.true.
    115 
     115!$OMP THREADPRIVATE(firstcall)       
     116      CHARACTER(len=20),PARAMETER :: modname="yamada_c"
    116117REAL, DIMENSION(klon,klev+1) :: fluxu,fluxv,fluxt
    117118REAL, DIMENSION(klon,klev+1) :: dddu,dddv,dddt
     
    119120REAL, DIMENSION(klon,klev+1) :: masseb,q2old,q2neg
    120121
    121 !$OMP THREADPRIVATE(firstcall)       
    122122      frif(ri)=0.6588*(ri+0.1776-sqrt(ri*ri-0.3221*ri+0.03156))
    123123      falpha(ri)=1.318*(0.2231-ri)/(0.2341-ri)
     
    571571
    572572      else
    573          stop'Cas nom prevu dans yamada4'
     573         CALL abort_physic(modname,'Cas nom prevu dans yamada4',1)
    574574
    575575      endif ! Fin du cas 8
Note: See TracChangeset for help on using the changeset viewer.