Changeset 5075


Ignore:
Timestamp:
Jul 19, 2024, 10:05:57 AM (4 months ago)
Author:
abarral
Message:

[continued & end] replace netcdf by lmdz_netcdf.F90 wrapper
"use netcdf" is now only used in lmdz_netcdf.F90 (except ecrad and obsolete/)
<include "netcdf.inc"> is now likewise only used in lmdz_netcdf.F90.

systematically specify explicitely <USE lmdz_netcdf, ONLY:> (probably left some missing, to correct later on)

Further replacement of nf_put_* by nf90_put_* (same for _get_)

[minor] replace deprecated boolean operators along the way

Location:
LMDZ6/trunk
Files:
108 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d/dynetat0.F90

    r4984 r5075  
    88  USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName
    99  USE strings_mod, ONLY: maxlen, msg, strStack, real2str, int2str
    10   USE netcdf,      ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_INQ_VARID, &
     10  USE lmdz_netcdf,      ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_INQ_VARID, &
    1111                         NF90_CLOSE, NF90_GET_VAR, NF90_NoErr
    1212  USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3, getKey
  • LMDZ6/trunk/libf/dyn3d/dynredem.F90

    r4389 r5075  
    99  USE strings_mod, ONLY: maxlen
    1010  USE infotrac, ONLY: nqtot, tracers
    11   USE netcdf, ONLY: NF90_CREATE, NF90_DEF_DIM, NF90_INQ_VARID, NF90_GLOBAL,    &
     11  USE lmdz_netcdf, ONLY: NF90_CREATE, NF90_DEF_DIM, NF90_INQ_VARID, NF90_GLOBAL,    &
    1212                    NF90_CLOSE,  NF90_PUT_ATT, NF90_UNLIMITED, NF90_CLOBBER,   &
    1313                    NF90_64BIT_OFFSET
     
    169169  USE infotrac, ONLY: nqtot, tracers, type_trac
    170170  USE control_mod
    171   USE netcdf,   ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_GET_VAR, NF90_INQ_VARID,  &
     171  USE lmdz_netcdf,   ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_GET_VAR, NF90_INQ_VARID,  &
    172172                      NF90_CLOSE, NF90_WRITE,   NF90_PUT_VAR, NF90_NoErr
    173173  USE dynredem_mod, ONLY: dynredem_write_u, dynredem_write_v, dynredem_read_u, &
  • LMDZ6/trunk/libf/dyn3d/dynredem_mod.F90

    r5069 r5075  
    11MODULE dynredem_mod
    22
    3   USE lmdz_netcdf
     3  USE lmdz_netcdf, ONLY: nf90_strerror,nf90_noerr,nf90_redef,nf90_put_var,nf90_enddef,nf90_put_att,&
     4          nf90_inq_varid,nf90_get_var,nf90_format,nf90_def_var
    45  IMPLICIT NONE; PRIVATE
    56  PUBLIC :: dynredem_write_u, dynredem_write_v, dynredem_read_u, err
  • LMDZ6/trunk/libf/dyn3d/guide_mod.F90

    r5071 r5075  
    7272  SUBROUTINE guide_init
    7373
    74     use netcdf, only: nf90_noerr
     74    use lmdz_netcdf, only: nf90_noerr
    7575    USE control_mod, ONLY: day_step
    7676    USE serre_mod, ONLY: grossismx
  • LMDZ6/trunk/libf/dyn3d/iniacademic.F90

    r4984 r5075  
    2222  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    2323  USE readTracFiles_mod, ONLY: addPhase
    24   use netcdf, only : NF90_NOWRITE,NF90_OPEN,NF90_NOERR,NF90_INQ_VARID
    25   use netcdf, only : NF90_CLOSE, NF90_GET_VAR
    26 
     24  use lmdz_netcdf, only : NF90_NOWRITE,NF90_OPEN,NF90_NOERR,NF90_INQ_VARID,NF90_CLOSE,NF90_GET_VAR
    2725
    2826  !   Author:    Frederic Hourdin      original: 15/01/93
     
    143141     relief=0.
    144142     ierr = NF90_OPEN ('relief_in.nc', NF90_NOWRITE,nid_relief)
    145      if (ierr.EQ.NF90_NOERR) THEN
     143     if (ierr==NF90_NOERR) THEN
    146144         ierr=NF90_INQ_VARID(nid_relief,'RELIEF',varid)
    147145         if (ierr==NF90_NOERR) THEN
     
    248246        tetastrat=ttp*zsig**(-kappa)
    249247        tetapv=tetastrat
    250         IF ((ok_pv).AND.(zsig.LT.0.1)) THEN
     248        IF ((ok_pv).AND.(zsig<0.1)) THEN
    251249           tetapv=tetastrat*(zsig*10.)**(kappa*cpp*gam_pv/1000./g)
    252250        ENDIF
  • LMDZ6/trunk/libf/dyn3d_common/grilles_gcm_netcdf_sub.F90

    r4357 r5075  
    1414  USE comconst_mod, ONLY: cpp, kappa, g, omeg, daysec, rad, pi
    1515  USE comvert_mod, ONLY: presnivs, preff, pa
    16   use netcdf, only: nf90_def_var, nf90_int, nf90_float, nf90_put_var
     16  USE lmdz_netcdf, ONLY: nf90_def_var, nf90_int, nf90_float, nf90_put_var, nf_enddef, &
     17      nf_put_att_text,nf_def_dim,nf_64bit_offset,nf_clobber,nf_create
    1718 
    1819  IMPLICIT NONE
     
    2122  INCLUDE "paramet.h"
    2223  INCLUDE "comgeom.h"
    23   INCLUDE "netcdf.inc"
    2424
    2525!========================
     
    232232
    233233SUBROUTINE handle_err(status)
    234   INCLUDE "netcdf.inc"
     234  USE lmdz_netcdf, ONLY: nf_strerror
    235235
    236236  INTEGER status
    237   IF (status.NE.nf_noerr) THEN
     237  IF (status/=nf_noerr) THEN
    238238     PRINT *,NF_STRERROR(status)
    239239     CALL abort_gcm('grilles_gcm_netcdf','netcdf error',1)
  • LMDZ6/trunk/libf/dyn3dmem/dynetat0_loc.F90

    r4984 r5075  
    99  USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName
    1010  USE strings_mod, ONLY: maxlen, msg, strStack, real2str, int2str, strIdx
    11   USE netcdf,      ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_INQUIRE_DIMENSION, NF90_INQ_VARID, &
     11  USE lmdz_netcdf,      ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_INQUIRE_DIMENSION, NF90_INQ_VARID, &
    1212                         NF90_CLOSE, NF90_GET_VAR, NF90_INQUIRE_VARIABLE,  NF90_NoErr
    1313  USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3, getKey
  • LMDZ6/trunk/libf/dyn3dmem/dynredem_loc.F90

    r4389 r5075  
    1111  USE strings_mod, ONLY: maxlen
    1212  USE infotrac, ONLY: nqtot, tracers
    13   USE netcdf, ONLY: NF90_CREATE, NF90_DEF_DIM, NF90_INQ_VARID, NF90_GLOBAL,    &
     13  USE lmdz_netcdf, ONLY: NF90_CREATE, NF90_DEF_DIM, NF90_INQ_VARID, NF90_GLOBAL,    &
    1414                    NF90_CLOSE,  NF90_PUT_ATT, NF90_UNLIMITED, NF90_CLOBBER,   &
    1515                    NF90_64BIT_OFFSET
     
    178178  USE infotrac, ONLY: nqtot, tracers, type_trac
    179179  USE control_mod
    180   USE netcdf,   ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_GET_VAR, NF90_INQ_VARID,  &
     180  USE lmdz_netcdf,   ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_GET_VAR, NF90_INQ_VARID,  &
    181181                      NF90_CLOSE, NF90_WRITE,   NF90_PUT_VAR, NF90_NoErr
    182182  USE dynredem_mod, ONLY: dynredem_write_u, dynredem_write_v, dynredem_read_u, &
  • LMDZ6/trunk/libf/dyn3dmem/dynredem_mod.F90

    r5069 r5075  
    44  USE parallel_lmdz
    55  USE mod_hallo
    6   USE lmdz_netcdf
     6  USE lmdz_netcdf, ONLY:nf90_strerror,nf90_noerr,nf90_redef,nf90_put_var,nf90_inquire_dimension,&
     7          nf90_format,nf90_inq_varid,nf90_get_var,nf90_def_var,nf90_enddef,nf90_put_att
    78  PRIVATE
    89  PUBLIC :: dynredem_write_u, dynredem_write_v, dynredem_read_u, err
  • LMDZ6/trunk/libf/dyn3dmem/iniacademic_loc.F90

    r4984 r5075  
    2323  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    2424  USE readTracFiles_mod, ONLY: addPhase
    25   use netcdf, only : NF90_NOWRITE,NF90_OPEN,NF90_NOERR,NF90_INQ_VARID
    26   use netcdf, only : NF90_CLOSE, NF90_GET_VAR
    27 
     25  use lmdz_netcdf, only : NF90_NOWRITE,NF90_OPEN,NF90_NOERR,NF90_INQ_VARID,NF90_CLOSE, NF90_GET_VAR
    2826
    2927  !   Author:    Frederic Hourdin      original: 15/01/93
     
    155153     relief=0.
    156154     ierr = NF90_OPEN ('relief_in.nc', NF90_NOWRITE,nid_relief)
    157      if (ierr.EQ.NF90_NOERR) THEN
     155     if (ierr==NF90_NOERR) THEN
    158156         ierr=NF90_INQ_VARID(nid_relief,'RELIEF',varid)
    159157         if (ierr==NF90_NOERR) THEN
     
    257255        tetastrat=ttp*zsig**(-kappa)
    258256        tetapv=tetastrat
    259         IF ((ok_pv).AND.(zsig.LT.0.1)) THEN
     257        IF ((ok_pv).AND.(zsig<0.1)) THEN
    260258           tetapv=tetastrat*(zsig*10.)**(kappa*cpp*gam_pv/1000./g)
    261259        ENDIF
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/ce0l.F90

    r4689 r5075  
    2121  USE etat0phys,      ONLY: etat0phys_netcdf
    2222  USE limit,          ONLY: limit_netcdf
    23   USE netcdf,         ONLY: NF90_OPEN, NF90_NOWRITE, NF90_CLOSE, NF90_NOERR,    &
     23  USE lmdz_netcdf,         ONLY: NF90_OPEN, NF90_NOWRITE, NF90_CLOSE, NF90_NOERR,    &
    2424         NF90_INQUIRE_DIMENSION, NF90_INQ_DIMID, NF90_INQ_VARID, NF90_GET_VAR
    2525  USE infotrac,       ONLY: init_infotrac
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/limit_netcdf.F90

    r5073 r5075  
    7171#ifndef CPP_1D
    7272  USE indice_sol_mod
    73   USE netcdf,             ONLY: NF90_OPEN,    NF90_CREATE,  NF90_CLOSE,        &
     73  USE lmdz_netcdf,             ONLY: NF90_OPEN,    NF90_CREATE,  NF90_CLOSE,        &
    7474                  NF90_DEF_DIM, NF90_DEF_VAR, NF90_PUT_VAR, NF90_PUT_ATT,      &
    75                   NF90_NOERR,   NF90_NOWRITE, NF90_DOUBLE, NF90_GLOBAL,       &
     75                  NF90_NOERR,   NF90_NOWRITE, NF90_GLOBAL,       &
    7676                  NF90_CLOBBER, NF90_ENDDEF,  NF90_UNLIMITED, NF90_FLOAT,      &
    77                   NF90_64BIT_OFFSET
     77                  NF90_64BIT_OFFSET, NF90_FORMAT
    7878  USE inter_barxy_m,      ONLY: inter_barxy
    7979  USE netcdf95,           ONLY: nf95_def_var, nf95_put_att, nf95_put_var
    8080  USE comconst_mod, ONLY: pi
    8181  USE phys_cal_mod, ONLY: calend
    82   USE lmdz_netcdf, ONLY: NF90_FORMAT
    8382  IMPLICIT NONE
    8483!-------------------------------------------------------------------------------
     
    322321!     2) Dimensional variables have the same names as corresponding dimensions.
    323322!-----------------------------------------------------------------------------
    324   USE netcdf, ONLY: NF90_OPEN, NF90_INQ_VARID, NF90_INQUIRE_VARIABLE, &
     323  USE lmdz_netcdf, ONLY: NF90_OPEN, NF90_INQ_VARID, NF90_INQUIRE_VARIABLE, &
    325324       NF90_CLOSE, NF90_INQ_DIMID, NF90_INQUIRE_DIMENSION, NF90_GET_VAR, &
    326325       NF90_GET_ATT
     
    741740! Purpose: NetCDF errors handling.
    742741!-------------------------------------------------------------------------------
    743   USE netcdf, ONLY : NF90_NOERR, NF90_STRERROR
     742  USE lmdz_netcdf, ONLY : NF90_NOERR, NF90_STRERROR
    744743  IMPLICIT NONE
    745744!-------------------------------------------------------------------------------
  • LMDZ6/trunk/libf/misc/lmdz_netcdf.F90

    r5073 r5075  
    44!  1) Turn netcdf into a "real" fortran module, without the INCLUDE call
    55!  2) Handle the NC_DOUBLE CPP key. This key should ONLY be used here.
    6 ! Ideally, the "real" netcdf module/headers should ONLY be called here. (WIP) TODO
     6! The "real" netcdf module/headers should ONLY be called here.
    77! ---------------------------------------------
    8 ! TODO check all uses of `use netcdf` + netcdf.inc
    98
    109MODULE lmdz_netcdf
  • LMDZ6/trunk/libf/misc/write_field.F90

    r2342 r5075  
    1 !
    2 ! $Id$
    3 !
    41module write_field
    5 implicit none
     2  USE lmdz_netcdf, ONLY: nf_sync, nf90_put_var, nf_enddef, nf_def_dim, nf_unlimited, &
     3      nf_clobber, nf90_format, nf_create, nf_def_var
     4
     5  implicit none
    66
    77  integer, parameter :: MaxWriteField = 100
     
    7373    subroutine WriteField_gen(name,Field,dimx,dimy,dimz)
    7474    implicit none
    75     include 'netcdf.inc'
    7675      character(len=*) :: name
    7776      integer :: dimx,dimy,dimz
     
    102101      count(4)=1
    103102
    104       status = NF_PUT_VARA_DOUBLE(FieldId(Index),FieldVarId(Index),start,count,Field)
     103      status = nf90_put_var(FieldId(Index),FieldVarId(Index),Field,start,count)
    105104      status = NF_SYNC(FieldId(Index))
    106105     
     
    109108    subroutine CreateNewField(name,dimx,dimy,dimz)
    110109    implicit none
    111     include 'netcdf.inc' 
    112110      character(len=*) :: name
    113111      integer :: dimx,dimy,dimz
     
    126124      status = NF_DEF_DIM(FieldId(NbField),'Z',dimz,TabDim(3))
    127125      status = NF_DEF_DIM(FieldId(NbField),'iter',NF_UNLIMITED,TabDim(4))
    128       status = NF_DEF_VAR(FieldId(NbField),FieldName(NbField),NF_DOUBLE,4,TabDim,FieldVarId(NbField))
     126      status = NF_DEF_VAR(FieldId(NbField),FieldName(NbField),NF90_FORMAT,4,TabDim,FieldVarId(NbField))
    129127      status = NF_ENDDEF(FieldId(NbField))
    130128
    131129    end subroutine CreateNewField
    132    
    133    
    134130   
    135131  subroutine write_field1D(name,Field)
     
    285281                      //trim(int2str(pos+offset))      &   
    286282                      //'," ---> ",g22.16," | ")'
    287 ! dépent de l'implémention, sur compaq, c'est necessaire
     283! d�pent de l'impl�mention, sur compaq, c'est necessaire
    288284!            Pos=Pos+ColumnSize
    289285          endif
  • LMDZ6/trunk/libf/misc/wxios.F90

    r4817 r5075  
    7070        reformaop = "average"
    7171       
    72         IF (op.EQ."inst(X)") THEN
     72        IF (op=="inst(X)") THEN
    7373            reformaop = "instant"
    7474        END IF
    7575       
    76         IF (op.EQ."once") THEN
     76        IF (op=="once") THEN
    7777            reformaop = "once"
    7878        END IF
    7979       
    80         IF (op.EQ."t_max(X)") THEN
     80        IF (op=="t_max(X)") THEN
    8181            reformaop = "maximum"
    8282        END IF
    8383       
    84         IF (op.EQ."t_min(X)") THEN
     84        IF (op=="t_min(X)") THEN
    8585            reformaop = "minimum"
    8686        END IF
     
    604604    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    605605    SUBROUTINE wxios_add_field(fieldname, fieldgroup, fieldlongname, fieldunit)
    606         USE netcdf, only: nf90_fill_real
     606        USE lmdz_netcdf, only: nf90_fill_real
    607607
    608608        IMPLICIT NONE
     
    621621        def = nf90_fill_real
    622622       
    623         IF (fieldunit .EQ. " ") THEN
     623        IF (fieldunit == " ") THEN
    624624            newunit = "-"
    625625        ELSE
     
    666666       
    667667        ! Ajout Abd pour NMC:
    668         IF (fid.LE.6) THEN
     668        IF (fid<=6) THEN
    669669          axis_id="presnivs"
    670670        ELSE
     
    682682       
    683683        !On selectionne le bon groupe de champs:
    684         IF (fdim.EQ.2) THEN
     684        IF (fdim==2) THEN
    685685          CALL xios_get_handle("fields_2D", fieldgroup)
    686686        ELSE
     
    726726            CALL xios_set_attr(field, level=field_level, enabled=.TRUE.)
    727727           
    728             IF (fdim.EQ.2) THEN
     728            IF (fdim==2) THEN
    729729                !Si c'est un champ 2D:
    730730                IF (prt_level >= 10) THEN
  • LMDZ6/trunk/libf/phylmd/Dust/condsurfc.F

    r5073 r5075  
    44     .                     lmt_omnat)
    55      USE dimphy
     6      USE lmdz_netcdf, ONLY: nf_close,nf_noerr,nf_inq_varid,nf_open,nf_nowrite,nf90_get_var
    67      IMPLICIT none
    78!
     
    1011!
    1112      INCLUDE "dimensions.h"
    12       INCLUDE "netcdf.inc"
    13      
     13
    1414      REAL lmt_bcff(klon), lmt_bcbb(klon),lmt_bc_penner(klon)
    1515      REAL lmt_omff(klon), lmt_ombb(klon)
  • LMDZ6/trunk/libf/phylmd/Dust/condsurfc_new.F

    r4593 r5075  
    66      USE mod_phys_lmdz_para
    77      USE dimphy
     8      USE lmdz_netcdf, ONLY:nf90_get_var,nf_close,nf_noerr,nf_inq_varid,nf_open,nf_nowrite
    89      IMPLICIT none
    910c
     
    1213c
    1314      INCLUDE "dimensions.h"
    14       INCLUDE "netcdf.inc"
    15      
     15
    1616      REAL lmt_bcff(klon), lmt_bcnff(klon), lmt_bcba(klon)
    1717      REAL lmt_omff(klon), lmt_omnff(klon), lmt_ombb(klon)
     
    3636c
    3737!      IF (jour.LT.0 .OR. jour.GT.(366-1)) THEN
    38       IF (jour.LT.0 .OR. jour.GT.366) THEN
     38      IF (jour<0 .OR. jour>366) THEN
    3939         PRINT*,'Le jour demande n est pas correcte:', jour
    4040         print *,'JE: FORCED TO CONTINUE (emissions have
     
    5858!
    5959      ierr = NF_OPEN ("carbon_emissions.nc", NF_NOWRITE, nid1)
    60       if (ierr.ne.NF_NOERR) then
     60      if (ierr/=NF_NOERR) then
    6161        write(6,*)' Pb d''ouverture du fichier limitbc.nc'
    6262        write(6,*)' ierr = ', ierr
     
    6767!
    6868      ierr = NF_INQ_VARID (nid1, "BCFF", nvarid)
    69       ierr = NF_GET_VARA_DOUBLE (nid1, nvarid, debut, epais,
    70      .  lmt_bcff_glo)
    71       IF (ierr .NE. NF_NOERR) THEN
     69      ierr = nf90_get_var (nid1, nvarid, lmt_bcff_glo, debut, epais)
     70      IF (ierr /= NF_NOERR) THEN
    7271         PRINT*, 'Pb de lecture pour les sources BC'
    7372         CALL exit(1)
     
    7978!
    8079      ierr = NF_INQ_VARID (nid1, "BCNFF", nvarid)
    81       ierr = NF_GET_VARA_DOUBLE (nid1, nvarid, debut, epais,
    82      .    lmt_bcnff_glo)
    83       IF (ierr .NE. NF_NOERR) THEN
     80      ierr = nf90_get_var (nid1, nvarid, lmt_bcnff_glo, debut, epais)
     81      IF (ierr /= NF_NOERR) THEN
    8482         PRINT*, 'Pb de lecture pour les sources BC'
    8583         CALL exit(1)
     
    8987!
    9088      ierr = NF_INQ_VARID (nid1, "BCBBL", nvarid)
    91       ierr = NF_GET_VARA_DOUBLE (nid1, nvarid, debut, epais,
    92      .  lmt_bcbbl_glo)
    93       IF (ierr .NE. NF_NOERR) THEN
     89      ierr = nf90_get_var (nid1, nvarid, lmt_bcbbl_glo, debut, epais)
     90      IF (ierr /= NF_NOERR) THEN
    9491         PRINT*, 'Pb de lecture pour les sources BC low'
    9592         CALL exit(1)
     
    9996!
    10097      ierr = NF_INQ_VARID (nid1, "BCBBH", nvarid)
    101       ierr = NF_GET_VARA_DOUBLE (nid1, nvarid, debut, epais,
    102      .      lmt_bcbbh_glo)
    103       IF (ierr .NE. NF_NOERR) THEN
     98      ierr = nf90_get_var (nid1, nvarid, lmt_bcbbh_glo, debut, epais)
     99      IF (ierr /= NF_NOERR) THEN
    104100         PRINT*, 'Pb de lecture pour les sources BC high'
    105101         CALL exit(1)
     
    109105!
    110106      ierr = NF_INQ_VARID (nid1, "BCBA", nvarid)
    111       ierr = NF_GET_VARA_DOUBLE (nid1, nvarid, debut, epais,
    112      .   lmt_bcba_glo)
    113       IF (ierr .NE. NF_NOERR) THEN
     107      ierr = nf90_get_var (nid1, nvarid, lmt_bcba_glo, debut, epais)
     108      IF (ierr /= NF_NOERR) THEN
    114109         PRINT*, 'Pb de lecture pour les sources BC'
    115110         CALL exit(1)
     
    125120!
    126121      ierr = NF_INQ_VARID (nid1, "OMFF", nvarid)
    127       ierr = NF_GET_VARA_DOUBLE (nid1, nvarid, debut, epais,
    128      .  lmt_omff_glo)
    129       IF (ierr .NE. NF_NOERR) THEN
     122      ierr = nf90_get_var (nid1, nvarid, lmt_omff_glo, debut, epais)
     123      IF (ierr /= NF_NOERR) THEN
    130124         PRINT*, 'Pb de lecture pour les sources OM'
    131125         CALL exit(1)
     
    135129!
    136130      ierr = NF_INQ_VARID (nid1, "OMNFF", nvarid)
    137       ierr = NF_GET_VARA_DOUBLE (nid1, nvarid, debut, epais,
    138      .   lmt_omnff_glo)
    139       IF (ierr .NE. NF_NOERR) THEN
     131      ierr = nf90_get_var (nid1, nvarid, lmt_omnff_glo, debut, epais)
     132      IF (ierr /= NF_NOERR) THEN
    140133         PRINT*, 'Pb de lecture pour les sources OM'
    141134         CALL exit(1)
     
    145138!
    146139      ierr = NF_INQ_VARID (nid1, "OMBBL", nvarid)
    147       ierr = NF_GET_VARA_DOUBLE (nid1, nvarid, debut, epais,
    148      .  lmt_ombbl_glo)
    149       IF (ierr .NE. NF_NOERR) THEN
     140      ierr = nf90_get_var (nid1, nvarid, lmt_ombbl_glo, debut, epais)
     141      IF (ierr /= NF_NOERR) THEN
    150142         PRINT*, 'Pb de lecture pour les sources OM low'
    151143         CALL exit(1)
     
    155147!
    156148      ierr = NF_INQ_VARID (nid1, "OMBBH", nvarid)
    157       ierr = NF_GET_VARA_DOUBLE (nid1, nvarid, debut, epais,
    158      .  lmt_ombbh_glo)
    159       IF (ierr .NE. NF_NOERR) THEN
     149      ierr = nf90_get_var (nid1, nvarid, lmt_ombbh_glo, debut, epais)
     150      IF (ierr /= NF_NOERR) THEN
    160151         PRINT*, 'Pb de lecture pour les sources OM high'
    161152         CALL exit(1)
     
    165156!
    166157      ierr = NF_INQ_VARID (nid1, "OMBA", nvarid)
    167       ierr = NF_GET_VARA_DOUBLE (nid1, nvarid, debut, epais,
    168      .   lmt_omba_glo)
    169       IF (ierr .NE. NF_NOERR) THEN
     158      ierr = nf90_get_var (nid1, nvarid, lmt_omba_glo, debut, epais)
     159      IF (ierr /= NF_NOERR) THEN
    170160         PRINT*, 'Pb de lecture pour les sources OM ship'
    171161         CALL exit(1)
     
    175165!
    176166      ierr = NF_INQ_VARID (nid1, "TERP", nvarid)
    177       ierr = NF_GET_VARA_DOUBLE (nid1, nvarid, debut, epais,
    178      .  lmt_terp_glo)
    179       IF (ierr .NE. NF_NOERR) THEN
     167      ierr = nf90_get_var (nid1, nvarid, lmt_terp_glo, debut, epais)
     168      IF (ierr /= NF_NOERR) THEN
    180169         PRINT*, 'Pb de lecture pour les sources Terpene'
    181170         CALL exit(1)
  • LMDZ6/trunk/libf/phylmd/Dust/condsurfs.F

    r5073 r5075  
    44     .                     lmt_dmsbio, lmt_h2sbio, lmt_dms, lmt_dmsconc)
    55       USE dimphy
     6       USE lmdz_netcdf, ONLY:nf_close,nf_noerr,nf_inq_varid,nf_open,nf_nowrite,nf90_get_var
    67      IMPLICIT none
    78c
     
    1011c
    1112      INCLUDE "dimensions.h"
    12       INCLUDE "netcdf.inc"
    1313c
    1414      REAL lmt_so2h(klon), lmt_so2b(klon), lmt_so2bb(klon)
  • LMDZ6/trunk/libf/phylmd/Dust/condsurfs_new.F

    r4593 r5075  
    99      USE mod_phys_lmdz_para
    1010      USE dimphy
     11      USE lmdz_netcdf, ONLY: nf90_get_var,nf_inq_varid,nf_close,nf_noerr,nf_open,nf_nowrite
    1112      IMPLICIT none
    1213c
     
    1516c
    1617      INCLUDE "dimensions.h"
    17       INCLUDE "netcdf.inc"
    1818c
    1919      REAL lmt_so2b(klon), lmt_so2h(klon), lmt_so2nff(klon)
     
    4040      INTEGER debut(2),epais(2)
    4141c
    42       IF (jour.LT.0 .OR. jour.GT.(366-1)) THEN
     42      IF (jour<0 .OR. jour>(366-1)) THEN
    4343         PRINT*,'Le jour demande n est pas correcte:', jour
    4444         print *,'JE: FORCED TO CONTINUE (emissions have
     
    6262!
    6363      ierr = NF_OPEN ("sulphur_emissions_antro.nc", NF_NOWRITE, nid)
    64       if (ierr.ne.NF_NOERR) then
     64      if (ierr/=NF_NOERR) then
    6565        write(6,*)' Pb d''ouverture du fichier sulphur_emissions_antro'
    6666        write(6,*)' ierr = ', ierr
     
    7272!
    7373      ierr = NF_INQ_VARID (nid, "SO2FF_LOW", nvarid)
    74       ierr = NF_GET_VARA_DOUBLE (nid, nvarid, debut, epais,lmt_so2b_glo)
    75       IF (ierr .NE. NF_NOERR) THEN
     74      ierr = nf90_get_var(nid, nvarid, lmt_so2b_glo, debut, epais)
     75      IF (ierr /= NF_NOERR) THEN
    7676        PRINT*, 'Pb de lecture pour les sources so2 low'
    7777        print *,'JE klon, jour, debut ,epais ',klon_glo,jour,debut,epais
     
    8484!
    8585      ierr = NF_INQ_VARID (nid, "SO2FF_HIGH", nvarid)
    86       ierr = NF_GET_VARA_DOUBLE (nid, nvarid, debut, epais,lmt_so2h_glo)
    87       IF (ierr .NE. NF_NOERR) THEN
     86      ierr = nf90_get_var(nid, nvarid, lmt_so2h_glo, debut, epais)
     87      IF (ierr /= NF_NOERR) THEN
    8888        PRINT*, 'Pb de lecture pour les sources so2 high'
    8989        CALL exit(1)
     
    9393!
    9494      ierr = NF_INQ_VARID (nid, "SO2BBH", nvarid)
    95       ierr = NF_GET_VARA_DOUBLE (nid, nvarid, debut,
    96      . epais, lmt_so2bb_h_glo)
    97       IF (ierr .NE. NF_NOERR) THEN
     95      ierr = nf90_get_var(nid, nvarid,  lmt_so2bb_h_glo, debut, epais)
     96      IF (ierr /= NF_NOERR) THEN
    9897        PRINT*, 'Pb de lecture pour les sources so2 BB high'
    9998        CALL exit(1)
     
    103102!
    104103      ierr = NF_INQ_VARID (nid, "SO2BBL", nvarid)
    105       ierr = NF_GET_VARA_DOUBLE (nid, nvarid, debut,
    106      . epais, lmt_so2bb_l_glo)
    107       IF (ierr .NE. NF_NOERR) THEN
     104      ierr = nf90_get_var(nid, nvarid,  lmt_so2bb_l_glo, debut, epais)
     105      IF (ierr /= NF_NOERR) THEN
    108106        PRINT*, 'Pb de lecture pour les sources so2 BB low'
    109107        CALL exit(1)
     
    113111!
    114112      ierr = NF_INQ_VARID (nid, "SO2BA", nvarid)
    115       ierr = NF_GET_VARA_DOUBLE (nid, nvarid, debut,epais,lmt_so2ba_glo)
    116       IF (ierr .NE. NF_NOERR) THEN
     113      ierr = nf90_get_var(nid, nvarid, lmt_so2ba_glo, debut, epais)
     114      IF (ierr /= NF_NOERR) THEN
    117115        PRINT*, 'Pb de lecture pour les sources so2 ship'
    118116        CALL exit(1)
     
    122120!
    123121      ierr = NF_INQ_VARID (nid, "SO2NFF", nvarid)
    124       ierr = NF_GET_VARA_DOUBLE (nid, nvarid, debut, epais,
    125      .  lmt_so2nff_glo)
    126       IF (ierr .NE. NF_NOERR) THEN
     122      ierr = nf90_get_var(nid, nvarid, lmt_so2nff_glo, debut, epais)
     123      IF (ierr /= NF_NOERR) THEN
    127124        PRINT*, 'Pb de lecture pour les sources so2 non FF'
    128125        CALL exit(1)
     
    135132!=======================================================================
    136133      ierr = NF_OPEN ("sulphur_emissions_nat.nc", NF_NOWRITE, nid)
    137       if (ierr.ne.NF_NOERR) then
     134      if (ierr/=NF_NOERR) then
    138135        write(6,*)' Pb d''ouverture du fichier sulphur_emissions_nat'
    139136        write(6,*)' ierr = ', ierr
     
    144141c
    145142      ierr = NF_INQ_VARID (nid, "DMSB", nvarid)
    146       ierr = NF_GET_VARA_DOUBLE (nid, nvarid,debut,epais,lmt_dmsbio_glo)
    147       IF (ierr .NE. NF_NOERR) THEN
     143      ierr = nf90_get_var(nid, nvarid, lmt_dmsbio_glo, debut, epais)
     144      IF (ierr /= NF_NOERR) THEN
    148145         PRINT*, 'Pb de lecture pour les sources dms bio'
    149146         CALL exit(1)
     
    153150c
    154151      ierr = NF_INQ_VARID (nid, "H2SB", nvarid)
    155       ierr = NF_GET_VARA_DOUBLE (nid, nvarid,debut,epais,lmt_h2sbio_glo)
    156       IF (ierr .NE. NF_NOERR) THEN
     152      ierr = nf90_get_var(nid, nvarid, lmt_h2sbio_glo, debut, epais)
     153      IF (ierr /= NF_NOERR) THEN
    157154         PRINT*, 'Pb de lecture pour les sources h2s bio'
    158155         CALL exit(1)
     
    161158c Ocean surface concentration of dms (emissions are computed later)
    162159c
    163       IF (flag_dms.EQ.4) THEN
     160      IF (flag_dms==4) THEN
    164161c
    165162      ierr = NF_INQ_VARID (nid, "DMSC2", nvarid)
    166       ierr = NF_GET_VARA_DOUBLE (nid,nvarid,debut,epais,lmt_dmsconc_glo)
    167       IF (ierr .NE. NF_NOERR) THEN
     163      ierr = nf90_get_var(nid, nvarid, lmt_dmsconc_glo, debut, epais)
     164      IF (ierr /= NF_NOERR) THEN
    168165         PRINT*, 'Pb de lecture pour les sources dms conc 2'
    169166         CALL exit(1)
     
    190187      print *,' Jour = ',jour
    191188      ierr = NF_OPEN ("sulphur_emissions_volc.nc", NF_NOWRITE, nid)
    192       if (ierr.ne.NF_NOERR) then
     189      if (ierr/=NF_NOERR) then
    193190        write(6,*)' Pb d''ouverture du fichier sulphur_emissions_volc'
    194191        write(6,*)' ierr = ', ierr
     
    200197!      ierr = NF_INQ_VARID (nid, "VOLC", nvarid)
    201198      ierr = NF_INQ_VARID (nid, "flx_volc_cont", nvarid)
    202       ierr = NF_GET_VARA_DOUBLE (nid, nvarid, debut, epais,
    203      .                           lmt_so2volc_cont_glo)
    204       IF (ierr .NE. NF_NOERR) THEN
     199      ierr = nf90_get_var(nid, nvarid, lmt_so2volc_cont_glo, debut, epais)
     200      IF (ierr /= NF_NOERR) THEN
    205201         PRINT*, 'Pb de lecture pour les sources so2 volcan (cont)'
    206202         CALL exit(1)
     
    214210!      ierr = NF_INQ_VARID (nid, "ALTI", nvarid)
    215211      ierr = NF_INQ_VARID (nid, "flx_volc_altcont", nvarid)
    216       ierr = NF_GET_VARA_DOUBLE (nid, nvarid, debut, epais,
    217      .                           lmt_altvolc_cont_glo)
    218       IF (ierr .NE. NF_NOERR) THEN
     212      ierr = nf90_get_var(nid, nvarid, lmt_altvolc_cont_glo, debut, epais)
     213      IF (ierr /= NF_NOERR) THEN
    219214         PRINT*, 'Pb de lecture pour les altitudes volcan (cont)'
    220215         CALL exit(1)
     
    224219c
    225220      ierr = NF_INQ_VARID (nid, "flx_volc_expl", nvarid)
    226       ierr = NF_GET_VARA_DOUBLE (nid, nvarid, debut, epais,
    227      .                           lmt_so2volc_expl_glo)
    228       IF (ierr .NE. NF_NOERR) THEN
     221      ierr = nf90_get_var(nid, nvarid, lmt_so2volc_expl_glo, debut, epais)
     222      IF (ierr /= NF_NOERR) THEN
    229223         PRINT*, 'Pb de lecture pour les sources so2 volcan (expl)'
    230224         CALL exit(1)
     
    237231c
    238232      ierr = NF_INQ_VARID (nid, "flx_volc_altexpl", nvarid)
    239       ierr = NF_GET_VARA_DOUBLE (nid, nvarid, debut, epais,
    240      .                           lmt_altvolc_expl_glo)
    241       IF (ierr .NE. NF_NOERR) THEN
     233      ierr = nf90_get_var(nid, nvarid, lmt_altvolc_expl_glo, debut, epais)
     234      IF (ierr /= NF_NOERR) THEN
    242235         PRINT*, 'Pb de lecture pour les altitudes volcan'
    243236         CALL exit(1)
  • LMDZ6/trunk/libf/phylmd/Dust/phys_output_write_spl_mod.F90

    r5024 r5075  
    390390    USE ioipsl, ONLY: histend, histsync
    391391    USE iophy, ONLY: set_itau_iophy, histwrite_phy
    392     USE netcdf, ONLY: nf90_fill_real
     392    USE lmdz_netcdf, ONLY: nf90_fill_real
    393393    ! ug Pour les sorties XIOS
    394394    USE lmdz_xios, ONLY: xios_update_calendar, using_xios
  • LMDZ6/trunk/libf/phylmd/Dust/phytracr_spl_mod.F90

    r4618 r5075  
    14411441       call abort_gcm('phytracr_mod', 'pb in ok_chimdust 1 SCDU',1)
    14421442          endif
    1443           if ( (id_codu .le. 0) .or. ( id_fine.le.0)  ) then 
     1443          if ( (id_codu <= 0) .or. ( id_fine<=0)  ) then
    14441444          call abort_gcm('phytracr_mod', 'pb in ok_chimdust 1',1)
    14451445          endif
     
    24372437      ENDDO
    24382438      ENDDO
    2439       IF (iflag_conv.EQ.2) THEN
     2439      IF (iflag_conv==2) THEN
    24402440! Tiedke
    24412441      CALL cltrac_spl(pdtphys,coefh,yu1,yv1,t_seri,tmp_var,  &
    24422442                 aux_var2,paprs,pplay,aux_var3)
    24432443
    2444       ELSE IF (iflag_conv.GE.3) THEN
     2444      ELSE IF (iflag_conv>=3) THEN
    24452445!KE
    24462446      CALL cltrac(pdtphys, coefh,t_seri,tmp_var,aux_var2,paprs,pplay,  &
     
    24942494
    24952495
    2496       IF (iflag_conv.GE.3) THEN
     2496      IF (iflag_conv>=3) THEN
    24972497
    24982498      IF (logitime) THEN
     
    27862786
    27872787
    2788       IF (iflag_conv.EQ.2) THEN
     2788      IF (iflag_conv==2) THEN
    27892789
    27902790      IF (logitime) THEN
     
    28392839      print *,'iflag_conv bef incloud',iflag_conv
    28402840
    2841         IF (iflag_conv.EQ.2) THEN
     2841        IF (iflag_conv==2) THEN
    28422842! Tiedke
    28432843      CALL incloud_scav(.false.,qmin,qmax,masse,henry,kk,prfl,          &
     
    28772877!     .                                  his_dhbclsc,his_dhbccon,tr_seri)
    28782878
    2879         IF (iflag_conv.EQ.2) THEN
     2879        IF (iflag_conv==2) THEN
    28802880! Tiedke
    28812881
     
    29912991!     .                                                 dtrconv,tr_seri)
    29922992! -------------------------------------------------------------     
    2993         IF (iflag_conv.EQ.2) THEN
     2993        IF (iflag_conv==2) THEN
    29942994! Tiedke
    29952995         CALL trconvect(pplay,t_seri,pdtphys,pmfu,pmfd,pen_u,pde_u,  &
     
    30003000         ENDDO
    30013001
    3002         ELSE IF (iflag_conv.GE.3) THEN
     3002        ELSE IF (iflag_conv>=3) THEN
    30033003! KE
    30043004         print *,'JE: KE in phytracr_spl'
     
    31643164
    31653165
    3166        IF (iflag_conv.GE.3) THEN
     3166       IF (iflag_conv>=3) THEN
    31673167       IF (logitime) THEN
    31683168       CALL SYSTEM_CLOCK(COUNT=clock_start)
     
    31953195       ql_incl = ql_incloud_ref
    31963196! choix du lessivage
    3197       IF (iflag_lscav .EQ. 3 .OR. iflag_lscav .EQ. 4) THEN
     3197      IF (iflag_lscav == 3 .OR. iflag_lscav == 4) THEN
    31983198      !IF (.false.) THEN  ! test #DFB (Binta) sans lsc_scav_spl
    31993199        print *,'JE iflag_lscav',iflag_lscav
     
    33623362      CALL satellite_out_spla(jD_cur,jH_cur,pdtphys,rlat,rlon,   &
    33633363                              masque_aqua_cur, masque_terra_cur )
    3364       IF (jH_cur-pdtphys/86400. .LT. 0.) THEN
     3364      IF (jH_cur-pdtphys/86400. < 0.) THEN
    33653365       !new utc day: put in 0 everything
    33663366!JE20150518<<
     
    34703470      ENDDO
    34713471
    3472       IF (jH_cur+pdtphys/86400. .GE. 1.) THEN 
     3472      IF (jH_cur+pdtphys/86400. >= 1.) THEN
    34733473!          print *,'last step of the day'
    34743474          DO i=1,klon
    3475                IF (masque_aqua(i).GT. 0) THEN
     3475               IF (masque_aqua(i)> 0) THEN
    34763476                   aod550_aqua(i)=aod550_aqua(i)/masque_aqua(i)
    34773477                   aod670_aqua(i)=aod670_aqua(i)/masque_aqua(i)
     
    35063506                   aod865_dustsco_aqua(i)= -999.
    35073507               ENDIF
    3508                IF (masque_terra(i).GT. 0) THEN
     3508               IF (masque_terra(i)> 0) THEN
    35093509                   aod550_terra(i)=aod550_terra(i)/masque_terra(i)
    35103510                   aod670_terra(i)=aod670_terra(i)/masque_terra(i)
     
    36353635      fluxss(:)=0.0
    36363636      DO i=1, klon
    3637          IF (iregion_ind(i).GT.0) THEN           ! LAND
     3637         IF (iregion_ind(i)>0) THEN           ! LAND
    36383638           ! SULFUR EMISSIONS
    36393639           fluxh2sff(i)= (lmt_so2ff_l(i)+lmt_so2ff_h(i))*frach2sofso2*  &       
     
    36563656           fluxff(i)=fluxbcff(i)+fluxomff(i)
    36573657         ENDIF
    3658          IF (iregion_bb(i).GT.0) THEN           ! LAND
     3658         IF (iregion_bb(i)>0) THEN           ! LAND
    36593659           ! SULFUR EMISSIONS
    36603660           fluxso2bb(i) =scale_param_bb(iregion_bb(i)) * fracso2emis *  &
     
    45154515      ENDIF
    45164516
    4517       IF (test_sca .EQ. 0 ) THEN
     4517      IF (test_sca == 0 ) THEN
    45184518        ! READ file!!
    45194519        call read_scalenc(filescaleparams,paramname_ind,            &
     
    45564556
    45574557      jH_sca=jH_sca+pdtphys/(24.*3600.)
    4558       IF (jH_sca.GT.(sca_resol)/24.) THEN
     4558      IF (jH_sca>(sca_resol)/24.) THEN
    45594559          test_sca=0
    45604560          jH_sca=jH_ini
     
    45684568      USE mod_grid_phy_lmdz
    45694569      USE mod_phys_lmdz_para
     4570      USE lmdz_netcdf, ONLY:nf_open,nf_close,nf_inq_varid,nf_nowrite,nf_noerr,nf90_get_var
    45704571      IMPLICIT NONE
    4571 
    4572       include "netcdf.inc"
    45734572
    45744573      CHARACTER*800 filescaleparams
     
    45894588          !nci=NCOPN(trim(adjustl(filescaleparams)),NCNOWRIT,rcode)
    45904589         ierr = NF_OPEN (trim(adjustl(filescaleparams)),NF_NOWRITE, nid)
    4591           if (ierr .EQ. NF_NOERR) THEN
     4590          if (ierr == NF_NOERR) THEN
    45924591          debutread=step_sca
    45934592          countread=1
     
    45984597            print *,varname
    45994598            ierr = NF_INQ_VARID (nid,trim(adjustl(varname)), nvarid)
    4600             ierr = NF_GET_VARA_DOUBLE (nid, nvarid, debutread,          &
    4601                          countread, auxreal)
    4602             IF (ierr .NE. NF_NOERR) THEN
     4599            ierr = nf90_get_var (nid, nvarid, auxreal, debutread, countread)
     4600            IF (ierr /= NF_NOERR) THEN
    46034601             PRINT*, 'Pb de lecture pour modvalues'
    46044602       print *,'JE  scale_var, step_sca',trim(adjustl(varname)),step_sca
  • LMDZ6/trunk/libf/phylmd/Dust/read_dust.F

    r5073 r5075  
    33      USE mod_grid_phy_lmdz
    44      USE mod_phys_lmdz_para
     5      USE lmdz_netcdf, ONLY:nf90_get_var
    56      IMPLICIT NONE
    67c
    78      INCLUDE "dimensions.h"
    89      INCLUDE "paramet.h"
    9       INCLUDE "netcdf.inc"
    1010c
    1111      INTEGER step, nbjour
     
    4545c
    4646      start(3)=step
    47 c
    48 !      status=NF_GET_VARA_DOUBLE(ncid1,varid1,start,count,dust_nc)
     47
    4948      status=nf90_get_var(ncid1,varid1,dust_nc_glo,start,count)
    50 c
     49
    5150!      call correctbid(iim,jjp1,dust_nc)
    5251      call correctbid(nbp_lon,nbp_lat,dust_nc_glo)
  • LMDZ6/trunk/libf/phylmd/Dust/read_surface.F90

    r5073 r5075  
    1010       USE mod_phys_lmdz_para
    1111       USE iophy
    12 !       USE netcdf
     12       USE lmdz_netcdf, ONLY:nf_inq_varid,nf_noerr,nf90_get_var
    1313       IMPLICIT NONE
    1414
    15        INCLUDE "netcdf.inc"
    1615       INCLUDE "dimensions.h"
    1716       INCLUDE "paramet.h"
  • LMDZ6/trunk/libf/phylmd/Dust/read_vent.F

    r5073 r5075  
    33      USE mod_grid_phy_lmdz
    44      USE mod_phys_lmdz_para
     5      USE lmdz_netcdf, ONLY: nf90_get_var
    56!      USE write_field_phy
    67      IMPLICIT NONE
     
    89c       INCLUDE "dimphy.h"
    910      INCLUDE "paramet.h"
    10       INCLUDE "netcdf.inc"
    1111c
    1212      INTEGER step, nbjour
  • LMDZ6/trunk/libf/phylmd/StratAer/interp_sulf_input.F90

    r4625 r5075  
    66  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
    77                      nf95_inq_varid, nf95_inquire_dimension, nf95_open
    8   USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
     8  USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
    99
    1010  USE mod_grid_phy_lmdz
  • LMDZ6/trunk/libf/phylmd/StratAer/stratH2O_methox.F90

    r4755 r5075  
    88  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
    99                      nf95_inq_varid, nf95_inquire_dimension, nf95_open
    10   USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
     10  USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
    1111
    1212  USE mod_grid_phy_lmdz
     
    7979!
    8080 
    81   IF (debutphy .OR. mth_cur .NE. mth_pre) THEN
     81  IF (debutphy .OR. mth_cur /= mth_pre) THEN
    8282     
    8383!--preparation of global fields
  • LMDZ6/trunk/libf/phylmd/condsurf.F90

    r5073 r5075  
    77  USE indice_sol_mod
    88  USE time_phylmdz_mod, ONLY: annee_ref
    9   USE lmdz_netcdf
     9  USE lmdz_netcdf, ONLY: nf90_get_var,nf_open,nf_inq_varid,nf_noerr,nf_close,nf_nowrite
    1010  IMPLICIT NONE
    1111
  • LMDZ6/trunk/libf/phylmd/create_etat0_unstruct_mod.F90

    r4856 r5075  
    2323  SUBROUTINE init_create_etat0_unstruct
    2424  USE lmdz_xios
    25   USE netcdf
     25  USE lmdz_netcdf, ONLY: NF90_NOWRITE,nf90_close,nf90_noerr,nf90_open
    2626  USE mod_phys_lmdz_para
    2727  IMPLICIT NONE
     
    126126      CALL xios_recv_field("qs",qsol_mpi)
    127127      CALL xios_recv_field("mask",zmasq_mpi)
    128       IF (landice_opt .LT. 2) CALL xios_recv_field("landice",lic_mpi)
     128      IF (landice_opt < 2) CALL xios_recv_field("landice",lic_mpi)
    129129    ENDIF
    130130    CALL scatter_omp(tsol_mpi,tsol)
    131131    CALL scatter_omp(qsol_mpi,qsol)
    132132    CALL scatter_omp(zmasq_mpi,zmasq)
    133     IF (landice_opt .LT. 2) CALL scatter_omp(lic_mpi,lic)
     133    IF (landice_opt < 2) CALL scatter_omp(lic_mpi,lic)
    134134
    135135    radsol(:)   = 0.0
     
    143143
    144144    pctsrf(:,:) = 0
    145     IF (landice_opt .LT. 2) THEN
     145    IF (landice_opt < 2) THEN
    146146       pctsrf(:,is_lic)=lic
    147147       WHERE(pctsrf(:,is_lic)<EPSFRA) pctsrf(:,is_lic)=0.
     
    180180  !--- The ocean and sea-ice fractions are not changed.
    181181  !--- This option is only available if landice_opt<2.   
    182   IF (landice_opt .LT. 2) THEN
     182  IF (landice_opt < 2) THEN
    183183     no_ter_antartique=.FALSE.
    184184     CALL getin_p('no_ter_antartique',no_ter_antartique)
  • LMDZ6/trunk/libf/phylmd/dyn1d/1DUTILS.h

    r4650 r5075  
    673673      USE logic_mod, ONLY: fxyhypb, ysinus
    674674      USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn
     675      USE lmdz_netcdf, ONLY:nf_open,nf_write,nf_noerr
    675676
    676677      IMPLICIT NONE
     
    682683      include "dimensions.h"
    683684!!#include "control.h"
    684       include "netcdf.inc"
    685685
    686686!   Arguments:
     
    820820      USE logic_mod, ONLY: fxyhypb, ysinus
    821821      USE temps_mod, ONLY: annee_ref,day_end,day_ref,itau_dyn,itaufin
     822      USE lmdz_netcdf, ONLY:nf_open,nf_write,nf_noerr
    822823
    823824      IMPLICIT NONE
     
    829830      include "dimensions.h"
    830831!!#include "control.h"
    831       include "netcdf.inc"
    832832
    833833!   Arguments:
  • LMDZ6/trunk/libf/phylmd/dyn1d/1D_decl_cases.h

    r4593 r5075  
    1         INCLUDE "netcdf.inc"
    21
    32! Declarations specifiques au cas Toga
  • LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_amma_read.F90

    r5073 r5075  
    11MODULE mod_1D_amma_read
    2 
     2        USE lmdz_netcdf, ONLY: nf90_get_var,nf_open,nf_noerr,nf_open,nf_nowrite,&
     3                nf_inq_dimid,nf_inq_dimlen,nf_strerror,nf_inq_varid
    34!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    45!Declarations specifiques au cas AMMA
     
    67! Option du cas AMMA ou on impose la discretisation verticale (Ap,Bp)
    78        integer nlev_amma, nt_amma
    8 
    99
    1010        integer year_ini_amma, day_ini_amma, mth_ini_amma
     
    5858SUBROUTINE read_1D_cases
    5959      implicit none
    60 
    61       INCLUDE "netcdf.inc"
    6260
    6361      INTEGER nid,rid,ierr
     
    172170
    173171
    174 END MODULE mod_1D_amma_read
    175172!=====================================================================
    176173      subroutine read_amma(nid,nlevel,ntime                          &
     
    180177!program reading forcings of the AMMA case study
    181178      implicit none
    182       INCLUDE "netcdf.inc"
    183179
    184180      integer ntime,nlevel
     
    459455        END
    460456
     457END MODULE mod_1D_amma_read
  • LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_cases_read.F90

    r5073 r5075  
    1 !
    2 ! $Id$
    3 !
    41MODULE mod_1D_cases_read
     2  USE lmdz_netcdf, ONLY: nf_noerr,nf_strerror,nf_inq_varid,nf_inq_dimlen,nf_inq_dimid,&
     3          nf_nowrite,nf_open,nf90_get_var
    54
    65!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    76!Declarations specifiques au cas standard
    87        character*80 :: fich_cas
    9 ! Discr?tisation 
     8! Discr?tisation
    109        integer nlev_cas, nt_cas
    1110
     
    5756        real, allocatable::  q_prof_cas(:)
    5857        real, allocatable::  u_prof_cas(:)
    59         real, allocatable::  v_prof_cas(:)       
     58        real, allocatable::  v_prof_cas(:)
    6059
    6160        real, allocatable::  vitw_prof_cas(:)
     
    8281
    8382        real lat_prof_cas,sens_prof_cas,ts_prof_cas,ustar_prof_cas
    84      
     83
    8584
    8685
     
    8887
    8988SUBROUTINE read_1D_cas
    90       implicit none
    91 
    92       INCLUDE "netcdf.inc"
    9389
    9490      INTEGER nid,rid,ierr
     
    137133!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    138134!profils moyens:
    139         allocate(plev_cas(nlev_cas,nt_cas))       
     135        allocate(plev_cas(nlev_cas,nt_cas))
    140136        allocate(z_cas(nlev_cas,nt_cas))
    141137        allocate(t_cas(nlev_cas,nt_cas),q_cas(nlev_cas,nt_cas),rh_cas(nlev_cas,nt_cas))
     
    204200!profils environnementaux:
    205201        deallocate(plev_cas)
    206        
     202
    207203        deallocate(z_cas)
    208204        deallocate(t_cas,q_cas,rh_cas)
     
    210206        deallocate(u_cas)
    211207        deallocate(v_cas)
    212        
     208
    213209!forcing
    214210        deallocate(ht_cas,vt_cas,dt_cas,dtrad_cas)
     
    257253END SUBROUTINE deallocate_1D_cases
    258254
    259 
    260 END MODULE mod_1D_cases_read
    261 !=====================================================================
     255  !=====================================================================
    262256      subroutine read_cas(nid,nlevel,ntime                          &
    263257     &     ,zz,pp,temp,qv,rh,theta,rv,u,v,ug,vg,w,                   &
     
    266260
    267261!program reading forcing of the case study
    268       implicit none
    269       INCLUDE "netcdf.inc"
    270262
    271263      integer ntime,nlevel
     
    296288      integer var3didin(nbvar3d)
    297289
    298        ierr=NF_INQ_VARID(nid,"zz",var3didin(1)) 
     290       ierr=NF_INQ_VARID(nid,"zz",var3didin(1))
    299291         if(ierr/=NF_NOERR) then
    300292           write(*,*) NF_STRERROR(ierr)
    301293           stop 'lev'
    302294         endif
    303      
    304       ierr=NF_INQ_VARID(nid,"pp",var3didin(2)) 
     295
     296      ierr=NF_INQ_VARID(nid,"pp",var3didin(2))
    305297         if(ierr/=NF_NOERR) then
    306298           write(*,*) NF_STRERROR(ierr)
     
    429421           stop 'advq'
    430422         endif
    431      
     423
    432424      ierr=NF_INQ_VARID(nid,"hq",var3didin(23))
    433425         if(ierr/=NF_NOERR) then
     
    465457           stop 'advr'
    466458         endif
    467      
     459
    468460      ierr=NF_INQ_VARID(nid,"hr",var3didin(29))
    469461         if(ierr/=NF_NOERR) then
     
    531523           stop 'q2'
    532524         endif
    533  
     525
    534526         ierr = nf90_get_var(nid,var3didin(1),zz)
    535527         if(ierr/=NF_NOERR) then
     
    560552         endif
    561553!          write(*,*)'lecture qv ok',qv
    562  
     554
    563555         ierr = nf90_get_var(nid,var3didin(5),rh)
    564556         if(ierr/=NF_NOERR) then
     
    807799
    808800
    809          return 
     801         return
    810802         end subroutine read_cas
    811803!======================================================================
     
    825817     &         ,hq_prof_cas,vq_prof_cas,lat_prof_cas,sens_prof_cas    &
    826818     &         ,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas)
    827          
     819
    828820
    829821        implicit none
     
    834826! day: current julian day (e.g. 717538.2)
    835827! day1: first day of the simulation
    836 ! nt_cas: total nb of data in the forcing 
     828! nt_cas: total nb of data in the forcing
    837829! pdt_cas: total time interval (in sec) between 2 forcing data
    838830!---------------------------------------------------------------------------------------
     
    926918       it_cas1=INT(timeit/pdt_cas)+1
    927919       IF (it_cas1 == nt_cas) THEN
    928        it_cas2=it_cas1 
     920       it_cas2=it_cas1
    929921       ELSE
    930922       it_cas2=it_cas1 + 1
     
    952944
    953945       lat_prof_cas = lat_cas(it_cas2)                                       &
    954      &          -frac*(lat_cas(it_cas2)-lat_cas(it_cas1)) 
     946     &          -frac*(lat_cas(it_cas2)-lat_cas(it_cas1))
    955947       sens_prof_cas = sens_cas(it_cas2)                                     &
    956948     &          -frac*(sens_cas(it_cas2)-sens_cas(it_cas1))
     
    10171009
    10181010!**********************************************************************************************
     1011END MODULE mod_1D_cases_read
  • LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_cases_read2.F90

    r4706 r5075  
    33!
    44MODULE mod_1D_cases_read2
    5 
     5  USE lmdz_netcdf, ONLY: nf90_get_var,nf_noerr,nf_inq_varid,nf_inq_dimlen,nf_strerror,nf_open,&
     6          nf_nowrite,nf_inq_dimid
    67!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    78  !Declarations specifiques au cas standard
     
    8182    implicit none
    8283
    83     INCLUDE "netcdf.inc"
    84 
    8584    INTEGER nid,rid,ierr
    8685    INTEGER ii,jj
     
    9089    ierr = NF_OPEN(fich_cas,NF_NOWRITE,nid)
    9190    print*,'fich_cas,NF_NOWRITE,nid ',fich_cas,NF_NOWRITE,nid
    92     if (ierr.NE.NF_NOERR) then
     91    if (ierr/=NF_NOERR) then
    9392       write(*,*) 'ERROR: GROS Pb opening forcings nc file '
    9493       write(*,*) NF_STRERROR(ierr)
     
    9796    !.......................................................................
    9897    ierr=NF_INQ_DIMID(nid,'lat',rid)
    99     IF (ierr.NE.NF_NOERR) THEN
     98    IF (ierr/=NF_NOERR) THEN
    10099       print*, 'Oh probleme lecture dimension lat'
    101100    ENDIF
     
    104103    !.......................................................................
    105104    ierr=NF_INQ_DIMID(nid,'lon',rid)
    106     IF (ierr.NE.NF_NOERR) THEN
     105    IF (ierr/=NF_NOERR) THEN
    107106       print*, 'Oh probleme lecture dimension lon'
    108107    ENDIF
     
    111110    !.......................................................................
    112111    ierr=NF_INQ_DIMID(nid,'lev',rid)
    113     IF (ierr.NE.NF_NOERR) THEN
     112    IF (ierr/=NF_NOERR) THEN
    114113       print*, 'Oh probleme lecture dimension zz'
    115114    ENDIF
     
    120119    print*,'nid,rid',nid,rid
    121120    nt_cas=0
    122     IF (ierr.NE.NF_NOERR) THEN
     121    IF (ierr/=NF_NOERR) THEN
    123122       stop 'probleme lecture dimension sens'
    124123    ENDIF
     
    192191    implicit none
    193192
    194     INCLUDE "netcdf.inc"
    195 
    196193    INTEGER nid,rid,ierr
    197194    INTEGER ii,jj
     
    201198    ierr = NF_OPEN(fich_cas,NF_NOWRITE,nid)
    202199    print*,'fich_cas,NF_NOWRITE,nid ',fich_cas,NF_NOWRITE,nid
    203     if (ierr.NE.NF_NOERR) then
     200    if (ierr/=NF_NOERR) then
    204201       write(*,*) 'ERROR: GROS Pb opening forcings nc file '
    205202       write(*,*) NF_STRERROR(ierr)
     
    208205    !.......................................................................
    209206    ierr=NF_INQ_DIMID(nid,'lat',rid)
    210     IF (ierr.NE.NF_NOERR) THEN
     207    IF (ierr/=NF_NOERR) THEN
    211208       print*, 'Oh probleme lecture dimension lat'
    212209    ENDIF
     
    215212    !.......................................................................
    216213    ierr=NF_INQ_DIMID(nid,'lon',rid)
    217     IF (ierr.NE.NF_NOERR) THEN
     214    IF (ierr/=NF_NOERR) THEN
    218215       print*, 'Oh probleme lecture dimension lon'
    219216    ENDIF
     
    222219    !.......................................................................
    223220    ierr=NF_INQ_DIMID(nid,'nlev',rid)
    224     IF (ierr.NE.NF_NOERR) THEN
     221    IF (ierr/=NF_NOERR) THEN
    225222       print*, 'Oh probleme lecture dimension nlev'
    226223    ENDIF
     
    230227    ierr=NF_INQ_DIMID(nid,'time',rid)
    231228    nt_cas=0
    232     IF (ierr.NE.NF_NOERR) THEN
     229    IF (ierr/=NF_NOERR) THEN
    233230       stop 'Oh probleme lecture dimension time'
    234231    ENDIF
     
    317314  !**********************************************************************************************
    318315  SUBROUTINE old_read_SCM_cas
    319     use netcdf, only: nf90_get_var
    320316    implicit none
    321317
    322     INCLUDE "netcdf.inc"
    323318    INCLUDE "date_cas.h"
    324319
     
    331326    ierr = NF_OPEN(fich_cas,NF_NOWRITE,nid)
    332327    print*,'fich_cas,NF_NOWRITE,nid ',fich_cas,NF_NOWRITE,nid
    333     if (ierr.NE.NF_NOERR) then
     328    if (ierr/=NF_NOERR) then
    334329       write(*,*) 'ERROR: GROS Pb opening forcings nc file '
    335330       write(*,*) NF_STRERROR(ierr)
     
    338333    !.......................................................................
    339334    ierr=NF_INQ_DIMID(nid,'lat',rid)
    340     IF (ierr.NE.NF_NOERR) THEN
     335    IF (ierr/=NF_NOERR) THEN
    341336       print*, 'Oh probleme lecture dimension lat'
    342337    ENDIF
     
    345340    !.......................................................................
    346341    ierr=NF_INQ_DIMID(nid,'lon',rid)
    347     IF (ierr.NE.NF_NOERR) THEN
     342    IF (ierr/=NF_NOERR) THEN
    348343       print*, 'Oh probleme lecture dimension lon'
    349344    ENDIF
     
    352347    !.......................................................................
    353348    ierr=NF_INQ_DIMID(nid,'lev',rid)
    354     IF (ierr.NE.NF_NOERR) THEN
     349    IF (ierr/=NF_NOERR) THEN
    355350       print*, 'Oh probleme lecture dimension nlev'
    356351    ENDIF
     
    364359    ierr=NF_INQ_DIMID(nid,'time',rid)
    365360    nt_cas=0
    366     IF (ierr.NE.NF_NOERR) THEN
     361    IF (ierr/=NF_NOERR) THEN
    367362       stop 'Oh probleme lecture dimension time'
    368363    ENDIF
     
    533528
    534529
    535 END MODULE mod_1D_cases_read2
    536530!=====================================================================
    537531subroutine read_cas2(nid,nlevel,ntime                          &
     
    541535
    542536  !program reading forcing of the case study
    543   use netcdf, only: nf90_get_var
    544537  implicit none
    545   INCLUDE "netcdf.inc"
    546538
    547539  integer ntime,nlevel
     
    589581  do i=1,nbvar3d
    590582     print *,'Dans read_cas2, on va lire ',var3didin(i),name_var(i)
    591      if(i.LE.35) then
     583     if(i<=35) then
    592584        ierr = NF90_GET_VAR(nid,var3didin(i),resul, count = [1, 1, nlevel, ntime])
    593585        print *,'Dans read_cas2, on a lu ',ierr,var3didin(i),name_var(i)
     
    658650
    659651  !program reading forcing of the case study
    660   use netcdf, only: nf90_get_var
    661652  implicit none
    662   INCLUDE "netcdf.inc"
    663653
    664654  integer ntime,nlevel
     
    711701     else
    712702        !-----------------------------------------------------------------------
    713         if(i.LE.4) then     ! Lecture des coord pression en (nlevelp1,lat,lon)
     703        if(i<=4) then     ! Lecture des coord pression en (nlevelp1,lat,lon)
    714704           ierr = NF90_GET_VAR(nid,var3didin(i),apbp, count = [1, 1, nlevel + 1])
    715705           print *,'read2_cas(apbp), on a lu ',i,name_var(i)
     
    719709           endif
    720710           !-----------------------------------------------------------------------
    721         else if(i.gt.4.and.i.LE.45) then   ! Lecture des variables en (time,nlevel,lat,lon)
     711        else if(i>4.and.i<=45) then   ! Lecture des variables en (time,nlevel,lat,lon)
    722712           ierr = NF90_GET_VAR(nid,var3didin(i),resul, count = [1, 1, nlevel, ntime])
    723713           print *,'read2_cas(resul), on a lu ',i,name_var(i)
     
    727717           endif
    728718           !-----------------------------------------------------------------------
    729         else if (i.gt.45.and.i.LE.51) then   ! Lecture des variables en (time,lat,lon)
     719        else if (i>45.and.i<=51) then   ! Lecture des variables en (time,lat,lon)
    730720           ierr = NF90_GET_VAR(nid,var3didin(i),resul2, count = [1, 1, ntime])
    731721           print *,'read2_cas(resul2), on a lu ',i,name_var(i)
     
    829819
    830820  !program reading forcing of the case study
    831   use netcdf, only: nf90_get_var
    832821  implicit none
    833   INCLUDE "netcdf.inc"
    834822
    835823  integer ntime,nlevel,k,t
     
    888876     else
    889877        !-----------------------------------------------------------------------
    890         if(i.LE.4) then     ! Lecture des coord pression en (nlevelp1,lat,lon)
     878        if(i<=4) then     ! Lecture des coord pression en (nlevelp1,lat,lon)
    891879           ierr = NF90_GET_VAR(nid,var3didin(i),apbp)
    892880           print *,'read2_cas(apbp), on a lu ',i,name_var(i)
     
    896884           endif
    897885           !-----------------------------------------------------------------------
    898         else if(i.gt.4.and.i.LE.12) then   ! Lecture des variables en (time,nlevel,lat,lon)
     886        else if(i>4.and.i<=12) then   ! Lecture des variables en (time,nlevel,lat,lon)
    899887           ierr = NF90_GET_VAR(nid,var3didin(i),resul1)
    900888           print *,'read2_cas(resul1), on a lu ',i,name_var(i)
     
    905893           print*,'Lecture de la variable #i ',i,name_var(i),minval(resul1),maxval(resul1)
    906894           !-----------------------------------------------------------------------
    907         else if(i.gt.12.and.i.LE.54) then   ! Lecture des variables en (time,nlevel,lat,lon)
     895        else if(i>12.and.i<=54) then   ! Lecture des variables en (time,nlevel,lat,lon)
    908896           ierr = NF90_GET_VAR(nid,var3didin(i),resul)
    909897           print *,'read2_cas(resul), on a lu ',i,name_var(i)
     
    914902           print*,'Lecture de la variable #i ',i,name_var(i),minval(resul),maxval(resul)
    915903           !-----------------------------------------------------------------------
    916         else if (i.gt.54.and.i.LE.65) then   ! Lecture des variables en (time,lat,lon)
     904        else if (i>54.and.i<=65) then   ! Lecture des variables en (time,lat,lon)
    917905           ierr = NF90_GET_VAR(nid,var3didin(i),resul2)
    918906           print *,'read2_cas(resul2), on a lu ',i,name_var(i)
     
    11481136
    11491137  it_cas1=INT(timeit/pdt_cas)+1
    1150   IF (it_cas1 .EQ. nt_cas) THEN
     1138  IF (it_cas1 == nt_cas) THEN
    11511139     it_cas2=it_cas1
    11521140  ELSE
     
    11571145  !print *,'it_cas1,it_cas2,time_cas1,time_cas2=',it_cas1,it_cas2,time_cas1,time_cas2
    11581146
    1159   if (it_cas1 .gt. nt_cas) then
     1147  if (it_cas1 > nt_cas) then
    11601148     write(*,*) 'PB-stop: day, day_ju_ini_cas,it_cas1, it_cas2, timeit: '            &
    11611149          ,day,day_ju_ini_cas,it_cas1,it_cas2,timeit
     
    11641152
    11651153  ! time interpolation:
    1166   IF (it_cas1 .EQ. it_cas2) THEN
     1154  IF (it_cas1 == it_cas2) THEN
    11671155     frac=0.
    11681156  ELSE
     
    13631351
    13641352  it_cas1=INT(timeit/pdt_cas)+1
    1365   IF (it_cas1 .EQ. nt_cas) THEN
     1353  IF (it_cas1 == nt_cas) THEN
    13661354     it_cas2=it_cas1
    13671355  ELSE
     
    13731361  !print *,'it_cas1,it_cas2,time_cas1,time_cas2=',it_cas1,it_cas2,time_cas1,time_cas2
    13741362
    1375   if (it_cas1 .gt. nt_cas) then
     1363  if (it_cas1 > nt_cas) then
    13761364     write(*,*) 'PB-stop: day, day_ju_ini_cas,it_cas1, it_cas2, timeit: '            &
    13771365          ,day,day_ju_ini_cas,it_cas1,it_cas2,timeit
     
    13801368
    13811369  ! time interpolation:
    1382   IF (it_cas1 .EQ. it_cas2) THEN
     1370  IF (it_cas1 == it_cas2) THEN
    13831371     frac=0.
    13841372  ELSE
     
    14751463!**********************************************************************************************
    14761464
     1465END MODULE mod_1D_cases_read2
  • LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_cases_read_std.F90

    r4706 r5075  
    33!
    44MODULE mod_1D_cases_read_std
     5  USE lmdz_netcdf, ONLY:nf_noerr,nf_inq_varid,nf_inq_dimid,nf_inq_dimlen,nf_open,nf_nowrite,&
     6          nf_strerror,nf90_get_var
    57
    68!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    8789  !**********************************************************************************************
    8890  SUBROUTINE read_SCM_cas
    89     use netcdf, only: nf90_get_var
    9091    implicit none
    9192
    92     INCLUDE "netcdf.inc"
    9393    INCLUDE "date_cas.h"
    9494
     
    101101    ierr = NF_OPEN(fich_cas,NF_NOWRITE,nid)
    102102    print*,'fich_cas,NF_NOWRITE,nid ',fich_cas,NF_NOWRITE,nid
    103     if (ierr.NE.NF_NOERR) then
     103    if (ierr/=NF_NOERR) then
    104104       write(*,*) 'ERROR: GROS Pb opening forcings nc file '
    105105       write(*,*) NF_STRERROR(ierr)
     
    108108    !.......................................................................
    109109    ierr=NF_INQ_DIMID(nid,'lat',rid)
    110     IF (ierr.NE.NF_NOERR) THEN
     110    IF (ierr/=NF_NOERR) THEN
    111111       print*, 'Oh probleme lecture dimension lat'
    112112    ENDIF
     
    115115    !.......................................................................
    116116    ierr=NF_INQ_DIMID(nid,'lon',rid)
    117     IF (ierr.NE.NF_NOERR) THEN
     117    IF (ierr/=NF_NOERR) THEN
    118118       print*, 'Oh probleme lecture dimension lon'
    119119    ENDIF
     
    122122    !.......................................................................
    123123    ierr=NF_INQ_DIMID(nid,'lev',rid)
    124     IF (ierr.NE.NF_NOERR) THEN
     124    IF (ierr/=NF_NOERR) THEN
    125125       print*, 'Oh probleme lecture dimension nlev'
    126126    ENDIF
     
    134134    ierr=NF_INQ_DIMID(nid,'time',rid)
    135135    nt_cas=0
    136     IF (ierr.NE.NF_NOERR) THEN
     136    IF (ierr/=NF_NOERR) THEN
    137137       stop 'Oh probleme lecture dimension time'
    138138    ENDIF
     
    329329
    330330    !program reading forcing of the case study
    331     use netcdf, only: nf90_get_var
    332331    implicit none
    333     INCLUDE "netcdf.inc"
    334332    INCLUDE "compar1d.h"
    335333
     
    455453          ! Reading variables 1D (N+1) vertical variables (nlevelp1,lat,lon)
    456454          !-----------------------------------------------------------------------
    457           if(i.LE.4) then
     455          if(i<=4) then
    458456             ierr = NF90_GET_VAR(nid,var3didin(i),apbp)
    459457             print *,'read_SCM(apbp), on a lu ',i,name_var(i)
     
    466464             !  Reading 1D (N) vertical varialbes    (nlevel,lat,lon)   
    467465             !-----------------------------------------------------------------------
    468           else if(i.gt.4.and.i.LE.12) then 
     466          else if(i>4.and.i<=12) then
    469467             ierr = NF90_GET_VAR(nid,var3didin(i),resul1)
    470468             print *,'read_SCM(resul1), on a lu ',i,name_var(i)
     
    479477             !  TBD : seems to be the same as above.
    480478             !-----------------------------------------------------------------------
    481           else if(i.gt.12.and.i.LE.61) then
     479          else if(i>12.and.i<=61) then
    482480             ierr = NF90_GET_VAR(nid,var3didin(i),resul)
    483481             print *,'read_SCM(resul), on a lu ',i,name_var(i)
     
    491489             !  Reading 1D time variables (time,lat,lon)
    492490             !-----------------------------------------------------------------------
    493           else if (i.gt.62.and.i.LE.75) then
     491          else if (i>62.and.i<=75) then
    494492             ierr = NF90_GET_VAR(nid,var3didin(i),resul2)
    495493             print *,'read_SCM(resul2), on a lu ',i,name_var(i)
     
    777775
    778776    it_cas1=INT(timeit/pdt_cas)+1
    779     IF (it_cas1 .EQ. nt_cas) THEN
     777    IF (it_cas1 == nt_cas) THEN
    780778       it_cas2=it_cas1
    781779    ELSE
     
    787785    !     print *,'it_cas1,it_cas2,time_cas1,time_cas2=',it_cas1,it_cas2,time_cas1,time_cas2
    788786
    789     if (it_cas1 .gt. nt_cas) then
     787    if (it_cas1 > nt_cas) then
    790788       write(*,*) 'PB-stop: day, day_ju_ini_cas,it_cas1, it_cas2, timeit: '            &
    791789            ,day,day_ju_ini_cas,it_cas1,it_cas2,timeit
     
    794792
    795793    ! time interpolation:
    796     IF (it_cas1 .EQ. it_cas2) THEN
     794    IF (it_cas1 == it_cas2) THEN
    797795       frac=0.
    798796    ELSE
     
    989987    do l = 1, llm
    990988
    991        if (play(l).ge.plev_prof_cas(nlev_cas)) then
     989       if (play(l)>=plev_prof_cas(nlev_cas)) then
    992990
    993991          mxcalc=l
     
    996994          k2=0
    997995
    998           if (play(l).le.plev_prof_cas(1)) then
     996          if (play(l)<=plev_prof_cas(1)) then
    999997
    1000998             do k = 1, nlev_cas-1
    1001                 if (play(l).le.plev_prof_cas(k).and. play(l).gt.plev_prof_cas(k+1)) then
     999                if (play(l)<=plev_prof_cas(k).and. play(l)>plev_prof_cas(k+1)) then
    10021000                   k1=k
    10031001                   k2=k+1
     
    10051003             enddo
    10061004
    1007              if (k1.eq.0 .or. k2.eq.0) then
     1005             if (k1==0 .or. k2==0) then
    10081006                write(*,*) 'PB! k1, k2 = ',k1,k2
    10091007                write(*,*) 'l,play(l) = ',l,play(l)/100
     
    10191017             t_mod_cas(l)= t_prof_cas(k2) - frac*(t_prof_cas(k2)-t_prof_cas(k1))
    10201018             theta_mod_cas(l)= th_prof_cas(k2) - frac*(th_prof_cas(k2)-th_prof_cas(k1))
    1021              if(theta_mod_cas(l).NE.0) t_mod_cas(l)= theta_mod_cas(l)*(play(l)/100000.)**(RD/RCPD)
     1019             if(theta_mod_cas(l)/=0) t_mod_cas(l)= theta_mod_cas(l)*(play(l)/100000.)**(RD/RCPD)
    10221020             thv_mod_cas(l)= thv_prof_cas(k2) - frac*(thv_prof_cas(k2)-thv_prof_cas(k1))
    10231021             thl_mod_cas(l)= thl_prof_cas(k2) - frac*(thl_prof_cas(k2)-thl_prof_cas(k1))
     
    10681066             t_mod_cas(l)= frac1*t_prof_cas(k1) - frac2*t_prof_cas(k2)
    10691067             theta_mod_cas(l)= frac1*th_prof_cas(k1) - frac2*th_prof_cas(k2)
    1070              if(theta_mod_cas(l).NE.0) t_mod_cas(l)= theta_mod_cas(l)*(play(l)/100000.)**(RD/RCPD)
     1068             if(theta_mod_cas(l)/=0) t_mod_cas(l)= theta_mod_cas(l)*(play(l)/100000.)**(RD/RCPD)
    10711069             thv_mod_cas(l)= frac1*thv_prof_cas(k1) - frac2*thv_prof_cas(k2)
    10721070             thl_mod_cas(l)= frac1*thl_prof_cas(k1) - frac2*thl_prof_cas(k2)
     
    11651163    do l = 1, llm+1
    11661164
    1167        if (plev(l).ge.plev_prof_cas(nlev_cas)) then
     1165       if (plev(l)>=plev_prof_cas(nlev_cas)) then
    11681166
    11691167          mxcalc=l
     
    11711169          k2=0
    11721170
    1173           if (plev(l).le.plev_prof_cas(1)) then
     1171          if (plev(l)<=plev_prof_cas(1)) then
    11741172
    11751173             do k = 1, nlev_cas-1
    1176                 if (plev(l).le.plev_prof_cas(k).and. plev(l).gt.plev_prof_cas(k+1)) then
     1174                if (plev(l)<=plev_prof_cas(k).and. plev(l)>plev_prof_cas(k+1)) then
    11771175                   k1=k
    11781176                   k2=k+1
     
    11801178             enddo
    11811179
    1182              if (k1.eq.0 .or. k2.eq.0) then
     1180             if (k1==0 .or. k2==0) then
    11831181                write(*,*) 'PB! k1, k2 = ',k1,k2
    11841182                write(*,*) 'l,plev(l) = ',l,plev(l)/100
  • LMDZ6/trunk/libf/phylmd/dyn1d/old_1DUTILS_read_interp.h

    r4593 r5075  
    146146!program reading forcings of the TWP-ICE experiment
    147147
    148         use netcdf, only: nf90_get_var
     148        use lmdz_netcdf, ONLY: nf_open,nf_nowrite,nf_noerr,nf_strerror,nf_inq_varid,nf90_get_var,&
     149            nf_inq_dimid,nf_inq_dimlen
     150
    149151
    150152      implicit none
    151 
    152       INCLUDE "netcdf.inc"
    153153
    154154      integer ntime,nlevel
     
    492492         subroutine catchaxis(nid,ttm,llm,time,lev,ierr)
    493493
    494          use netcdf, only: nf90_get_var
     494         use lmdz_netcdf, ONLY: nf_open,nf_nowrite,nf_noerr,nf_strerror,nf_inq_varid,nf90_get_var,&
     495            nf_inq_dimid,nf_inq_dimlen
    495496
    496497         implicit none
    497          INCLUDE "netcdf.inc"
    498498         integer nid,ttm,llm
    499499         real*8 time(ttm)
     
    21702170
    21712171
    2172       use netcdf, only: nf90_get_var
     2172      use lmdz_netcdf, ONLY: nf_open,nf_nowrite,nf_noerr,nf_strerror,nf_inq_varid,nf90_get_var,&
     2173            nf_inq_dimid,nf_inq_dimlen
    21732174      implicit none
    2174 
    2175       INCLUDE "netcdf.inc"
    21762175
    21772176      integer ntime,nlevel
     
    23812380!program reading initial profils and forcings of the Dice case study
    23822381
    2383       use netcdf, only: nf90_get_var
     2382      use lmdz_netcdf, ONLY: nf_open,nf_nowrite,nf_noerr,nf_strerror,nf_inq_varid,nf90_get_var,&
     2383            nf_inq_dimid,nf_inq_dimlen
    23842384
    23852385      implicit none
    23862386
    2387       INCLUDE "netcdf.inc"
    23882387      INCLUDE "YOMCST.h"
    23892388
     
    27152714!program reading initial profils and forcings of the Gabls4 case study
    27162715
    2717       use netcdf, only: nf90_get_var
     2716      use lmdz_netcdf, ONLY: nf_open,nf_nowrite,nf_noerr,nf_strerror,nf_inq_varid,nf90_get_var,&
     2717            nf_inq_dimid,nf_inq_dimlen
    27182718
    27192719      implicit none
    2720 
    2721       INCLUDE "netcdf.inc"
    27222720
    27232721      integer ntime,nlevel,nsol
  • LMDZ6/trunk/libf/phylmd/dyn1d/old_1D_decl_cases.h

    r4593 r5075  
    1          INCLUDE "netcdf.inc"
    21
    32! Declarations specifiques au cas Toga
  • LMDZ6/trunk/libf/phylmd/dyn1d/old_lmdz1d.F90

    r4744 r5075  
    4444   USE temps_mod, ONLY: annee_ref, calend, day_end, day_ini, day_ref, &
    4545                        itau_dyn, itau_phy, start_time, year_len
    46    USE phys_cal_mod, ONLY : year_len_phys_cal_mod => year_len
     46   USE phys_cal_mod, ONLY : year_len_phys_cal_mod => year_len
     47   USE mod_1D_cases_read, ONLY: interp_case_time ! used in included old_1D_read_forc_cases.h
     48
    4749
    4850      implicit none
     
    366368      if (forcing_type <=0) THEN
    367369       forcing_les = .true.
    368       elseif (forcing_type .eq.1) THEN
     370      elseif (forcing_type ==1) THEN
    369371       forcing_radconv = .true.
    370       elseif (forcing_type .eq.2) THEN
     372      elseif (forcing_type ==2) THEN
    371373       forcing_toga    = .true.
    372       elseif (forcing_type .eq.3) THEN
     374      elseif (forcing_type ==3) THEN
    373375       forcing_GCM2SCM = .true.
    374       elseif (forcing_type .eq.4) THEN
     376      elseif (forcing_type ==4) THEN
    375377       forcing_twpice = .true.
    376       elseif (forcing_type .eq.5) THEN
     378      elseif (forcing_type ==5) THEN
    377379       forcing_rico = .true.
    378       elseif (forcing_type .eq.6) THEN
     380      elseif (forcing_type ==6) THEN
    379381       forcing_amma = .true.
    380       elseif (forcing_type .eq.7) THEN
     382      elseif (forcing_type ==7) THEN
    381383       forcing_dice = .true.
    382       elseif (forcing_type .eq.8) THEN
     384      elseif (forcing_type ==8) THEN
    383385       forcing_gabls4 = .true.
    384       elseif (forcing_type .eq.101) THEN ! Cindynamo starts 1-10-2011 0h
     386      elseif (forcing_type ==101) THEN ! Cindynamo starts 1-10-2011 0h
    385387       forcing_case = .true.
    386388       year_ini_cas=2011
     
    389391       heure_ini_cas=0.
    390392       pdt_cas=3*3600.         ! forcing frequency
    391       elseif (forcing_type .eq.102) THEN ! Bomex starts 24-6-1969 0h
     393      elseif (forcing_type ==102) THEN ! Bomex starts 24-6-1969 0h
    392394       forcing_case = .true.
    393395       year_ini_cas=1969
     
    396398       heure_ini_cas=0.
    397399       pdt_cas=1800.         ! forcing frequency
    398       elseif (forcing_type .eq.103) THEN ! Arm_cu starts 21-6-1997 11h30
     400      elseif (forcing_type ==103) THEN ! Arm_cu starts 21-6-1997 11h30
    399401       forcing_case2 = .true.
    400402       year_ini_cas=1997
     
    403405       heure_ini_cas=11.5
    404406       pdt_cas=1800.         ! forcing frequency
    405       elseif (forcing_type .eq.104) THEN ! rico starts 16-12-2004 0h
     407      elseif (forcing_type ==104) THEN ! rico starts 16-12-2004 0h
    406408       forcing_case2 = .true.
    407409       year_ini_cas=2004
     
    410412       heure_ini_cas=0.
    411413       pdt_cas=1800.         ! forcing frequency
    412       elseif (forcing_type .eq.105) THEN ! bomex starts 16-12-2004 0h
     414      elseif (forcing_type ==105) THEN ! bomex starts 16-12-2004 0h
    413415       forcing_case2 = .true.
    414416       year_ini_cas=1969
     
    417419       heure_ini_cas=0.
    418420       pdt_cas=1800.         ! forcing frequency
    419       elseif (forcing_type .eq.106) THEN ! ayotte_24SC starts 6-11-1992 0h
     421      elseif (forcing_type ==106) THEN ! ayotte_24SC starts 6-11-1992 0h
    420422       forcing_case2 = .true.
    421423       year_ini_cas=1992
     
    424426       heure_ini_cas=10.
    425427       pdt_cas=86400.        ! forcing frequency
    426       elseif (forcing_type .eq.113) THEN ! Arm_cu starts 21-6-1997 11h30
     428      elseif (forcing_type ==113) THEN ! Arm_cu starts 21-6-1997 11h30
    427429       forcing_SCM = .true.
    428430       year_ini_cas=1997
     
    432434       mth_ini_cas=1 ! pour le moment on compte depuis le debut de l'annee
    433435       call getin('time_ini',heure_ini_cas)
    434       elseif (forcing_type .eq.40) THEN
     436      elseif (forcing_type ==40) THEN
    435437       forcing_GCSSold = .true.
    436       elseif (forcing_type .eq.50) THEN
     438      elseif (forcing_type ==50) THEN
    437439       forcing_fire = .true.
    438       elseif (forcing_type .eq.59) THEN
     440      elseif (forcing_type ==59) THEN
    439441       forcing_sandu   = .true.
    440       elseif (forcing_type .eq.60) THEN
     442      elseif (forcing_type ==60) THEN
    441443       forcing_astex   = .true.
    442       elseif (forcing_type .eq.61) THEN
     444      elseif (forcing_type ==61) THEN
    443445       forcing_armcu = .true.
    444        IF(llm.NE.19.AND.llm.NE.40) stop 'Erreur nombre de niveaux !!'
     446       IF(llm/=19.AND.llm/=40) stop 'Erreur nombre de niveaux !!'
    445447      else
    446448       write (*,*) 'ERROR : unknown forcing_type ', forcing_type
     
    461463     jcode = iflag_nudge
    462464     do i = 1,nudge_max
    463        nudge(i) = mod(jcode,10) .ge. 1
     465       nudge(i) = mod(jcode,10) >= 1
    464466       jcode = jcode/10
    465467     enddo
     
    528530
    529531! Special case for arm_cu which lasts less than one day : 53100s !! (MPL 20111026)
    530       IF(forcing_type .EQ. 61) fnday=53100./86400.
    531       IF(forcing_type .EQ. 103) fnday=53100./86400.
     532      IF(forcing_type == 61) fnday=53100./86400.
     533      IF(forcing_type == 103) fnday=53100./86400.
    532534! Special case for amma which lasts less than one day : 64800s !! (MPL 20120216)
    533       IF(forcing_type .EQ. 6) fnday=64800./86400.
     535      IF(forcing_type == 6) fnday=64800./86400.
    534536!     IF(forcing_type .EQ. 6) fnday=50400./86400.
    535  IF(forcing_type .EQ. 8 ) fnday=129600./86400.
     537 IF(forcing_type == 8 ) fnday=129600./86400.
    536538      annee_ref = anneeref
    537539      mois = 1
     
    544546      day_end = day_ini + int(fnday)
    545547
    546       IF (forcing_type .eq.2) THEN
     548      IF (forcing_type ==2) THEN
    547549! Convert the initial date of Toga-Coare to Julian day
    548550      call ymds2ju                                                          &
    549551     & (year_ini_toga,mth_ini_toga,day_ini_toga,heure,day_ju_ini_toga)
    550552
    551       ELSEIF (forcing_type .eq.4) THEN
     553      ELSEIF (forcing_type ==4) THEN
    552554! Convert the initial date of TWPICE to Julian day
    553555      call ymds2ju                                                          &
    554556     & (year_ini_twpi,mth_ini_twpi,day_ini_twpi,heure_ini_twpi              &
    555557     & ,day_ju_ini_twpi)
    556       ELSEIF (forcing_type .eq.6) THEN
     558      ELSEIF (forcing_type ==6) THEN
    557559! Convert the initial date of AMMA to Julian day
    558560      call ymds2ju                                                          &
    559561     & (year_ini_amma,mth_ini_amma,day_ini_amma,heure_ini_amma              &
    560562     & ,day_ju_ini_amma)
    561       ELSEIF (forcing_type .eq.7) THEN
     563      ELSEIF (forcing_type ==7) THEN
    562564! Convert the initial date of DICE to Julian day
    563565      call ymds2ju                                                         &
    564566     & (year_ini_dice,mth_ini_dice,day_ini_dice,heure_ini_dice             &
    565567     & ,day_ju_ini_dice)
    566  ELSEIF (forcing_type .eq.8 ) THEN
     568 ELSEIF (forcing_type ==8 ) THEN
    567569! Convert the initial date of GABLS4 to Julian day
    568570      call ymds2ju                                                         &
    569571     & (year_ini_gabls4,mth_ini_gabls4,day_ini_gabls4,heure_ini_gabls4     &
    570572     & ,day_ju_ini_gabls4)
    571       ELSEIF (forcing_type .gt.100) THEN
     573      ELSEIF (forcing_type >100) THEN
    572574! Convert the initial date to Julian day
    573575      day_ini_cas=day_deb
     
    577579     & ,day_ju_ini_cas)
    578580      print*,'time case 2',day_ini_cas,day_ju_ini_cas
    579       ELSEIF (forcing_type .eq.59) THEN
     581      ELSEIF (forcing_type ==59) THEN
    580582! Convert the initial date of Sandu case to Julian day
    581583      call ymds2ju                                                          &
     
    583585     &    time_ini*3600.,day_ju_ini_sandu)
    584586
    585       ELSEIF (forcing_type .eq.60) THEN
     587      ELSEIF (forcing_type ==60) THEN
    586588! Convert the initial date of Astex case to Julian day
    587589      call ymds2ju                                                          &
     
    589591     &    time_ini*3600.,day_ju_ini_astex)
    590592
    591       ELSEIF (forcing_type .eq.61) THEN
     593      ELSEIF (forcing_type ==61) THEN
    592594! Convert the initial date of Arm_cu case to Julian day
    593595      call ymds2ju                                                          &
     
    596598      ENDIF
    597599
    598       IF (forcing_type .gt.100) THEN
     600      IF (forcing_type >100) THEN
    599601      daytime = day + heure_ini_cas/24. ! 1st day and initial time of the simulation
    600602      ELSE
     
    638640      call phys_state_var_init(read_climoz)
    639641
    640       if (ngrid.ne.klon) then
     642      if (ngrid/=klon) then
    641643         print*,'stop in inifis'
    642644         print*,'Probleme de dimensions :'
     
    702704      zlay=-rd*300.*log(play/psurf)/rg ! moved after reading profiles
    703705
    704       IF (forcing_type .eq. 59) THEN
     706      IF (forcing_type == 59) THEN
    705707! pour forcing_sandu, on cherche l'indice le plus proche de 700hpa#3000m
    706708      write(*,*) '***********************'
    707709      do l = 1, llm
    708710       write(*,*) 'l,play(l),presnivs(l): ',l,play(l),presnivs(l)
    709        if (trouve_700 .and. play(l).le.70000) then
     711       if (trouve_700 .and. play(l)<=70000) then
    710712         llm700=l
    711713         print *,'llm700,play=',llm700,play(l)/100.
     
    826828        print*,'avant phyredem'
    827829        pctsrf(1,:)=0.
    828           if (nat_surf.eq.0.) then
     830          if (nat_surf==0.) then
    829831          pctsrf(1,is_oce)=1.
    830832          pctsrf(1,is_ter)=0.
    831833          pctsrf(1,is_lic)=0.
    832834          pctsrf(1,is_sic)=0.
    833         else if (nat_surf .eq. 1) then
     835        else if (nat_surf == 1) then
    834836          pctsrf(1,is_oce)=0.
    835837          pctsrf(1,is_ter)=1.
    836838          pctsrf(1,is_lic)=0.
    837839          pctsrf(1,is_sic)=0.
    838         else if (nat_surf .eq. 2) then
     840        else if (nat_surf == 2) then
    839841          pctsrf(1,is_oce)=0.
    840842          pctsrf(1,is_ter)=0.
    841843          pctsrf(1,is_lic)=1.
    842844          pctsrf(1,is_sic)=0.
    843         else if (nat_surf .eq. 3) then
     845        else if (nat_surf == 3) then
    844846          pctsrf(1,is_oce)=0.
    845847          pctsrf(1,is_ter)=0.
     
    870872        pbl_tke(:,2,:)=1.e-2
    871873        PRINT *, ' pbl_tke dans lmdz1d '
    872         if (prt_level .ge. 5) then
     874        if (prt_level >= 5) then
    873875         DO nsrf = 1,4
    874876           PRINT *,'pbl_tke(1,:,',nsrf,') ',pbl_tke(1,:,nsrf)
     
    10211023      endif
    10221024!Al1 ================  end restart =================================
    1023       IF (ecrit_slab_oc.eq.1) then
     1025      IF (ecrit_slab_oc==1) then
    10241026         open(97,file='div_slab.dat',STATUS='UNKNOWN')
    1025        elseif (ecrit_slab_oc.eq.0) then
     1027       elseif (ecrit_slab_oc==0) then
    10261028         open(97,file='div_slab.dat',STATUS='OLD')
    10271029       endif
     
    10461048      it_end = nint(fnday*day_step)
    10471049!test JLD     it_end = 10
    1048       do while(it.le.it_end)
    1049 
    1050        if (prt_level.ge.1) then
     1050      do while(it<=it_end)
     1051
     1052       if (prt_level>=1) then
    10511053         print*,'XXXXXXXXXXXXXXXXXXX ITAP,day,time=',                       &
    10521054     &             it,day,time,it_end,day_step
     
    10541056       endif
    10551057!Al1 demande de restartphy.nc
    1056        if (it.eq.it_end) lastcall=.True.
     1058       if (it==it_end) lastcall=.True.
    10571059
    10581060!---------------------------------------------------------------------
     
    11491151
    11501152       if (forcing_toga .or. forcing_GCSSold .or. forcing_twpice            &
    1151      &    .or.forcing_amma .or. forcing_type.eq.101) then
     1153     &    .or.forcing_amma .or. forcing_type==101) then
    11521154         fcoriolis=0.0 ; ug=0. ; vg=0.
    11531155       endif
     
    11641166!on calcule dt_cooling
    11651167        do l=1,llm
    1166         if (play(l).ge.20000.) then
     1168        if (play(l)>=20000.) then
    11671169            dt_cooling(l)=-1.5/86400.
    1168         elseif ((play(l).ge.10000.).and.((play(l).lt.20000.))) then
     1170        elseif ((play(l)>=10000.).and.((play(l)<20000.))) then
    11691171            dt_cooling(l)=-1.5/86400.*(play(l)-10000.)/(10000.)-1./86400.*(20000.-play(l))/10000.*(temp(l)-200.)
    11701172        else
     
    12731275     &               +d_q_nudge(1:mxcalc,:) )
    12741276
    1275         if (prt_level.ge.3) then
     1277        if (prt_level>=3) then
    12761278          print *,                                                          &
    12771279     &    'physiq-> temp(1),dt_phys(1),d_t_adv(1),dt_cooling(1) ',         &
     
    13511353
    13521354!Al1
    1353       if (ecrit_slab_oc.ne.-1) close(97)
     1355      if (ecrit_slab_oc/=-1) close(97)
    13541356
    13551357!Al1 Call to 1D equivalent of dynredem (an,mois,jour,heure ?)
  • LMDZ6/trunk/libf/phylmd/grid_noro_m.F90

    r3435 r5075  
    435435! Purpose: Read parameters usually determined with grid_noro from a file.
    436436!===============================================================================
    437   USE netcdf, ONLY: NF90_OPEN,  NF90_INQ_DIMID, NF90_INQUIRE_DIMENSION,        &
     437  USE lmdz_netcdf, ONLY: NF90_OPEN,  NF90_INQ_DIMID, NF90_INQUIRE_DIMENSION,        &
    438438        NF90_NOERR, NF90_CLOSE, NF90_INQ_VARID, NF90_GET_VAR, NF90_STRERROR,   &
    439439        NF90_NOWRITE
  • LMDZ6/trunk/libf/phylmd/ice_sursat_mod.F90

    r4535 r5075  
    9696  USE mod_phys_lmdz_para, ONLY: scatter, bcast
    9797  USE print_control_mod, ONLY: lunout
     98  USE lmdz_netcdf, ONLY: nf90_get_var, nf_inq_varid, nf_inq_dimlen, nf_inq_dimid, &
     99      nf_open, nf_noerr
    98100
    99101  IMPLICIT NONE
    100102
    101103  INCLUDE "YOMCST.h"
    102   INCLUDE 'netcdf.inc'
    103104
    104105  !--------------------------------------------------------
     
    168169      iret = nf_inq_varid(ncida, 'lev', varid)
    169170      IF (iret /= NF_NOERR) CALL abort_physic(modname,'problem to get lev dimid aircraft_phy.nc file',1)
    170       iret = nf_get_var_double(ncida, varid, zmida)
     171      iret = nf90_get_var(ncida, varid, zmida)
    171172      IF (iret /= NF_NOERR) CALL abort_physic(modname,'problem to read zmida file',1)
    172173      !
    173174      iret = nf_inq_varid(ncida, 'emi_co2_aircraft', varid)  !--CO2 as a proxy for m flown -
    174175      IF (iret /= NF_NOERR) CALL abort_physic(modname,'problem to get emi_distance dimid aircraft_phy.nc file',1)
    175       iret = nf_get_var_double(ncida, varid, pkm_airpl_glo)
     176      iret = nf90_get_var(ncida, varid, pkm_airpl_glo)
    176177      IF (iret /= NF_NOERR) CALL abort_physic(modname,'problem to read pkm_airpl file',1)
    177178      !
    178179      iret = nf_inq_varid(ncida, 'emi_h2o_aircraft', varid)
    179180      IF (iret /= NF_NOERR) CALL abort_physic(modname,'problem to get emi_h2o_aircraft dimid aircraft_phy.nc file',1)
    180       iret = nf_get_var_double(ncida, varid, ph2o_airpl_glo)
     181      iret = nf90_get_var(ncida, varid, ph2o_airpl_glo)
    181182      IF (iret /= NF_NOERR) CALL abort_physic(modname,'problem to read ph2o_airpl file',1)
    182183      !
     
    276277  !
    277278  DO i=1, klon
    278    IF (latitude_deg(i).GE.42.0.AND.latitude_deg(i).LE.48.0) THEN
     279   IF (latitude_deg(i)>=42.0.AND.latitude_deg(i)<=48.0) THEN
    279280     flight_m(i,38) = 50000.0  !--5000 m of flight/second in grid cell x 10 scaling
    280281   ENDIF
     
    412413     pdf_b = pdf_k/(2.*sqrt(2.))
    413414     pdf_e1 = pdf_a+pdf_b
    414      IF (abs(pdf_e1).GE.erf_lim) THEN
     415     IF (abs(pdf_e1)>=erf_lim) THEN
    415416        pdf_e1 = sign(1.,pdf_e1)
    416417        pdf_N = max(0.,sign(rneb,pdf_e1))
     
    425426     ! On perd la memoire sur la temperature (sur qvc) pour garder
    426427     ! celle sur alpha_cld
    427      IF (pdf_N.GT.1.) THEN
     428     IF (pdf_N>1.) THEN
    428429        ! On inverse alpha_cld = int_qvc^infty P(q) dq
    429430        ! pour determiner qvc = f(alpha_cld)
     
    441442        pdf_a = log(qvc/q)/(pdf_k*sqrt(2.))
    442443        pdf_e1 = pdf_a+pdf_b
    443         IF (abs(pdf_e1).GE.erf_lim) THEN
     444        IF (abs(pdf_e1)>=erf_lim) THEN
    444445           pdf_e1 = sign(1.,pdf_e1)
    445446        ELSE
     
    461462        pdf_a = log(qvc*gamma_prec/q)/(pdf_k*sqrt(2.))
    462463        pdf_e2 = pdf_a+pdf_b
    463         IF (abs(pdf_e2).GE.erf_lim) THEN
     464        IF (abs(pdf_e2)>=erf_lim) THEN
    464465           pdf_e2 = sign(1.,pdf_e2)
    465466        ELSE
     
    468469        pdf_e2 = 0.5*(1.+pdf_e2) ! integrale sous P pour q > gamma qsat
    469470
    470         IF (abs(pdf_e1-pdf_e2).LT.eps) THEN
     471        IF (abs(pdf_e1-pdf_e2)<eps) THEN
    471472           pdf_N1 = pdf_N2
    472473        ELSE
     
    475476
    476477        ! Barriere qui traite le cas gamma_prec = 1.
    477         IF (pdf_N1.LE.0.) THEN
     478        IF (pdf_N1<=0.) THEN
    478479           pdf_N1 = 0.
    479            IF (pdf_e2.GT.eps) THEN
     480           IF (pdf_e2>eps) THEN
    480481              pdf_N2 = rneb/pdf_e2
    481482           ELSE
     
    487488     ! Physique 1
    488489     ! Sublimation
    489      IF (qvc.LT.qsat) THEN
     490     IF (qvc<qsat) THEN
    490491        pdf_a = log(qvc/q)/(pdf_k*sqrt(2.))
    491492        pdf_e1 = pdf_a+pdf_b
    492         IF (abs(pdf_e1).GE.erf_lim) THEN
     493        IF (abs(pdf_e1)>=erf_lim) THEN
    493494           pdf_e1 = sign(1.,pdf_e1)
    494495        ELSE
     
    498499        pdf_a = log(qsat/q)/(pdf_k*sqrt(2.))
    499500        pdf_e2 = pdf_a+pdf_b
    500         IF (abs(pdf_e2).GE.erf_lim) THEN
     501        IF (abs(pdf_e2)>=erf_lim) THEN
    501502           pdf_e2 = sign(1.,pdf_e2)
    502503        ELSE
     
    516517
    517518     ! Condensation
    518      IF (gamma_ss*qsat.LT.gamma_prec*qvc) THEN
     519     IF (gamma_ss*qsat<gamma_prec*qvc) THEN
    519520     
    520521        pdf_a = log(gamma_ss*qsat/q)/(pdf_k*sqrt(2.))
    521522        pdf_e1 = pdf_a+pdf_b
    522         IF (abs(pdf_e1).GE.erf_lim) THEN
     523        IF (abs(pdf_e1)>=erf_lim) THEN
    523524           pdf_e1 = sign(1.,pdf_e1)
    524525        ELSE
     
    528529        pdf_a = log(gamma_prec*qvc/q)/(pdf_k*sqrt(2.))
    529530        pdf_e2 = pdf_a+pdf_b
    530         IF (abs(pdf_e2).GE.erf_lim) THEN
     531        IF (abs(pdf_e2)>=erf_lim) THEN
    531532           pdf_e2 = sign(1.,pdf_e2)
    532533        ELSE
     
    545546        pdf_a = log(gamma_ss*qsat/q)/(pdf_k*sqrt(2.))
    546547        pdf_e1 = pdf_a+pdf_b
    547         IF (abs(pdf_e1).GE.erf_lim) THEN
     548        IF (abs(pdf_e1)>=erf_lim) THEN
    548549           pdf_e1 = sign(1.,pdf_e1)
    549550        ELSE
     
    562563     pdf_a = log(qsat/q)/(pdf_k*sqrt(2.))
    563564     pdf_e1 = pdf_a+pdf_b
    564      IF (abs(pdf_e1).GE.erf_lim) THEN
     565     IF (abs(pdf_e1)>=erf_lim) THEN
    565566        pdf_e1 = sign(1.,pdf_e1)
    566567     ELSE
     
    570571
    571572     pdf_e2 = pdf_a-pdf_b
    572      IF (abs(pdf_e2).GE.erf_lim) THEN
     573     IF (abs(pdf_e2)>=erf_lim) THEN
    573574        pdf_e2 = sign(1.,pdf_e2)
    574575     ELSE
     
    584585     pdf_a = log(max(qsat,qvc)/q)/(pdf_k*sqrt(2.))
    585586     pdf_e1 = pdf_a-pdf_b
    586      IF (abs(pdf_e1).GE.erf_lim) THEN
     587     IF (abs(pdf_e1)>=erf_lim) THEN
    587588        pdf_e1 = sign(1.,pdf_e1)
    588589     ELSE
     
    592593     pdf_a = log(min(gamma_ss*qsat,gamma_prec*qvc)/q)/(pdf_k*sqrt(2.))
    593594     pdf_e2 = pdf_a-pdf_b
    594      IF (abs(pdf_e2).GE.erf_lim) THEN
     595     IF (abs(pdf_e2)>=erf_lim) THEN
    595596        pdf_e2 = sign(1.,pdf_e2)
    596597     ELSE
     
    603604
    604605     ! Partie 2 (sous condition)
    605      IF (gamma_ss*qsat.GT.gamma_prec*qvc) THEN
     606     IF (gamma_ss*qsat>gamma_prec*qvc) THEN
    606607        pdf_a = log(gamma_ss*qsat/q)/(pdf_k*sqrt(2.))
    607608        pdf_e1 = pdf_a-pdf_b
    608         IF (abs(pdf_e1).GE.erf_lim) THEN
     609        IF (abs(pdf_e1)>=erf_lim) THEN
    609610           pdf_e1 = sign(1.,pdf_e1)
    610611        ELSE
     
    632633
    633634     ! Physique 2 : Turbulence
    634      IF (rneb.GT.eps.AND.rneb.LT.1.-eps) THEN ! rneb != 0 and != 1
     635     IF (rneb>eps.AND.rneb<1.-eps) THEN ! rneb != 0 and != 1
    635636       !
    636637       tke = pbl_tke(i,k,is_ave)
     
    642643       b_tur = (rneb*V_cell/4./PI/N_cld)**(1./3.)
    643644       ! On verifie que la longeur de melange n'est pas trop grande
    644        IF (L_tur.GT.b_tur) THEN
     645       IF (L_tur>b_tur) THEN
    645646          L_tur = b_tur
    646647       ENDIF
     
    665666       q_eq = q_eq/(V_env + V_cld)
    666667
    667        IF (q_eq.GT.qsat) THEN
     668       IF (q_eq>qsat) THEN
    668669          drnebclr = - V_clr/V_cell
    669670          dqclr = drnebclr*qclr/MAX(eps,rnebclr)
     
    703704     ! Barrieres
    704705     ! ISSR trop petite
    705      IF (rnebss.LT.eps) THEN
     706     IF (rnebss<eps) THEN
    706707        rneb = MIN(rneb + rnebss,1.0-eps) !--ajout OB barriere
    707708        qcld = qcld + qss
     
    711712
    712713     ! le nuage est trop petit
    713      IF (rneb.LT.eps) THEN
     714     IF (rneb<eps) THEN
    714715        ! s'il y a une ISSR on met tout dans l'ISSR, sinon dans le
    715716        ! clear sky
    716         IF (rnebss.LT.eps) THEN
     717        IF (rnebss<eps) THEN
    717718           rnebclr = 1.
    718719           rnebss = 0. !--ajout OB
     
    749750     !--critical T_LM below which no liquid contrail can form in exhaust
    750751     !Tcontr(i,k) = 226.69+9.43*log(Gcontr-0.053)+0.72*(log(Gcontr-0.053))**2 !--K
    751      IF (Gcontr .GT. 0.1) THEN
     752     IF (Gcontr > 0.1) THEN
    752753     !
    753754       Tcontr = 226.69+9.43*log(Gcontr-0.053)+0.72*(log(Gcontr-0.053))**2 !--K
     
    775776       !qcontr2 = eps_w*qcontr / (pplay+eps_w*qcontr)
    776777       !
    777        IF (t .LT. Tcontr) THEN !--contrail formation is possible
     778       IF (t < Tcontr) THEN !--contrail formation is possible
    778779       !
    779780       !--compute fractions of persistent (P) and non-persistent(N) contrail potential regions
    780781       !!IF (qcontr(i,k).GE.qsat) THEN
    781        IF (qcontr2.GE.qsat) THEN
     782       IF (qcontr2>=qsat) THEN
    782783         !--none of the unsaturated clear sky is prone for contrail formation
    783784         !!fcontrN(i,k) = 0.0
     
    787788         pdf_a = log(qsat/q)/(pdf_k*sqrt(2.))
    788789         pdf_e1 = pdf_a+pdf_b
    789          IF (abs(pdf_e1).GE.erf_lim) THEN
     790         IF (abs(pdf_e1)>=erf_lim) THEN
    790791            pdf_e1 = sign(1.,pdf_e1)
    791792         ELSE
     
    796797         pdf_a = log(MIN(qcontr2,qvc)/q)/(pdf_k*sqrt(2.))
    797798         pdf_e2 = pdf_a+pdf_b
    798          IF (abs(pdf_e2).GE.erf_lim) THEN
     799         IF (abs(pdf_e2)>=erf_lim) THEN
    799800            pdf_e2 = sign(1.,pdf_e2)
    800801         ELSE
     
    807808         pdf_a = log(qsat/q)/(pdf_k*sqrt(2.))
    808809         pdf_e1 = pdf_a+pdf_b
    809          IF (abs(pdf_e1).GE.erf_lim) THEN
     810         IF (abs(pdf_e1)>=erf_lim) THEN
    810811            pdf_e1 = sign(1.,pdf_e1)
    811812         ELSE
     
    816817         pdf_a = log(MIN(qcontr2,qvc)/q)/(pdf_k*sqrt(2.))
    817818         pdf_e2 = pdf_a+pdf_b
    818          IF (abs(pdf_e2).GE.erf_lim) THEN
     819         IF (abs(pdf_e2)>=erf_lim) THEN
    819820            pdf_e2 = sign(1.,pdf_e2)
    820821         ELSE
     
    827828         pdf_a = log(MAX(qsat,qvc)/q)/(pdf_k*sqrt(2.))
    828829         pdf_e1 = pdf_a+pdf_b
    829          IF (abs(pdf_e1).GE.erf_lim) THEN
     830         IF (abs(pdf_e1)>=erf_lim) THEN
    830831            pdf_e1 = sign(1.,pdf_e1)
    831832         ELSE
     
    836837         pdf_a = log(MIN(qcontr2,MIN(gamma_prec*qvc,gamma_ss*qsat))/q)/(pdf_k*sqrt(2.))
    837838         pdf_e2 = pdf_a+pdf_b
    838          IF (abs(pdf_e2).GE.erf_lim) THEN
     839         IF (abs(pdf_e2)>=erf_lim) THEN
    839840            pdf_e2 = sign(1.,pdf_e2)
    840841         ELSE
     
    847848         pdf_a = log(gamma_prec*qvc/q)/(pdf_k*sqrt(2.))
    848849         pdf_e1 = pdf_a+pdf_b
    849          IF (abs(pdf_e1).GE.erf_lim) THEN
     850         IF (abs(pdf_e1)>=erf_lim) THEN
    850851            pdf_e1 = sign(1.,pdf_e1)
    851852         ELSE
     
    856857         pdf_a = log(MIN(qcontr2,gamma_ss*qsat)/q)/(pdf_k*sqrt(2.))
    857858         pdf_e2 = pdf_a+pdf_b
    858          IF (abs(pdf_e2).GE.erf_lim) THEN
     859         IF (abs(pdf_e2)>=erf_lim) THEN
    859860            pdf_e2 = sign(1.,pdf_e2)
    860861         ELSE
     
    875876         pdf_a = log(qcontr2/q)/(pdf_k*sqrt(2.))
    876877         pdf_e1 = pdf_a+pdf_b   !--normalement pdf_b est deja defini
    877          IF (abs(pdf_e1).GE.erf_lim) THEN
     878         IF (abs(pdf_e1)>=erf_lim) THEN
    878879            pdf_e1 = sign(1.,pdf_e1)
    879880         ELSE
     
    883884         pdf_a = log(qsat/q)/(pdf_k*sqrt(2.))
    884885         pdf_e2 = pdf_a+pdf_b
    885          IF (abs(pdf_e2).GE.erf_lim) THEN
     886         IF (abs(pdf_e2)>=erf_lim) THEN
    886887            pdf_e2 = sign(1.,pdf_e2)
    887888         ELSE
  • LMDZ6/trunk/libf/phylmd/inlandsis/surf_inlandsis_mod.F90

    r3900 r5075  
    638638            END DO
    639639
    640             IF (sissnow(ikl) .LE. sn_low) THEN  !add snow
    641                 IF (isnoSV(ikl).GE.1) THEN
     640            IF (sissnow(ikl) <= sn_low) THEN  !add snow
     641                IF (isnoSV(ikl)>=1) THEN
    642642                    dzsnSV(ikl, 1) = dzsnSV(ikl, 1) + sn_add / max(ro__SV(ikl, 1), epsi)
    643643                    toicSV(ikl) = toicSV(ikl) - sn_add
     
    657657            END IF
    658658
    659             IF (sissnow(ikl) .ge. sn_upp) THEN  !thinnen snow layer below
     659            IF (sissnow(ikl) >= sn_upp) THEN  !thinnen snow layer below
    660660                dzsnSV(ikl, 1) = dzsnSV(ikl, 1) / sn_div
    661661                toicSV(ikl) = toicSV(ikl) + dzsnSV(ikl, 1) * ro__SV(ikl, 1) / sn_div
     
    10491049        ! Objet: Lecture du fichier de conditions initiales pour SISVAT
    10501050        !======================================================================
    1051         include "netcdf.inc"
    10521051        !    include "indicesol.h"
    10531052
     
    11181117
    11191118        DO isn = 1, nsno
    1120             IF (isn.LE.99) THEN
     1119            IF (isn<=99) THEN
    11211120                WRITE(str2, '(i2.2)') isn
    11221121                CALL get_field("AGESNOW" // str2, &
     
    11281127        ENDDO
    11291128        DO isn = 1, nsno
    1130             IF (isn.LE.99) THEN
     1129            IF (isn<=99) THEN
    11311130                WRITE(str2, '(i2.2)') isn
    11321131                CALL get_field("DZSNOW" // str2, &
     
    11381137        ENDDO
    11391138        DO isn = 1, nsno
    1140             IF (isn.LE.99) THEN
     1139            IF (isn<=99) THEN
    11411140                WRITE(str2, '(i2.2)') isn
    11421141                CALL get_field("G2SNOW" // str2, &
     
    11481147        ENDDO
    11491148        DO isn = 1, nsno
    1150             IF (isn.LE.99) THEN
     1149            IF (isn<=99) THEN
    11511150                WRITE(str2, '(i2.2)') isn
    11521151                CALL get_field("G1SNOW" // str2, &
     
    11581157        ENDDO
    11591158        DO isn = 1, nsismx
    1160             IF (isn.LE.99) THEN
     1159            IF (isn<=99) THEN
    11611160                WRITE(str2, '(i2.2)') isn
    11621161                CALL get_field("ETA" // str2, &
     
    11681167        ENDDO
    11691168        DO isn = 1, nsismx
    1170             IF (isn.LE.99) THEN
     1169            IF (isn<=99) THEN
    11711170                WRITE(str2, '(i2.2)') isn
    11721171                CALL get_field("RO" // str2, &
     
    11781177        ENDDO
    11791178        DO isn = 1, nsismx
    1180             IF (isn.LE.99) THEN
     1179            IF (isn<=99) THEN
    11811180                WRITE(str2, '(i2.2)') isn
    11821181                CALL get_field("TSS" // str2, &
     
    11881187        ENDDO
    11891188        DO isn = 1, nsno
    1190             IF (isn.LE.99) THEN
     1189            IF (isn<=99) THEN
    11911190                WRITE(str2, '(i2.2)') isn
    11921191                CALL get_field("HISTORY" // str2, &
     
    12871286        IMPLICIT none
    12881287
    1289         include "netcdf.inc"
    12901288        !    include "indicesol.h"
    12911289        !    include "dimsoil.h"
     
    14031401
    14041402            DO isn = 1, nsno
    1405                 IF (isn.LE.99) THEN
     1403                IF (isn<=99) THEN
    14061404                    WRITE(str2, '(i2.2)') isn
    14071405                    CALL put_field(pass, "AGESNOW" // str2, &
     
    14141412            ENDDO
    14151413            DO isn = 1, nsno
    1416                 IF (isn.LE.99) THEN
     1414                IF (isn<=99) THEN
    14171415                    WRITE(str2, '(i2.2)') isn
    14181416                    CALL put_field(pass, "DZSNOW" // str2, &
     
    14251423            ENDDO
    14261424            DO isn = 1, nsno
    1427                 IF (isn.LE.99) THEN
     1425                IF (isn<=99) THEN
    14281426                    WRITE(str2, '(i2.2)') isn
    14291427                    CALL put_field(pass, "G2SNOW" // str2, &
     
    14361434            ENDDO
    14371435            DO isn = 1, nsno
    1438                 IF (isn.LE.99) THEN
     1436                IF (isn<=99) THEN
    14391437                    WRITE(str2, '(i2.2)') isn
    14401438                    CALL put_field(pass, "G1SNOW" // str2, &
     
    14471445            ENDDO
    14481446            DO isn = 1, nsismx
    1449                 IF (isn.LE.99) THEN
     1447                IF (isn<=99) THEN
    14501448                    WRITE(str2, '(i2.2)') isn
    14511449                    CALL put_field(pass, "ETA" // str2, &
     
    14581456            ENDDO
    14591457            DO isn = 1, nsismx   !nsno
    1460                 IF (isn.LE.99) THEN
     1458                IF (isn<=99) THEN
    14611459                    WRITE(str2, '(i2.2)') isn
    14621460                    CALL put_field(pass, "RO" // str2, &
     
    14691467            ENDDO
    14701468            DO isn = 1, nsismx
    1471                 IF (isn.LE.99) THEN
     1469                IF (isn<=99) THEN
    14721470                    WRITE(str2, '(i2.2)') isn
    14731471                    CALL put_field(pass, "TSS" // str2, &
     
    14801478            ENDDO
    14811479            DO isn = 1, nsno
    1482                 IF (isn.LE.99) THEN
     1480                IF (isn<=99) THEN
    14831481                    WRITE(str2, '(i2.2)') isn
    14841482                    CALL put_field(pass, "HISTORY" // str2, &
  • LMDZ6/trunk/libf/phylmd/interfoce_lim.F90

    r5073 r5075  
    1010  USE mod_phys_lmdz_para
    1111  USE indice_sol_mod
    12   USE lmdz_netcdf
     12  USE lmdz_netcdf, ONLY: nf90_get_var,nf_close,nf_noerr,nf_inq_varid,nf_open,nf_nowrite
    1313 
    1414  IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/iostart.F90

    r5073 r5075  
    3030
    3131  SUBROUTINE Open_startphy(filename)
    32   USE lmdz_netcdf
     32  USE lmdz_netcdf, ONLY: nf90_nowrite, nf90_noerr,nf90_open
    3333  USE mod_phys_lmdz_para
    3434  IMPLICIT NONE
     
    4848
    4949  SUBROUTINE Close_startphy
    50   USE lmdz_netcdf
     50  USE lmdz_netcdf, ONLY: nf90_close
    5151  USE mod_phys_lmdz_para
    5252  IMPLICIT NONE
     
    6161
    6262  FUNCTION Inquire_Field(Field_name)
    63   USE lmdz_netcdf
     63  USE lmdz_netcdf, ONLY: nf90_noerr,nf90_inq_varid
    6464  USE mod_phys_lmdz_para
    6565  IMPLICIT NONE
     
    115115 
    116116  SUBROUTINE Get_field_rgen(field_name,field,field_size,found)
    117   USE lmdz_netcdf
     117  USE lmdz_netcdf, ONLY: nf90_inq_varid,nf90_noerr,nf90_get_var
    118118  USE dimphy
    119119  USE geometry_mod
     
    251251
    252252  SUBROUTINE Get_var_rgen(var_name,var,var_size,found)
    253   USE lmdz_netcdf
     253  USE lmdz_netcdf, ONLY: nf90_noerr,nf90_get_var,nf90_inq_varid
    254254  USE dimphy
    255255  USE mod_grid_phy_lmdz
     
    301301
    302302  SUBROUTINE open_restartphy(filename)
    303   USE lmdz_netcdf
     303  USE lmdz_netcdf, ONLY: nf90_create,nf90_clobber,nf90_64bit_offset,nf90_noerr,nf90_strerror,&
     304          nf90_global,nf90_put_att,nf90_def_dim
    304305  USE mod_phys_lmdz_para, ONLY: is_master
    305306  USE mod_grid_phy_lmdz, ONLY: klon_glo
     
    332333 
    333334  SUBROUTINE enddef_restartphy
    334   USE lmdz_netcdf
     335  USE lmdz_netcdf, ONLY: nf90_enddef
    335336  USE mod_phys_lmdz_para
    336337  IMPLICIT NONE
     
    342343
    343344  SUBROUTINE close_restartphy
    344   USE lmdz_netcdf
     345  USE lmdz_netcdf, ONLY: nf90_close
    345346  USE mod_phys_lmdz_para
    346347  IMPLICIT NONE
     
    385386 
    386387  SUBROUTINE put_field_rgen(pass, field_name,title,field,field_size)
    387   USE lmdz_netcdf
     388  USE lmdz_netcdf, ONLY: nf90_def_var,nf90_format,nf90_put_att,nf90_inq_varid,nf90_put_var
    388389  USE dimphy
    389390  USE geometry_mod
     
    508509
    509510  SUBROUTINE put_var_rgen(pass, var_name,title,var,var_size)
    510   USE lmdz_netcdf
     511  USE lmdz_netcdf, ONLY: nf90_format,nf90_def_var,nf90_put_var,nf90_inq_varid,nf90_put_att
    511512  USE dimphy
    512513  USE mod_phys_lmdz_para
  • LMDZ6/trunk/libf/phylmd/iotd_ecrit.F90

    r4593 r5075  
    2222!=================================================================
    2323 
    24       use netcdf, only: nf90_put_var
     24      USE lmdz_netcdf, ONLY: nf90_put_var,nf_inq_varid,nf_enddef,nf_redef,nf_sync,nf_noerr,&
     25              nf_float,nf_def_var
    2526      implicit none
    2627
    2728! Commons
    2829
    29       INCLUDE "netcdf.inc"
    3030      INCLUDE "iotd.h"
    3131
     
    9090
    9191!! Quand on tombe sur la premiere variable on ajoute un pas de temps
    92         if (nom.eq.firstnom) then
     92        if (nom==firstnom) then
    9393        ! We have identified a "first call" (at given date)
    9494
     
    114114!        print*,'IOTD Date ,varid,nid,ntime,date',varid,nid,ntime,date
    115115
    116            if (ierr.ne.NF_NOERR) then
     116           if (ierr/=NF_NOERR) then
    117117              write(*,*) "***** PUT_VAR matter in writediagfi_nc"
    118118              write(*,*) "***** with time"
     
    175175      ierr= NF90_PUT_VAR(nid,varid,zx,corner,edges)
    176176
    177       if (ierr.ne.NF_NOERR) then
     177      if (ierr/=NF_NOERR) then
    178178           write(*,*) "***** PUT_VAR problem in writediagfi"
    179179           write(*,*) "***** with ",nom
  • LMDZ6/trunk/libf/phylmd/iotd_fin.F90

    r4593 r5075  
    1       SUBROUTINE iotd_fin
    2       IMPLICIT NONE
     1SUBROUTINE iotd_fin
     2  USE lmdz_netcdf, ONLY : nf_close
    33
    4 !=======================================================================
    5 !
    6 !   Auteur:  F. Hourdin
    7 !   -------
    8 !
    9 !   Objet:
    10 !   ------
    11 !   Light interface for netcdf outputs. can be used outside LMDZ
    12 !
    13 !=======================================================================
     4  IMPLICIT NONE
    145
     6  !=======================================================================
     7  !
     8  !   Auteur:  F. Hourdin
     9  !   -------
     10  !
     11  !   Objet:
     12  !   ------
     13  !   Light interface for netcdf outputs. can be used outside LMDZ
     14  !
     15  !=======================================================================
    1516
    16       INCLUDE "netcdf.inc"
    17       INCLUDE "iotd.h"
    18       integer ierr
     17  INCLUDE "iotd.h"
     18  integer ierr
    1919
    20 !   Arguments:
    21 !   ----------
     20  !   Arguments:
     21  !   ----------
    2222
    23       ierr=NF_close(nid)
     23  ierr = NF_close(nid)
    2424
    25       END
     25END
  • LMDZ6/trunk/libf/phylmd/iotd_ini.F90

    r4593 r5075  
    11      SUBROUTINE iotd_ini(fichnom,iim,jjm,llm,prlon,prlat,pcoordv,jour0,mois0,an0,t0,timestep,calendrier)
     2            USE lmdz_netcdf, ONLY: nf_enddef,nf_put_att_text,nf_float,nf_def_var,nf_redef,&
     3                    nf_global,nf_def_dim,nf_create,nf_clobber,nf_unlimited,nf90_put_var
    24      IMPLICIT NONE
    35
     
    1618!   -------------
    1719
    18       INCLUDE "netcdf.inc"
    1920      INCLUDE "iotd.h"
    2021
     
    3132      real  px(1000)
    3233      character (len=10) :: nom
    33       real*4 rlon(iim),rlat(jjm),coordv(llm)
     34      real(kind=4) rlon(iim),rlat(jjm),coordv(llm)
    3435
    3536!   Local:
     
    7172      n_names_iotd_def=0
    7273      open(99,file='iotd.def',form='formatted',status='old',iostat=ierr)
    73          if ( ierr.eq.0 ) then
     74         if ( ierr==0 ) then
    7475            ierr=0
    7576            do while (ierr==0)
     
    112113      ierr=NF_PUT_ATT_TEXT(nid,nvarid,'units',12,"degrees_east")
    113114      ierr=NF_ENDDEF(nid)
    114       ierr=NF_PUT_VAR_REAL(nid,nvarid,rlon)
     115      ierr=nf90_put_var(nid,nvarid,rlon)
    115116       print*,ierr
    116117
     
    121122      ierr=NF_PUT_ATT_TEXT(nid,nvarid,'units',13,"degrees_north")
    122123      ierr=NF_ENDDEF(nid)
    123       ierr=NF_PUT_VAR_REAL(nid,nvarid,rlat)
     124      ierr=nf90_put_var(nid,nvarid,rlat)
    124125!
    125126! ---- vertical ------------
     
    135136      endif
    136137      ierr=NF_ENDDEF(nid)
    137       ierr=NF_PUT_VAR_REAL(nid,nvarid,coordv)
     138      ierr=nf90_put_var(nid,nvarid,coordv)
    138139
    139140!
  • LMDZ6/trunk/libf/phylmd/limit_read_mod.F90

    r4619 r5075  
    165165    USE mod_phys_lmdz_para
    166166    USE surface_data, ONLY : type_ocean, ok_veget
    167     USE netcdf
     167    USE lmdz_netcdf, ONLY:nf90_get_var,nf90_inq_varid,nf90_close,nf90_inquire_dimension,&
     168            nf90_inquire,nf90_get_att,nf90_inq_dimid,nf90_nowrite,nf90_noerr,nf90_open
    168169    USE indice_sol_mod
    169170    USE phys_cal_mod, ONLY : calend, year_len
  • LMDZ6/trunk/libf/phylmd/limit_slab.F90

    r3102 r5075  
    66  USE mod_grid_phy_lmdz, ONLY: klon_glo
    77  USE mod_phys_lmdz_para
    8   USE netcdf
     8  USE lmdz_netcdf, ONLY: nf90_close,nf90_get_var,nf90_inq_varid,nf90_nowrite,nf90_noerr,nf90_open
    99  USE indice_sol_mod
    1010  USE ocean_slab_mod, ONLY: nslay
     
    9999        END IF
    100100        ! Try next layers if more than 1
    101         IF ((nslay.GT.1).AND.read_bils) THEN
     101        IF ((nslay>1).AND.read_bils) THEN
    102102          DO i=2,nslay
    103103            WRITE(str2,'(i2.2)') i
    104104            ierr = NF90_INQ_VARID(nid,'BILS_OCE'//str2, nvarid)
    105             IF (ierr.EQ.NF90_NOERR) THEN
     105            IF (ierr==NF90_NOERR) THEN
    106106              ierr = NF90_GET_VAR(nid,nvarid,bils_glo(:,i),start,epais)
    107107            ENDIF
  • LMDZ6/trunk/libf/phylmd/mo_simple_plumes.F90

    r4164 r5075  
    2424MODULE MO_SIMPLE_PLUMES
    2525
    26   USE netcdf
     26    USE lmdz_netcdf, ONLY:nf90_get_var,nf90_close,nf90_inq_varid,nf90_inq_dimid,&
     27            nf90_inquire_dimension,nf90_noerr,nf90_nowrite,nf90_open
    2728
    2829  IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/moy_undefSTD.F90

    r4619 r5075  
    33
    44SUBROUTINE moy_undefstd(itap, itapm1)
    5   USE netcdf
     5  USE lmdz_netcdf, ONLY: nf90_fill_real
    66  USE dimphy
    77#ifdef CPP_IOIPSL
  • LMDZ6/trunk/libf/phylmd/open_climoz_m.F90

    r4489 r5075  
    1313!-------------------------------------------------------------------------------
    1414  USE netcdf95, ONLY: nf95_open, nf95_close, nf95_gw_var, nf95_inq_varid
    15   USE netcdf,   ONLY: nf90_nowrite
     15  USE lmdz_netcdf,   ONLY: nf90_nowrite
    1616  USE mod_phys_lmdz_mpi_data,      ONLY: is_mpi_root
    1717  USE mod_phys_lmdz_mpi_transfert, ONLY: bcast_mpi
  • LMDZ6/trunk/libf/phylmd/pbl_surface_mod.F90

    r5039 r5075  
    415415    use lmdz_blowing_snow_ini, only : zeta_bs
    416416    USE wxios, ONLY: missing_val_xios => missing_val, using_xios
    417     USE netcdf, only: missing_val_netcdf => nf90_fill_real
     417    USE lmdz_netcdf, only: missing_val_netcdf => nf90_fill_real
    418418
    419419     
  • LMDZ6/trunk/libf/phylmd/phyetat0_mod.F90

    r4744 r5075  
    4040  USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy
    4141  USE wxios, ONLY: missing_val_xios => missing_val, using_xios
    42   use netcdf, only: missing_val_netcdf => nf90_fill_real
     42  use lmdz_netcdf, only: missing_val_netcdf => nf90_fill_real
    4343  use config_ocean_skin_m, only: activate_ocean_skin
    4444
     
    152152  tab_cntrl(6)=nbapp_rad
    153153
    154   IF (iflag_cycle_diurne.GE.1) tab_cntrl( 7) = iflag_cycle_diurne
     154  IF (iflag_cycle_diurne>=1) tab_cntrl( 7) = iflag_cycle_diurne
    155155  IF (soil_model) tab_cntrl( 8) =1.
    156156  IF (new_oliq) tab_cntrl( 9) =1.
     
    251251       + pctsrf(1 : klon, is_lic)
    252252  DO i = 1 , klon
    253      IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN
     253     IF ( abs(fractint(i) - zmasq(i) ) > EPSFRA ) THEN
    254254        WRITE(*, *) 'phyetat0: attention fraction terre pas ',  &
    255255             'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
     
    262262       + pctsrf(1 : klon, is_sic)
    263263  DO i = 1 , klon
    264      IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN
     264     IF ( abs( fractint(i) - (1. - zmasq(i))) > EPSFRA ) THEN
    265265        WRITE(*, *) 'phyetat0 attention fraction ocean pas ',  &
    266266             'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
     
    290290  DO nsrf = 1, nbsrf
    291291     DO isw=1, nsw
    292         IF (isw.GT.99) THEN
     292        IF (isw>99) THEN
    293293           PRINT*, "Trop de bandes SW"
    294294           call abort_physic("phyetat0", "", 1)
     
    313313
    314314   DO isoil=1, nsoilmx
    315         IF (isoil.GT.99) THEN
     315        IF (isoil>99) THEN
    316316           PRINT*, "Trop de couches "
    317317           call abort_physic("phyetat0", "", 1)
     
    416416  !          dummy values (as is the case when generated by ce0l,
    417417  !          or by iniaqua)
    418   IF ( (maxval(q_ancien).EQ.minval(q_ancien))       .OR. &
    419        (maxval(ql_ancien).EQ.minval(ql_ancien))     .OR. &
    420        (maxval(qs_ancien).EQ.minval(qs_ancien))     .OR. &
    421        (maxval(rneb_ancien).EQ.minval(rneb_ancien)) .OR. &
    422        (maxval(prw_ancien).EQ.minval(prw_ancien))   .OR. &
    423        (maxval(prlw_ancien).EQ.minval(prlw_ancien)) .OR. &
    424        (maxval(prsw_ancien).EQ.minval(prsw_ancien)) .OR. &
    425        (maxval(t_ancien).EQ.minval(t_ancien)) ) THEN
     418  IF ( (maxval(q_ancien)==minval(q_ancien))       .OR. &
     419       (maxval(ql_ancien)==minval(ql_ancien))     .OR. &
     420       (maxval(qs_ancien)==minval(qs_ancien))     .OR. &
     421       (maxval(rneb_ancien)==minval(rneb_ancien)) .OR. &
     422       (maxval(prw_ancien)==minval(prw_ancien))   .OR. &
     423       (maxval(prlw_ancien)==minval(prlw_ancien)) .OR. &
     424       (maxval(prsw_ancien)==minval(prsw_ancien)) .OR. &
     425       (maxval(t_ancien)==minval(t_ancien)) ) THEN
    426426    ancien_ok=.false.
    427427  ENDIF
    428428
    429429  IF (ok_bs) THEN
    430     IF ( (maxval(qbs_ancien).EQ.minval(qbs_ancien))       .OR. &
    431          (maxval(prbsw_ancien).EQ.minval(prbsw_ancien)) ) THEN
     430    IF ( (maxval(qbs_ancien)==minval(qbs_ancien))       .OR. &
     431         (maxval(prbsw_ancien)==minval(prbsw_ancien)) ) THEN
    432432       ancien_ok=.false.
    433433    ENDIF
     
    549549  IF ( type_ocean == 'slab' ) THEN
    550550      CALL ocean_slab_init(phys_tstep, pctsrf)
    551       IF (nslay.EQ.1) THEN
     551      IF (nslay==1) THEN
    552552        found=phyetat0_get(tslab,["tslab01","tslab  "],"tslab",0.)
    553553      ELSE
     
    578578              PRINT*, "Initialisation a 0/1m suivant fraction glace"
    579579              seaice(:)=0.
    580               WHERE (pctsrf(:,is_sic).GT.EPSFRA)
     580              WHERE (pctsrf(:,is_sic)>EPSFRA)
    581581                  seaice=917.
    582582              ENDWHERE
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r5050 r5075  
    456456    USE ioipsl, ONLY: histend, histsync
    457457    USE iophy, ONLY: set_itau_iophy, histwrite_phy
    458     USE netcdf, ONLY: nf90_fill_real
     458    USE lmdz_netcdf, ONLY: nf90_fill_real
    459459    USE print_control_mod, ONLY: prt_level,lunout
    460460    ! ug Pour les sorties XIOS
     
    555555      kmax_100m=1
    556556      DO k=1, klev-1
    557         IF (presnivs(k).GT.0.97*101325.) kmax_100m = k !--finding out max level for 100 m with a good margin
     557        IF (presnivs(k)>0.97*101325.) kmax_100m = k !--finding out max level for 100 m with a good margin
    558558      ENDDO
    559559    ENDIF
     
    782782          DO k=1, kmax_100m-1                                      !--we could stop much lower
    783783            DO i=1,klon
    784               IF (z(i,k).LT.100..AND.z(i,k+1).GE.100.) THEN
     784              IF (z(i,k)<100..AND.z(i,k+1)>=100.) THEN
    785785                wind100m(i)=SQRT( (u_seri(i,k)+(100.-z(i,k))/(z(i,k+1)-z(i,k))*(u_seri(i,k+1)-u_seri(i,k)))**2.0 + &
    786786                                  (v_seri(i,k)+(100.-z(i,k))/(z(i,k+1)-z(i,k))*(v_seri(i,k+1)-v_seri(i,k)))**2.0 )
     
    794794         !--polynomial fit for 14,Vestas,1074,V136/3450 kW windmill - Olivier
    795795         DO i=1,klon
    796            IF (pctsrf(i,is_ter).GT.0.05 .AND. wind100m(i).NE.missing_val) THEN
     796           IF (pctsrf(i,is_ter)>0.05 .AND. wind100m(i)/=missing_val) THEN
    797797             x=wind100m(i)
    798              IF (x.LE.3.0 .OR. x.GE.22.5) THEN
     798             IF (x<=3.0 .OR. x>=22.5) THEN
    799799               zx_tmp_fi2d(i)=0.0
    800              ELSE IF (x.GE.10.0) THEN
     800             ELSE IF (x>=10.0) THEN
    801801               zx_tmp_fi2d(i)=1.0
    802802             ELSE
     
    815815         !--polynomial fit for 14,Vestas,867,V164/8000 kW - Olivier
    816816         DO i=1,klon
    817            IF (pctsrf(i,is_oce).GT.0.05 .AND. wind100m(i).NE.missing_val) THEN
     817           IF (pctsrf(i,is_oce)>0.05 .AND. wind100m(i)/=missing_val) THEN
    818818             x=wind100m(i)
    819              IF (x.LE.3.0 .OR. x.GE.25.5) THEN
     819             IF (x<=3.0 .OR. x>=25.5) THEN
    820820               zx_tmp_fi2d(i)=0.0
    821              ELSE IF (x.GE.12.5) THEN
     821             ELSE IF (x>=12.5) THEN
    822822               zx_tmp_fi2d(i)=1.0
    823823             ELSE
     
    14071407       CALL histwrite_phy(o_uwat, uwat)
    14081408       CALL histwrite_phy(o_vwat, vwat)
    1409        IF (iflag_con.GE.3) THEN ! sb
     1409       IF (iflag_con>=3) THEN ! sb
    14101410          CALL histwrite_phy(o_cape, cape)
    14111411          CALL histwrite_phy(o_pbase, ema_pcb)
     
    15121512            DO k=1, nlevSTD
    15131513              bb2=clevSTD(k)
    1514               IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
    1515                   bb2.EQ."500".OR.bb2.EQ."200".OR. &
    1516                   bb2.EQ."100".OR. &
    1517                   bb2.EQ."50".OR.bb2.EQ."10") THEN
     1514              IF (bb2=="850".OR.bb2=="700".OR. &
     1515                  bb2=="500".OR.bb2=="200".OR. &
     1516                  bb2=="100".OR. &
     1517                  bb2=="50".OR.bb2=="10") THEN
    15181518                  ll=ll+1
    15191519                  CALL histwrite_phy(o_uSTDlevs(ll),ulevSTD(:,k))
     
    15301530       IF (vars_defined) THEN
    15311531          DO i=1, klon
    1532              IF (pctsrf(i,is_oce).GT.epsfra.OR. &
    1533                   pctsrf(i,is_sic).GT.epsfra) THEN
     1532             IF (pctsrf(i,is_oce)>epsfra.OR. &
     1533                  pctsrf(i,is_sic)>epsfra) THEN
    15341534                zx_tmp_fi2d(i) = (ftsol(i, is_oce) * pctsrf(i,is_oce)+ &
    15351535                     ftsol(i, is_sic) * pctsrf(i,is_sic))/ &
     
    15431543
    15441544       ! Couplage convection-couche limite
    1545        IF (iflag_con.GE.3) THEN
     1545       IF (iflag_con>=3) THEN
    15461546          IF (iflag_coupl>=1) THEN
    15471547             CALL histwrite_phy(o_ale_bl, ale_bl)
     
    15501550       ENDIF !(iflag_con.GE.3)
    15511551       ! Wakes
    1552        IF (iflag_con.EQ.3) THEN
     1552       IF (iflag_con==3) THEN
    15531553          CALL histwrite_phy(o_Mipsh, Mipsh)
    15541554          IF (iflag_wake>=1) THEN
     
    16201620          CALL histwrite_phy(o_fqd, fqd)
    16211621       ENDIF !(iflag_con.EQ.3)
    1622        IF (iflag_con.EQ.3.OR.iflag_con.EQ.30) THEN
     1622       IF (iflag_con==3.OR.iflag_con==30) THEN
    16231623          ! sortie RomP convection descente insaturee iflag_con=30
    16241624          ! etendue a iflag_con=3 (jyg)
     
    16511651       IF (type_ocean=='slab ') THEN
    16521652          CALL histwrite_phy(o_slab_bils, slab_wfbils)
    1653           IF (nslay.EQ.1) THEN
     1653          IF (nslay==1) THEN
    16541654              IF (vars_defined) zx_tmp_fi2d(:)=tslab(:,1)
    16551655              CALL histwrite_phy(o_tslab, zx_tmp_fi2d)
     
    16691669          ENDIF
    16701670          IF (slab_hdiff) THEN
    1671             IF (nslay.EQ.1) THEN
     1671            IF (nslay==1) THEN
    16721672                IF (vars_defined) zx_tmp_fi2d(:)=dt_hdiff(:,1)
    16731673                CALL histwrite_phy(o_slab_hdiff, zx_tmp_fi2d)
     
    16761676            ENDIF
    16771677          ENDIF
    1678           IF (slab_ekman.GT.0) THEN
    1679             IF (nslay.EQ.1) THEN
     1678          IF (slab_ekman>0) THEN
     1679            IF (nslay==1) THEN
    16801680                IF (vars_defined) zx_tmp_fi2d(:)=dt_ekman(:,1)
    16811681                CALL histwrite_phy(o_slab_ekman, zx_tmp_fi2d)
     
    17021702       IF (vars_defined) THEN
    17031703          DO i=1, klon
    1704              IF (zt2m(i).LE.273.15) then
     1704             IF (zt2m(i)<=273.15) then
    17051705                zx_tmp_fi2d(i)=MAX(0.,rh2m(i)*100.)
    17061706             ELSE
     
    17441744!This is warranted by treating INCA aerosols as offline aerosols
    17451745#ifndef CPP_ECRAD
    1746        IF (flag_aerosol.GT.0) THEN
     1746       IF (flag_aerosol>0) THEN
    17471747          IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
    17481748
     
    17771777       ENDIF
    17781778       !--STRAT AER
    1779        IF (flag_aerosol.GT.0.OR.flag_aerosol_strat.GT.0) THEN
     1779       IF (flag_aerosol>0.OR.flag_aerosol_strat>0) THEN
    17801780          DO naero = 1, naero_tot
    17811781             CALL histwrite_phy(o_tausumaero(naero),tausum_aero(:,2,naero))
    17821782          ENDDO
    17831783       ENDIF
    1784        IF (flag_aerosol_strat.GT.0) THEN
     1784       IF (flag_aerosol_strat>0) THEN
    17851785          CALL histwrite_phy(o_tausumaero_lw,tausum_aero(:,6,id_STRAT_phy))
    17861786       ENDIF
     
    19331933          CALL histwrite_phy(o_sollwai, zx_tmp_fi2d)
    19341934       ENDIF
    1935        IF (flag_aerosol.GT.0.AND.ok_cdnc) THEN
     1935       IF (flag_aerosol>0.AND.ok_cdnc) THEN
    19361936          CALL histwrite_phy(o_scdnc, scdnc)
    19371937          CALL histwrite_phy(o_cldncl, cldncl)
     
    20022002#endif
    20032003
    2004        IF (flag_aerosol_strat.EQ.2) THEN
     2004       IF (flag_aerosol_strat==2) THEN
    20052005         CALL histwrite_phy(o_stratomask, stratomask)
    20062006       ENDIF
     
    20302030       CALL histwrite_phy(o_rnebjn, zx_tmp_fi3d)
    20312031       CALL histwrite_phy(o_rhum, zx_rh)
    2032        IF (iflag_ice_thermo .GT. 0) THEN
     2032       IF (iflag_ice_thermo > 0) THEN
    20332033          IF (vars_defined) zx_tmp_fi3d = zx_rhl * 100.
    20342034          CALL histwrite_phy(o_rhl, zx_tmp_fi3d)
     
    21112111       CALL histwrite_phy(o_dqlphy2d,  zx_tmp_fi2d)
    21122112
    2113        IF (nqo.EQ.3) THEN
     2113       IF (nqo==3) THEN
    21142114       CALL histwrite_phy(o_dqsphy,  d_qx(:,:,isol))
    21152115       IF (vars_defined) CALL water_int(klon,klev,d_qx(:,:,isol),zmasse,zx_tmp_fi2d)
     
    21952195       ENDIF
    21962196       CALL histwrite_phy(o_dtcon, zx_tmp_fi3d)
    2197        IF (iflag_thermals.EQ.0) THEN
     2197       IF (iflag_thermals==0) THEN
    21982198          IF (vars_defined) THEN
    21992199             zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + &
     
    22012201          ENDIF
    22022202          CALL histwrite_phy(o_tntc, zx_tmp_fi3d)
    2203        ELSE IF(iflag_thermals.GE.1.AND.iflag_wake.EQ.1) THEN
     2203       ELSE IF(iflag_thermals>=1.AND.iflag_wake==1) THEN
    22042204          IF (vars_defined) THEN
    22052205             zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + &
     
    22182218       CALL histwrite_phy(o_dqcon2d, zx_tmp_fi2d)
    22192219
    2220        IF (iflag_thermals.EQ.0) THEN
     2220       IF (iflag_thermals==0) THEN
    22212221          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys
    22222222          CALL histwrite_phy(o_tnhusc, zx_tmp_fi3d)
    2223        ELSE IF (iflag_thermals.GE.1.AND.iflag_wake.EQ.1) THEN
     2223       ELSE IF (iflag_thermals>=1.AND.iflag_wake==1) THEN
    22242224          IF (vars_defined) THEN
    22252225             zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys + &
     
    26942694             DO k=1, nlevSTD
    26952695                DO i=1, klon
    2696                    IF (O3STD(i,k).NE.missing_val) THEN
     2696                   IF (O3STD(i,k)/=missing_val) THEN
    26972697                      zx_tmp_fi3d_STD(i,k) = O3STD(i,k) * 1.e+9
    26982698                   ELSE
     
    27072707                DO k=1, nlevSTD
    27082708                   DO i=1, klon
    2709                       IF (O3daySTD(i,k).NE.missing_val) THEN
     2709                      IF (O3daySTD(i,k)/=missing_val) THEN
    27102710                         zx_tmp_fi3d_STD(i,k) = O3daySTD(i,k) * 1.e+9
    27112711                      ELSE
  • LMDZ6/trunk/libf/phylmd/phys_state_var_mod.F90

    r4984 r5075  
    1010! Declaration des variables
    1111      USE dimphy
    12       USE netcdf, only: nf90_fill_real
     12      USE lmdz_netcdf, only: nf90_fill_real
    1313      INTEGER, PARAMETER :: nlevSTD=17
    1414      INTEGER, PARAMETER :: nlevSTD8=8
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r5066 r5075  
    4848    USE mod_phys_lmdz_para
    4949    USE netcdf95, only: nf95_close
    50     USE netcdf, only: nf90_fill_real     ! IM for NMC files
     50    USE lmdz_netcdf, only: nf90_fill_real     ! IM for NMC files
    5151    USE open_climoz_m, only: open_climoz ! ozone climatology from a file
    5252    USE ozonecm_m, only: ozonecm ! ozone of J.-F. Royer
  • LMDZ6/trunk/libf/phylmd/plevel.F90

    r4619 r5075  
    77  ! ================================================================
    88  ! ================================================================
    9   USE netcdf
     9  USE lmdz_netcdf, ONLY: nf90_fill_real
    1010  USE dimphy
    1111#ifdef CPP_IOIPSL
  • LMDZ6/trunk/libf/phylmd/plevel_new.F90

    r4619 r5075  
    88  ! ================================================================
    99  ! ================================================================
    10   USE netcdf
    1110  USE dimphy
    1211#ifdef CPP_IOIPSL
  • LMDZ6/trunk/libf/phylmd/press_coefoz_m.F90

    r4489 r5075  
    2424
    2525    use netcdf95, only: nf95_open, nf95_close, nf95_gw_var, nf95_inq_varid
    26     use netcdf, only: nf90_nowrite
     26    use lmdz_netcdf, only: nf90_nowrite
    2727
    2828    use mod_phys_lmdz_mpi_data, only: is_mpi_root
  • LMDZ6/trunk/libf/phylmd/read_map2D.F90

    r2311 r5075  
    33! Return variable for the given timestep.
    44  USE dimphy
    5   USE netcdf
     5  USE lmdz_netcdf, ONLY: nf90_open,nf90_close,nf90_nowrite,nf90_noerr,nf90_get_var,nf90_inq_varid
    66  USE mod_grid_phy_lmdz
    77  USE mod_phys_lmdz_para
  • LMDZ6/trunk/libf/phylmd/read_pstoke.F90

    r4262 r5075  
    1717  ! ******************************************************************************
    1818
    19   USE netcdf
     19  USE lmdz_netcdf, ONLY: nf90_open,nf90_inq_varid,nf90_nowrite,nf90_get_var,nf_inq_dim,&
     20          nf_inq_dimid
    2021  USE dimphy
    2122  USE indice_sol_mod
     
    2324
    2425  IMPLICIT NONE
    25 
    26   include "netcdf.inc"
    2726
    2827  INTEGER klono, klevo, imo, jmo
  • LMDZ6/trunk/libf/phylmd/read_pstoke0.F90

    r5073 r5075  
    1616  ! ******************************************************************************
    1717
    18   USE netcdf
     18  USE lmdz_netcdf, ONLY: nf_inq_dimid,nf_inq_dim,nf90_get_var,nf90_inq_varid,nf90_open,&
     19          nf90_nowrite
    1920  USE dimphy
    2021  USE indice_sol_mod
     
    2223
    2324  IMPLICIT NONE
    24 
    25   include "netcdf.inc"
    2625
    2726  INTEGER kon, kev, zkon, zkev
     
    253252    ! niveaux de pression
    254253
    255     status = nf_get_vara_real(ncidp, varidpl, 1, kev, pl)
     254    status = nf90_get_var(ncidp, varidpl, pl, [1], [kev])
    256255
    257256    ! lecture de aire et phis
  • LMDZ6/trunk/libf/phylmd/readaerosol_mod.F90

    r4627 r5075  
    22!
    33MODULE readaerosol_mod
     4
     5  USE lmdz_netcdf, ONLY: nf90_strerror,nf90_noerr,nf90_get_var,nf90_inq_varid,&
     6          nf90_inquire_dimension,nf90_inq_dimid,nf90_open,nf90_nowrite,nf90_close
    47
    58  REAL, SAVE :: not_valid=-333.
     
    8689! Read data depending on actual year and interpolate if necessary
    8790!****************************************************************************************
    88      IF (iyr_in .LT. 1850) THEN
     91     IF (iyr_in < 1850) THEN
    8992        cyear='.nat'
    9093        WRITE(lunout,*) 'get_aero 1 iyr_in=', iyr_in,'   ',cyear
     
    9396        CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, pt_out, psurf, load)
    9497       
    95      ELSE IF (iyr_in .GE. 2100) THEN
     98     ELSE IF (iyr_in >= 2100) THEN
    9699        cyear='2100'
    97100        WRITE(lunout,*) 'get_aero 2 iyr_in=', iyr_in,'   ',cyear
     
    103106        ! Read data from 2 decades and interpolate to actual year
    104107        ! a) from actual 10-yr-period
    105         IF (iyr_in.LT.1900) THEN
     108        IF (iyr_in<1900) THEN
    106109           iyr1 = 1850
    107110           iyr2 = 1900
    108         ELSE IF (iyr_in.GE.1900.AND.iyr_in.LT.1920) THEN
     111        ELSE IF (iyr_in>=1900.AND.iyr_in<1920) THEN
    109112           iyr1 = 1900
    110113           iyr2 = 1920
     
    174177
    175178SUBROUTINE init_aero_fromfile(flag_aerosol, aerosol_couple)
    176   USE netcdf
    177179  USE mod_phys_lmdz_para
    178180  USE mod_grid_phy_lmdz, ONLY: grid_type, unstructured
     
    265267!****************************************************************************************
    266268
    267     USE netcdf
    268269    USE dimphy
    269270    USE mod_grid_phy_lmdz, ONLY: nbp_lon_=>nbp_lon, nbp_lat_=>nbp_lat, klon_glo, &
     
    507508!****************************************************************************************
    508509          DO imth=1, 12
    509              IF (imth.EQ.1) THEN
     510             IF (imth==1) THEN
    510511                cvar=TRIM(varname)//'JAN'
    511              ELSE IF (imth.EQ.2) THEN
     512             ELSE IF (imth==2) THEN
    512513                cvar=TRIM(varname)//'FEB'
    513              ELSE IF (imth.EQ.3) THEN
     514             ELSE IF (imth==3) THEN
    514515                cvar=TRIM(varname)//'MAR'
    515              ELSE IF (imth.EQ.4) THEN
     516             ELSE IF (imth==4) THEN
    516517                cvar=TRIM(varname)//'APR'
    517              ELSE IF (imth.EQ.5) THEN
     518             ELSE IF (imth==5) THEN
    518519                cvar=TRIM(varname)//'MAY'
    519              ELSE IF (imth.EQ.6) THEN
     520             ELSE IF (imth==6) THEN
    520521                cvar=TRIM(varname)//'JUN'
    521              ELSE IF (imth.EQ.7) THEN
     522             ELSE IF (imth==7) THEN
    522523                cvar=TRIM(varname)//'JUL'
    523              ELSE IF (imth.EQ.8) THEN
     524             ELSE IF (imth==8) THEN
    524525                cvar=TRIM(varname)//'AUG'
    525              ELSE IF (imth.EQ.9) THEN
     526             ELSE IF (imth==9) THEN
    526527                cvar=TRIM(varname)//'SEP'
    527              ELSE IF (imth.EQ.10) THEN
     528             ELSE IF (imth==10) THEN
    528529                cvar=TRIM(varname)//'OCT'
    529              ELSE IF (imth.EQ.11) THEN
     530             ELSE IF (imth==11) THEN
    530531                cvar=TRIM(varname)//'NOV'
    531              ELSE IF (imth.EQ.12) THEN
     532             ELSE IF (imth==12) THEN
    532533                cvar=TRIM(varname)//'DEC'
    533534             END IF
     
    716717
    717718  SUBROUTINE check_err(status,text)
    718     USE netcdf
    719719    USE print_control_mod, ONLY: lunout
    720720    IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/readaerosolstrato.F90

    r4619 r5075  
    33    use netcdf95, only: nf95_close, nf95_gw_var, nf95_inq_dimid, &
    44                        nf95_inq_varid, nf95_open
    5     use netcdf, only: nf90_get_var, nf90_noerr, nf90_nowrite
     5    use lmdz_netcdf, only: nf90_get_var, nf90_noerr, nf90_nowrite
    66
    77    USE phys_cal_mod, ONLY : mth_cur
     
    6868
    6969!--only read file if beginning of run or start of new month
    70     IF (debut.OR.mth_cur.NE.mth_pre) THEN
     70    IF (debut.OR.mth_cur/=mth_pre) THEN
    7171
    7272!--only root reads
    7373    IF (is_mpi_root.AND.is_omp_root) THEN
    7474
    75     IF (nbands.NE.2) THEN
     75    IF (nbands/=2) THEN
    7676        abort_message='nbands doit etre egal a 2 dans readaerosolstrat'
    7777        CALL abort_physic(modname,abort_message,1)
     
    8383    CALL nf95_gw_var(ncid_in, varid, lev)
    8484    n_lev = size(lev)
    85     IF (n_lev.NE.klev) THEN
     85    IF (n_lev/=klev) THEN
    8686       abort_message='Le nombre de niveaux n est pas egal a klev'
    8787       CALL abort_physic(modname,abort_message,1)
     
    9393    WRITE(lunout,*) 'LAT aerosol strato=', n_lat, latitude
    9494    IF (grid_type/=unstructured) THEN
    95       IF (n_lat.NE.nbp_lat) THEN
     95      IF (n_lat/=nbp_lat) THEN
    9696         abort_message='Le nombre de lat n est pas egal a nbp_lat'
    9797         CALL abort_physic(modname,abort_message,1)
     
    104104    IF (grid_type/=unstructured) THEN
    105105      WRITE(lunout,*) 'LON aerosol strato=', n_lon, longitude
    106       IF (n_lon.NE.nbp_lon) THEN
     106      IF (n_lon/=nbp_lon) THEN
    107107         abort_message='Le nombre de lon n est pas egal a nbp_lon'
    108108         CALL abort_physic(modname,abort_message,1)
     
    114114    n_month = size(time)
    115115    WRITE(lunout,*) 'TIME aerosol strato=', n_month, time
    116     IF (n_month.NE.12) THEN
     116    IF (n_month/=12) THEN
    117117       abort_message='Le nombre de month n est pas egal a 12'
    118118       CALL abort_physic(modname,abort_message,1)
     
    131131
    132132!---select the correct month
    133     IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN
     133    IF (mth_cur<1.OR.mth_cur>12) THEN
    134134     WRITE(lunout,*) 'probleme avec le mois dans readaerosolstrat =', mth_cur
    135135    ENDIF
  • LMDZ6/trunk/libf/phylmd/readaerosolstrato_m.F90

    r4619 r5075  
    2424
    2525SUBROUTINE init_readaerosolstrato1
    26   USE netcdf
    27   USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, & 
     26  USE lmdz_netcdf, ONLY: nf90_nowrite
     27  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
    2828                      nf95_inq_varid, nf95_open
    2929  USE mod_phys_lmdz_para
     
    6767 
    6868SUBROUTINE init_readaerosolstrato2
    69   USE netcdf
    70   USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, & 
     69  USE lmdz_netcdf, ONLY: nf90_nowrite
     70  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
    7171                      nf95_inq_varid, nf95_open
    7272  USE mod_phys_lmdz_para
  • LMDZ6/trunk/libf/phylmd/readchlorophyll.F90

    r4489 r5075  
    88
    99    USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, nf95_inq_varid, nf95_open
    10     USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
     10    USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
    1111    USE phys_cal_mod, ONLY: mth_cur
    1212    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, grid2dto1d_glo
     
    5050
    5151!--only read file if beginning of run or start of new month
    52     IF (debut.OR.mth_cur.NE.mth_pre) THEN
     52    IF (debut.OR.mth_cur/=mth_pre) THEN
    5353
    5454    IF (is_mpi_root.AND.is_omp_root) THEN
     
    5959    CALL nf95_gw_var(ncid_in, varid, longitude)
    6060    n_lon = size(longitude)
    61     IF (n_lon.NE.nbp_lon) THEN
     61    IF (n_lon/=nbp_lon) THEN
    6262       abort_message='Le nombre de lon n est pas egal a nbp_lon'
    6363       CALL abort_physic(modname,abort_message,1)
     
    6767    CALL nf95_gw_var(ncid_in, varid, latitude)
    6868    n_lat = size(latitude)
    69     IF (n_lat.NE.nbp_lat) THEN
     69    IF (n_lat/=nbp_lat) THEN
    7070       abort_message='Le nombre de lat n est pas egal a jnbp_lat'
    7171       CALL abort_physic(modname,abort_message,1)
     
    7575    CALL nf95_gw_var(ncid_in, varid, time)
    7676    n_month = size(time)
    77     IF (n_month.NE.12) THEN
     77    IF (n_month/=12) THEN
    7878       abort_message='Le nombre de month n est pas egal a 12'
    7979       CALL abort_physic(modname,abort_message,1)
     
    9292
    9393!---select the correct month
    94     IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN
     94    IF (mth_cur<1.OR.mth_cur>12) THEN
    9595      WRITE(lunout,*)'probleme avec le mois dans readchlorophyll =', mth_cur
    9696    ENDIF
     
    104104!      if(isnan(chlorocon_mois_glo(i)))then ! isnan() is not in the Fortran standard...
    105105!      Another way to check for NaN:
    106        IF (chlorocon_mois_glo(i).NE.chlorocon_mois_glo(i)) chlorocon_mois_glo(i)=0.
     106       IF (chlorocon_mois_glo(i)/=chlorocon_mois_glo(i)) chlorocon_mois_glo(i)=0.
    107107    ENDDO
    108108
  • LMDZ6/trunk/libf/phylmd/regr_horiz_time_climoz_m.F90

    r4847 r5075  
    44  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, grid_type, unstructured
    55  USE nrtype,            ONLY: pi
    6   USE netcdf,   ONLY: NF90_CLOBBER, NF90_FLOAT,     NF90_OPEN,   &
     6  USE lmdz_netcdf,   ONLY: NF90_CLOBBER, NF90_FLOAT,     NF90_OPEN,   &
    77                      NF90_NOWRITE, NF90_NOERR,     NF90_GET_ATT, NF90_GLOBAL
    88  USE netcdf95, ONLY: NF95_DEF_DIM, NF95_INQ_DIMID, NF95_INQUIRE_DIMENSION,    &
     
    702702!
    703703!-------------------------------------------------------------------------------
    704   USE netcdf, ONLY: NF90_NOERR, NF90_strerror
     704  USE lmdz_netcdf, ONLY: NF90_NOERR, NF90_strerror
    705705!-------------------------------------------------------------------------------
    706706! Arguments:
  • LMDZ6/trunk/libf/phylmd/regr_lat_time_coefoz_m.F90

    r4489 r5075  
    4545    use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, nf95_get_var, &
    4646         nf95_put_var, nf95_gw_var
    47     use netcdf, only: nf90_nowrite
     47    use lmdz_netcdf, only: nf90_nowrite
    4848    use nrtype, only: pi
    4949    use regular_lonlat_mod, only: boundslat_reg, south
     
    245245    use netcdf95, only: nf95_create, nf95_def_dim, nf95_def_var, &
    246246         nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var
    247     use netcdf, only: nf90_clobber, nf90_float, nf90_copy_att, nf90_global
     247    use lmdz_netcdf, only: nf90_clobber, nf90_float, nf90_copy_att, nf90_global
    248248    use nrtype, only: pi
    249249    use regular_lonlat_mod, only : lat_reg
     
    328328    subroutine handle_err_copy_att(att_name)
    329329
    330       use netcdf, only: nf90_noerr, nf90_strerror
     330      use lmdz_netcdf, only: nf90_noerr, nf90_strerror
    331331
    332332      character(len=*), intent(in):: att_name
  • LMDZ6/trunk/libf/phylmd/regr_pr_comb_coefoz_m.F90

    r3086 r5075  
    7272
    7373    use netcdf95, only: nf95_open, nf95_close
    74     use netcdf, only: nf90_nowrite
     74    use lmdz_netcdf, only: nf90_nowrite
    7575    use assert_m, only: assert
    7676    use dimphy, only: klon
  • LMDZ6/trunk/libf/phylmd/regr_pr_o3_m.F90

    r4489 r5075  
    2626
    2727    use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, nf95_get_var
    28     use netcdf, only:  nf90_nowrite
     28    use lmdz_netcdf, only:  nf90_nowrite
    2929    use assert_m, only: assert
    3030    use regr_conserv_m, only: regr_conserv
  • LMDZ6/trunk/libf/phylmd/regr_pr_time_av_m.F90

    r4489 r5075  
    115115  USE netcdf95,       ONLY: NF95_INQ_VARID, NF95_INQUIRE_VARIABLE, &
    116116                            NF95_INQ_DIMID, NF95_INQUIRE_DIMENSION, nf95_get_var
    117   USE netcdf,         ONLY: NF90_INQ_VARID, NF90_NOERR
     117  USE lmdz_netcdf,         ONLY: NF90_INQ_VARID, NF90_NOERR
    118118  USE assert_m,       ONLY: assert
    119119  USE assert_eq_m,    ONLY: assert_eq
  • LMDZ6/trunk/libf/phylmd/rrtm/read_rsun_rrtm.F90

    r4489 r5075  
    88
    99  USE netcdf95, ONLY: nf95_close, nf95_inq_varid, nf95_open, nf95_gw_var
    10   USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
     10  USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
    1111
    1212  USE phys_cal_mod, ONLY : days_elapsed, year_len
  • LMDZ6/trunk/libf/phylmd/rrtm/readaerosolstrato1_rrtm.F90

    r4619 r5075  
    77    USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
    88                        nf95_inq_varid, nf95_open
    9     USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
     9    USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
    1010
    1111    USE phys_cal_mod, ONLY : mth_cur
  • LMDZ6/trunk/libf/phylmd/rrtm/readaerosolstrato2_rrtm.F90

    r4619 r5075  
    66    USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
    77                        nf95_inq_varid, nf95_open
    8     USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
     8    USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
    99
    1010    USE phys_cal_mod, ONLY : mth_cur
  • LMDZ6/trunk/libf/phylmd/tracco2i_mod.F90

    r4489 r5075  
    104104
    105105! Initialization of tr_seri(id_CO2) If it is not initialized
    106       IF (MAXVAL(tr_seri(:,:,id_CO2)).LT.1.e-15) THEN
     106      IF (MAXVAL(tr_seri(:,:,id_CO2))<1.e-15) THEN
    107107        tr_seri(:,:,id_CO2)=co2_ppm0*1.e-6/RMD*RMCO2 !--initialised from co2_ppm0 in rdem
    108108      ENDIF
     
    299299!--for every timestep comment out the IF ENDIF statements
    300300!--otherwise this is updated every day
    301     IF (debutphy.OR.day_cur.NE.day_pre) THEN
     301    IF (debutphy.OR.day_cur/=day_pre) THEN
    302302
    303303      CALL gather(tr_seri(:,:,id_CO2),co2_glo)
     
    351351
    352352    USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_varid, nf95_open
    353     USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
     353    USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
    354354
    355355    USE carbon_cycle_mod, ONLY : fco2_ff, fco2_bb, fco2_land, fco2_ocean
     
    401401        CALL nf95_gw_var(ncid_in, varid, vector)
    402402        n_glo = size(vector)
    403         IF (n_glo.NE.klon_glo) THEN
     403        IF (n_glo/=klon_glo) THEN
    404404           abort_message='sflx_lmdz_co2_ff: le nombre de points n est pas egal a klon_glo'
    405405           CALL abort_physic(modname,abort_message,1)
     
    409409        CALL nf95_gw_var(ncid_in, varid, time)
    410410        n_month = size(time)
    411         IF (n_month.NE.12) THEN
     411        IF (n_month/=12) THEN
    412412           abort_message='sflx_lmdz_co2_ff: le nombre de month n est pas egal a 12'
    413413           CALL abort_physic(modname,abort_message,1)
     
    434434      CALL nf95_gw_var(ncid_in, varid, vector)
    435435      n_glo = size(vector)
    436       IF (n_glo.NE.klon_glo) THEN
     436      IF (n_glo/=klon_glo) THEN
    437437         abort_message='sflx_lmdz_co2_bb: le nombre de points n est pas egal a klon_glo'
    438438         CALL abort_physic(modname,abort_message,1)
     
    442442      CALL nf95_gw_var(ncid_in, varid, time)
    443443      n_month = size(time)
    444       IF (n_month.NE.12) THEN
     444      IF (n_month/=12) THEN
    445445         abort_message='sflx_lmdz_co2_bb: le nombre de month n est pas egal a 12'
    446446         CALL abort_physic(modname,abort_message,1)
     
    474474
    475475!---select the correct month
    476   IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN
     476  IF (mth_cur<1.OR.mth_cur>12) THEN
    477477    PRINT *,'probleme avec le mois dans co2_ini =', mth_cur
    478478  ENDIF
  • LMDZ6/trunk/libf/phylmd/undefSTD.F90

    r4619 r5075  
    33
    44SUBROUTINE undefstd(itap, read_climoz)
    5   USE netcdf
     5  USE lmdz_netcdf, ONLY: nf90_fill_real
    66  USE dimphy
    77#ifdef CPP_IOIPSL
  • LMDZ6/trunk/libf/phylmdiso/isotopes_routines_mod.F90

    r4982 r5075  
    1587115871  USE isotopes_verif_mod
    1587215872#endif
    15873 
    1587415873       implicit none   
    1587515874
    1587615875      ! equivalent de phyetat0 pour les isotopes 
    1587715876
    15878 #include "netcdf.inc"
    1587915877#include "dimsoil.h"
    1588015878#include "clesphys.h"
     
    1642916427   IMPLICIT NONE
    1643016428
    16431 #include "netcdf.inc"
    1643216429#include "dimsoil.h"
    1643316430#include "clesphys.h"
  • LMDZ6/trunk/libf/phylmdiso/limit_read_mod.F90

    r4619 r5075  
    274274    USE mod_phys_lmdz_para
    275275    USE surface_data, ONLY : type_ocean, ok_veget
    276     USE netcdf
     276    USE lmdz_netcdf, ONLY:nf90_noerr,nf90_close,nf90_get_var,nf90_inq_varid,nf90_nowrite,&
     277            nf90_inq_dimid,nf90_inquire_dimension,nf90_open
    277278    USE indice_sol_mod
    278279#ifdef ISO
  • LMDZ6/trunk/libf/phylmdiso/phyaqua_mod.F90

    r5073 r5075  
    147147    !END IF
    148148   
    149     if (year_len.ne.360) then
     149    if (year_len/=360) then
    150150      write (*,*) year_len
    151151      write (*,*) 'iniaqua: 360 day calendar is required !'
     
    960960      END IF
    961961
    962       if (type_profil.EQ.20) then
     962      if (type_profil==20) then
    963963      print*,'Profile SST 20'
    964964!     Méthode 13 "Qmax2K" plateau réel �|  l'Equateur augmenté +2K
     
    969969      endif
    970970
    971       if (type_profil.EQ.21) then
     971      if (type_profil==21) then
    972972      print*,'Profile SST 21'
    973973!     Méthode 13 "Qmax2K" plateau réel �|  l'Equateur augmenté +2K
  • LMDZ6/trunk/libf/phylmdiso/phyetat0_mod.F90

    r4982 r5075  
    4848  USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy
    4949  USE wxios, ONLY: missing_val_xios => missing_val, using_xios
    50   use netcdf, only: missing_val_netcdf => nf90_fill_real
     50  use lmdz_netcdf, only: missing_val_netcdf => nf90_fill_real
    5151  use config_ocean_skin_m, only: activate_ocean_skin
    5252#ifdef ISO
  • LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90

    r5066 r5075  
    4848    USE mod_phys_lmdz_para
    4949    USE netcdf95, only: nf95_close
    50     USE netcdf, only: nf90_fill_real     ! IM for NMC files
     50    USE lmdz_netcdf, only: nf90_fill_real     ! IM for NMC files
    5151    USE open_climoz_m, only: open_climoz ! ozone climatology from a file
    5252    USE ozonecm_m, only: ozonecm ! ozone of J.-F. Royer
  • LMDZ6/trunk/tools/make_sso/make_sso_SpherePack.f90

    r4168 r5075  
    66! Purpose: Project ETOPO file (GMT4 axes conventions) on spherical harmonics.
    77!-------------------------------------------------------------------------------
    8   USE netcdf
     8  USE lmdz_netcdf, ONLY: nf90_noerr,nf90_strerror,nf90_close,nf90_put_var,nf90_enddef,&
     9          nf90_put_att,nf90_global,nf90_real,nf90_def_var,nf90_def_dim,nf90_inq_varid,&
     10          nf90_nowrite,nf90_inquire_dimension,nf90_inquire_variable,nf90_open
    911!  USE sphpack
    1012  IMPLICIT NONE
  • LMDZ6/trunk/tools/netcdf95/Attributes/nf95_copy_att.f90

    r4918 r5075  
    88  subroutine nf95_copy_att(ncid_in, varid_in, name, ncid_out, varid_out, ncerr)
    99
    10     use netcdf, only: nf90_copy_att
     10    use lmdz_netcdf, only: nf90_copy_att
    1111
    1212    use nf95_abort_m, only: nf95_abort
  • LMDZ6/trunk/tools/netcdf95/Attributes/nf95_get_att.f90

    r4918 r5075  
    22
    33  use nf95_abort_m, only: nf95_abort
    4   use netcdf, only: nf90_get_att, nf90_noerr
     4  use lmdz_netcdf, only: nf90_get_att, nf90_noerr
    55  use nf95_inquire_attribute_m, only: nf95_inquire_attribute
    66  use nf95_constants, only: nf95_noerr
  • LMDZ6/trunk/tools/netcdf95/Attributes/nf95_get_missing.F90

    r4918 r5075  
    11module nf95_get_missing_m
    22
    3   use netcdf, only: nf90_noerr
     3  use lmdz_netcdf, only: nf90_noerr
    44  use nf95_get_att_m, only: nf95_get_att
    55
     
    1818  subroutine nf95_get_missing_real(ncid, varid, missing)
    1919
    20     use netcdf, only: NF90_FILL_REAL
     20    use lmdz_netcdf, only: NF90_FILL_REAL
    2121    use typesizes, only: FourByteReal
    2222
     
    4444  subroutine nf95_get_missing_dble(ncid, varid, missing)
    4545
    46     use netcdf, only: NF90_FILL_double
     46    use lmdz_netcdf, only: NF90_FILL_double
    4747    use typesizes, only: EightByteReal
    4848
     
    7070  subroutine nf95_get_missing_short_int(ncid, varid, missing)
    7171
    72     use netcdf, only: NF90_FILL_short
     72    use lmdz_netcdf, only: NF90_FILL_short
    7373    use typesizes, only: TwoByteInt
    7474
     
    9696  subroutine nf95_get_missing_int(ncid, varid, missing)
    9797
    98     use netcdf, only: NF90_FILL_INT
     98    use lmdz_netcdf, only: NF90_FILL_INT
    9999
    100100    integer, intent(in)::  ncid, varid
     
    121121  subroutine nf95_get_missing_char(ncid, varid, missing)
    122122
    123     use netcdf, only: NF90_FILL_char
     123    use lmdz_netcdf, only: NF90_FILL_char
    124124
    125125    integer, intent(in)::  ncid, varid
  • LMDZ6/trunk/tools/netcdf95/Attributes/nf95_inquire_attribute.f90

    r4918 r5075  
    1010
    1111    use nf95_abort_m, only: nf95_abort
    12     use netcdf, only: nf90_inquire_attribute
     12    use lmdz_netcdf, only: nf90_inquire_attribute
    1313    use nf95_constants, only: nf95_noerr
    1414
  • LMDZ6/trunk/tools/netcdf95/Attributes/nf95_put_att.f90

    r4918 r5075  
    11module nf95_put_att_m
    22
    3   use netcdf, only: nf90_put_att
     3  use lmdz_netcdf, only: nf90_put_att
    44  use nf95_abort_m, only: nf95_abort
    55  use nf95_constants, only: nf95_noerr
  • LMDZ6/trunk/tools/netcdf95/Datasets/nf95_close.f90

    r4918 r5075  
    1010    ! call it.
    1111
    12     use netcdf, only: nf90_close, nf90_strerror
     12    use lmdz_netcdf, only: nf90_close, nf90_strerror
    1313
    1414    use nf95_constants, only: nf95_noerr
  • LMDZ6/trunk/tools/netcdf95/Datasets/nf95_create.f90

    r4918 r5075  
    88
    99    use nf95_abort_m, only: nf95_abort
    10     use netcdf, only: nf90_create
     10    use lmdz_netcdf, only: nf90_create
    1111    use nf95_constants, only: nf95_noerr
    1212
  • LMDZ6/trunk/tools/netcdf95/Datasets/nf95_create_single.f90

    r4918 r5075  
    11module nf95_create_single_m
    22
    3   use netcdf, only: NF90_MAX_NAME
     3  use lmdz_netcdf, only: NF90_MAX_NAME
    44
    55  implicit none
     
    1919    ! Shortcut to create a file containing a single primary variable.
    2020
    21     use netcdf, only: NF90_CLOBBER, NF90_FLOAT
     21    use lmdz_netcdf, only: NF90_CLOBBER, NF90_FLOAT
    2222
    2323    use nf95_create_m, only: nf95_create
  • LMDZ6/trunk/tools/netcdf95/Datasets/nf95_enddef.f90

    r4918 r5075  
    88
    99    use nf95_abort_m, only: nf95_abort
    10     use netcdf, only: nf90_enddef
     10    use lmdz_netcdf, only: nf90_enddef
    1111    use nf95_constants, only: nf95_noerr
    1212
  • LMDZ6/trunk/tools/netcdf95/Datasets/nf95_find_coord.f90

    r4918 r5075  
    1515    ! attribute "std_name".
    1616
    17     use netcdf, only: NF90_MAX_NAME, NF90_NOERR
     17    use lmdz_netcdf, only: NF90_MAX_NAME, NF90_NOERR
    1818    use nf95_get_att_m, only: nf95_get_att
    1919    use nf95_inq_varid_m, only: nf95_inq_varid
  • LMDZ6/trunk/tools/netcdf95/Datasets/nf95_inquire.f90

    r4918 r5075  
    1010   
    1111    use nf95_abort_m, only: nf95_abort
    12     use netcdf, only: nf90_inquire
     12    use lmdz_netcdf, only: nf90_inquire
    1313    use nf95_constants, only: nf95_noerr
    1414
  • LMDZ6/trunk/tools/netcdf95/Datasets/nf95_open.f90

    r4918 r5075  
    88
    99    use nf95_abort_m, only: nf95_abort
    10     use netcdf, only: nf90_open
     10    use lmdz_netcdf, only: nf90_open
    1111    use nf95_constants, only: nf95_noerr
    1212
  • LMDZ6/trunk/tools/netcdf95/Datasets/nf95_redef.f90

    r4918 r5075  
    88
    99    use nf95_abort_m, only: nf95_abort
    10     use netcdf, only: nf90_redef
     10    use lmdz_netcdf, only: nf90_redef
    1111    use nf95_constants, only: nf95_noerr
    1212
  • LMDZ6/trunk/tools/netcdf95/Datasets/nf95_sync.f90

    r4918 r5075  
    88
    99    use nf95_abort_m, only: nf95_abort
    10     use netcdf, only: nf90_sync
     10    use lmdz_netcdf, only: nf90_sync
    1111    use nf95_constants, only: nf95_noerr
    1212
  • LMDZ6/trunk/tools/netcdf95/Groups/nf95_inq_file_ncid.f90

    r4918 r5075  
    1111    ! by nf95_abort, so it cannot call it.
    1212
    13     use netcdf, only: nf90_strerror
     13    use lmdz_netcdf, only: nf90_strerror
    1414
    1515    use nf95_constants, only: Nf95_ENOGRP, nf95_noerr
  • LMDZ6/trunk/tools/netcdf95/Groups/nf95_inq_grp_parent.f90

    r4918 r5075  
    1212    use, intrinsic:: ISO_C_BINDING
    1313
    14     use netcdf, only: nf90_strerror
     14    use lmdz_netcdf, only: nf90_strerror
    1515
    1616    use nc_constants, only: NC_NOERR
  • LMDZ6/trunk/tools/netcdf95/Groups/nf95_inq_grps.f90

    r4918 r5075  
    2626    use, intrinsic:: ISO_C_BINDING
    2727
    28     use netcdf, only: nf90_noerr
     28    use lmdz_netcdf, only: nf90_noerr
    2929
    3030    use nc_constants, only: nc_noerr
  • LMDZ6/trunk/tools/netcdf95/Variables/check_start_count.f90

    r4918 r5075  
    1919    use nf95_close_m, only: nf95_close
    2020    use nf95_inquire_variable_m, only: nf95_inquire_variable
    21     use netcdf, only: nf90_noerr
     21    use lmdz_netcdf, only: nf90_noerr
    2222
    2323    character(len=*), intent(in):: name_calling ! name of calling procedure
  • LMDZ6/trunk/tools/netcdf95/Variables/nf95_def_var.f90

    r4918 r5075  
    77  ! "nf95_def_var_scalar" cannot be distinguished from "nf95_def_var_oneDim".
    88
    9   use netcdf, only: nf90_def_var
     9  use lmdz_netcdf, only: nf90_def_var
    1010  use nf95_abort_m, only: nf95_abort
    1111  use nf95_constants, only: nf95_noerr
  • LMDZ6/trunk/tools/netcdf95/Variables/nf95_get_var.f90

    r4918 r5075  
    11module nf95_get_var_m
    22
    3   use netcdf, only: nf90_get_var, NF90_NOERR
     3  use lmdz_netcdf, only: nf90_get_var, NF90_NOERR
    44 
    55  use nf95_abort_m, only: nf95_abort
  • LMDZ6/trunk/tools/netcdf95/Variables/nf95_inq_varid.f90

    r4918 r5075  
    88
    99    use nf95_abort_m, only: nf95_abort
    10     use netcdf, only: nf90_inq_varid
     10    use lmdz_netcdf, only: nf90_inq_varid
    1111    use nf95_constants, only: nf95_noerr
    1212
  • LMDZ6/trunk/tools/netcdf95/Variables/nf95_inquire_variable.f90

    r4918 r5075  
    1616
    1717    use nf95_abort_m, only: nf95_abort
    18     use netcdf, only: nf90_inquire_variable, nf90_max_var_dims
     18    use lmdz_netcdf, only: nf90_inquire_variable, nf90_max_var_dims
    1919    use nf95_constants, only: nf95_noerr
    2020
  • LMDZ6/trunk/tools/netcdf95/Variables/nf95_put_var.f90

    r4918 r5075  
    11module nf95_put_var_m
    22
    3   use netcdf, only: nf90_put_var
     3  use lmdz_netcdf, only: nf90_put_var
    44  use nf95_abort_m, only: nf95_abort
    55  use check_start_count_m, only: check_start_count
  • LMDZ6/trunk/tools/netcdf95/nf95_abort.f90

    r4918 r5075  
    1010
    1111    ! Libraries:
    12     use netcdf, only: nf90_strerror
     12    use lmdz_netcdf, only: nf90_strerror
    1313
    1414    use nf95_close_m, only: nf95_close
  • LMDZ6/trunk/tools/netcdf95/nf95_def_dim.f90

    r4918 r5075  
    88
    99    use nf95_abort_m, only: nf95_abort
    10     use netcdf, only: nf90_def_dim
     10    use lmdz_netcdf, only: nf90_def_dim
    1111    use nf95_constants, only: nf95_noerr
    1212
  • LMDZ6/trunk/tools/netcdf95/nf95_inq_dimid.f90

    r4918 r5075  
    88
    99    use nf95_abort_m, only: nf95_abort
    10     use netcdf, only: nf90_inq_dimid
     10    use lmdz_netcdf, only: nf90_inq_dimid
    1111    use nf95_constants, only: nf95_noerr
    1212
  • LMDZ6/trunk/tools/netcdf95/nf95_inquire_dimension.f90

    r4918 r5075  
    88
    99    use nf95_abort_m, only: nf95_abort
    10     use netcdf, only: nf90_inquire_dimension
     10    use lmdz_netcdf, only: nf90_inquire_dimension
    1111    use nf95_constants, only: nf95_noerr
    1212
Note: See TracChangeset for help on using the changeset viewer.