Changeset 5075
- Timestamp:
- Jul 19, 2024, 10:05:57 AM (4 months ago)
- Location:
- LMDZ6/trunk
- Files:
-
- 108 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/dyn3d/dynetat0.F90
r4984 r5075 8 8 USE infotrac, ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName 9 9 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, & 11 11 NF90_CLOSE, NF90_GET_VAR, NF90_NoErr 12 12 USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3, getKey -
LMDZ6/trunk/libf/dyn3d/dynredem.F90
r4389 r5075 9 9 USE strings_mod, ONLY: maxlen 10 10 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, & 12 12 NF90_CLOSE, NF90_PUT_ATT, NF90_UNLIMITED, NF90_CLOBBER, & 13 13 NF90_64BIT_OFFSET … … 169 169 USE infotrac, ONLY: nqtot, tracers, type_trac 170 170 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, & 172 172 NF90_CLOSE, NF90_WRITE, NF90_PUT_VAR, NF90_NoErr 173 173 USE dynredem_mod, ONLY: dynredem_write_u, dynredem_write_v, dynredem_read_u, & -
LMDZ6/trunk/libf/dyn3d/dynredem_mod.F90
r5069 r5075 1 1 MODULE dynredem_mod 2 2 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 4 5 IMPLICIT NONE; PRIVATE 5 6 PUBLIC :: dynredem_write_u, dynredem_write_v, dynredem_read_u, err -
LMDZ6/trunk/libf/dyn3d/guide_mod.F90
r5071 r5075 72 72 SUBROUTINE guide_init 73 73 74 use netcdf, only: nf90_noerr74 use lmdz_netcdf, only: nf90_noerr 75 75 USE control_mod, ONLY: day_step 76 76 USE serre_mod, ONLY: grossismx -
LMDZ6/trunk/libf/dyn3d/iniacademic.F90
r4984 r5075 22 22 USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0 23 23 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 27 25 28 26 ! Author: Frederic Hourdin original: 15/01/93 … … 143 141 relief=0. 144 142 ierr = NF90_OPEN ('relief_in.nc', NF90_NOWRITE,nid_relief) 145 if (ierr .EQ.NF90_NOERR) THEN143 if (ierr==NF90_NOERR) THEN 146 144 ierr=NF90_INQ_VARID(nid_relief,'RELIEF',varid) 147 145 if (ierr==NF90_NOERR) THEN … … 248 246 tetastrat=ttp*zsig**(-kappa) 249 247 tetapv=tetastrat 250 IF ((ok_pv).AND.(zsig .LT.0.1)) THEN248 IF ((ok_pv).AND.(zsig<0.1)) THEN 251 249 tetapv=tetastrat*(zsig*10.)**(kappa*cpp*gam_pv/1000./g) 252 250 ENDIF -
LMDZ6/trunk/libf/dyn3d_common/grilles_gcm_netcdf_sub.F90
r4357 r5075 14 14 USE comconst_mod, ONLY: cpp, kappa, g, omeg, daysec, rad, pi 15 15 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 17 18 18 19 IMPLICIT NONE … … 21 22 INCLUDE "paramet.h" 22 23 INCLUDE "comgeom.h" 23 INCLUDE "netcdf.inc"24 24 25 25 !======================== … … 232 232 233 233 SUBROUTINE handle_err(status) 234 INCLUDE "netcdf.inc"234 USE lmdz_netcdf, ONLY: nf_strerror 235 235 236 236 INTEGER status 237 IF (status .NE.nf_noerr) THEN237 IF (status/=nf_noerr) THEN 238 238 PRINT *,NF_STRERROR(status) 239 239 CALL abort_gcm('grilles_gcm_netcdf','netcdf error',1) -
LMDZ6/trunk/libf/dyn3dmem/dynetat0_loc.F90
r4984 r5075 9 9 USE infotrac, ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName 10 10 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, & 12 12 NF90_CLOSE, NF90_GET_VAR, NF90_INQUIRE_VARIABLE, NF90_NoErr 13 13 USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3, getKey -
LMDZ6/trunk/libf/dyn3dmem/dynredem_loc.F90
r4389 r5075 11 11 USE strings_mod, ONLY: maxlen 12 12 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, & 14 14 NF90_CLOSE, NF90_PUT_ATT, NF90_UNLIMITED, NF90_CLOBBER, & 15 15 NF90_64BIT_OFFSET … … 178 178 USE infotrac, ONLY: nqtot, tracers, type_trac 179 179 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, & 181 181 NF90_CLOSE, NF90_WRITE, NF90_PUT_VAR, NF90_NoErr 182 182 USE dynredem_mod, ONLY: dynredem_write_u, dynredem_write_v, dynredem_read_u, & -
LMDZ6/trunk/libf/dyn3dmem/dynredem_mod.F90
r5069 r5075 4 4 USE parallel_lmdz 5 5 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 7 8 PRIVATE 8 9 PUBLIC :: dynredem_write_u, dynredem_write_v, dynredem_read_u, err -
LMDZ6/trunk/libf/dyn3dmem/iniacademic_loc.F90
r4984 r5075 23 23 USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0 24 24 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 28 26 29 27 ! Author: Frederic Hourdin original: 15/01/93 … … 155 153 relief=0. 156 154 ierr = NF90_OPEN ('relief_in.nc', NF90_NOWRITE,nid_relief) 157 if (ierr .EQ.NF90_NOERR) THEN155 if (ierr==NF90_NOERR) THEN 158 156 ierr=NF90_INQ_VARID(nid_relief,'RELIEF',varid) 159 157 if (ierr==NF90_NOERR) THEN … … 257 255 tetastrat=ttp*zsig**(-kappa) 258 256 tetapv=tetastrat 259 IF ((ok_pv).AND.(zsig .LT.0.1)) THEN257 IF ((ok_pv).AND.(zsig<0.1)) THEN 260 258 tetapv=tetastrat*(zsig*10.)**(kappa*cpp*gam_pv/1000./g) 261 259 ENDIF -
LMDZ6/trunk/libf/dynphy_lonlat/phylmd/ce0l.F90
r4689 r5075 21 21 USE etat0phys, ONLY: etat0phys_netcdf 22 22 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, & 24 24 NF90_INQUIRE_DIMENSION, NF90_INQ_DIMID, NF90_INQ_VARID, NF90_GET_VAR 25 25 USE infotrac, ONLY: init_infotrac -
LMDZ6/trunk/libf/dynphy_lonlat/phylmd/limit_netcdf.F90
r5073 r5075 71 71 #ifndef CPP_1D 72 72 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, & 74 74 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, & 76 76 NF90_CLOBBER, NF90_ENDDEF, NF90_UNLIMITED, NF90_FLOAT, & 77 NF90_64BIT_OFFSET 77 NF90_64BIT_OFFSET, NF90_FORMAT 78 78 USE inter_barxy_m, ONLY: inter_barxy 79 79 USE netcdf95, ONLY: nf95_def_var, nf95_put_att, nf95_put_var 80 80 USE comconst_mod, ONLY: pi 81 81 USE phys_cal_mod, ONLY: calend 82 USE lmdz_netcdf, ONLY: NF90_FORMAT83 82 IMPLICIT NONE 84 83 !------------------------------------------------------------------------------- … … 322 321 ! 2) Dimensional variables have the same names as corresponding dimensions. 323 322 !----------------------------------------------------------------------------- 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, & 325 324 NF90_CLOSE, NF90_INQ_DIMID, NF90_INQUIRE_DIMENSION, NF90_GET_VAR, & 326 325 NF90_GET_ATT … … 741 740 ! Purpose: NetCDF errors handling. 742 741 !------------------------------------------------------------------------------- 743 USE netcdf, ONLY : NF90_NOERR, NF90_STRERROR742 USE lmdz_netcdf, ONLY : NF90_NOERR, NF90_STRERROR 744 743 IMPLICIT NONE 745 744 !------------------------------------------------------------------------------- -
LMDZ6/trunk/libf/misc/lmdz_netcdf.F90
r5073 r5075 4 4 ! 1) Turn netcdf into a "real" fortran module, without the INCLUDE call 5 5 ! 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) TODO6 ! The "real" netcdf module/headers should ONLY be called here. 7 7 ! --------------------------------------------- 8 ! TODO check all uses of `use netcdf` + netcdf.inc9 8 10 9 MODULE lmdz_netcdf -
LMDZ6/trunk/libf/misc/write_field.F90
r2342 r5075 1 !2 ! $Id$3 !4 1 module 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 6 6 7 7 integer, parameter :: MaxWriteField = 100 … … 73 73 subroutine WriteField_gen(name,Field,dimx,dimy,dimz) 74 74 implicit none 75 include 'netcdf.inc'76 75 character(len=*) :: name 77 76 integer :: dimx,dimy,dimz … … 102 101 count(4)=1 103 102 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) 105 104 status = NF_SYNC(FieldId(Index)) 106 105 … … 109 108 subroutine CreateNewField(name,dimx,dimy,dimz) 110 109 implicit none 111 include 'netcdf.inc'112 110 character(len=*) :: name 113 111 integer :: dimx,dimy,dimz … … 126 124 status = NF_DEF_DIM(FieldId(NbField),'Z',dimz,TabDim(3)) 127 125 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)) 129 127 status = NF_ENDDEF(FieldId(NbField)) 130 128 131 129 end subroutine CreateNewField 132 133 134 130 135 131 subroutine write_field1D(name,Field) … … 285 281 //trim(int2str(pos+offset)) & 286 282 //'," ---> ",g22.16," | ")' 287 ! d épent de l'implémention, sur compaq, c'est necessaire283 ! d�pent de l'impl�mention, sur compaq, c'est necessaire 288 284 ! Pos=Pos+ColumnSize 289 285 endif -
LMDZ6/trunk/libf/misc/wxios.F90
r4817 r5075 70 70 reformaop = "average" 71 71 72 IF (op .EQ."inst(X)") THEN72 IF (op=="inst(X)") THEN 73 73 reformaop = "instant" 74 74 END IF 75 75 76 IF (op .EQ."once") THEN76 IF (op=="once") THEN 77 77 reformaop = "once" 78 78 END IF 79 79 80 IF (op .EQ."t_max(X)") THEN80 IF (op=="t_max(X)") THEN 81 81 reformaop = "maximum" 82 82 END IF 83 83 84 IF (op .EQ."t_min(X)") THEN84 IF (op=="t_min(X)") THEN 85 85 reformaop = "minimum" 86 86 END IF … … 604 604 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 605 605 SUBROUTINE wxios_add_field(fieldname, fieldgroup, fieldlongname, fieldunit) 606 USE netcdf, only: nf90_fill_real606 USE lmdz_netcdf, only: nf90_fill_real 607 607 608 608 IMPLICIT NONE … … 621 621 def = nf90_fill_real 622 622 623 IF (fieldunit .EQ." ") THEN623 IF (fieldunit == " ") THEN 624 624 newunit = "-" 625 625 ELSE … … 666 666 667 667 ! Ajout Abd pour NMC: 668 IF (fid .LE.6) THEN668 IF (fid<=6) THEN 669 669 axis_id="presnivs" 670 670 ELSE … … 682 682 683 683 !On selectionne le bon groupe de champs: 684 IF (fdim .EQ.2) THEN684 IF (fdim==2) THEN 685 685 CALL xios_get_handle("fields_2D", fieldgroup) 686 686 ELSE … … 726 726 CALL xios_set_attr(field, level=field_level, enabled=.TRUE.) 727 727 728 IF (fdim .EQ.2) THEN728 IF (fdim==2) THEN 729 729 !Si c'est un champ 2D: 730 730 IF (prt_level >= 10) THEN -
LMDZ6/trunk/libf/phylmd/Dust/condsurfc.F
r5073 r5075 4 4 . lmt_omnat) 5 5 USE dimphy 6 USE lmdz_netcdf, ONLY: nf_close,nf_noerr,nf_inq_varid,nf_open,nf_nowrite,nf90_get_var 6 7 IMPLICIT none 7 8 ! … … 10 11 ! 11 12 INCLUDE "dimensions.h" 12 INCLUDE "netcdf.inc" 13 13 14 14 REAL lmt_bcff(klon), lmt_bcbb(klon),lmt_bc_penner(klon) 15 15 REAL lmt_omff(klon), lmt_ombb(klon) -
LMDZ6/trunk/libf/phylmd/Dust/condsurfc_new.F
r4593 r5075 6 6 USE mod_phys_lmdz_para 7 7 USE dimphy 8 USE lmdz_netcdf, ONLY:nf90_get_var,nf_close,nf_noerr,nf_inq_varid,nf_open,nf_nowrite 8 9 IMPLICIT none 9 10 c … … 12 13 c 13 14 INCLUDE "dimensions.h" 14 INCLUDE "netcdf.inc" 15 15 16 16 REAL lmt_bcff(klon), lmt_bcnff(klon), lmt_bcba(klon) 17 17 REAL lmt_omff(klon), lmt_omnff(klon), lmt_ombb(klon) … … 36 36 c 37 37 ! IF (jour.LT.0 .OR. jour.GT.(366-1)) THEN 38 IF (jour .LT.0 .OR. jour.GT.366) THEN38 IF (jour<0 .OR. jour>366) THEN 39 39 PRINT*,'Le jour demande n est pas correcte:', jour 40 40 print *,'JE: FORCED TO CONTINUE (emissions have … … 58 58 ! 59 59 ierr = NF_OPEN ("carbon_emissions.nc", NF_NOWRITE, nid1) 60 if (ierr .ne.NF_NOERR) then60 if (ierr/=NF_NOERR) then 61 61 write(6,*)' Pb d''ouverture du fichier limitbc.nc' 62 62 write(6,*)' ierr = ', ierr … … 67 67 ! 68 68 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 72 71 PRINT*, 'Pb de lecture pour les sources BC' 73 72 CALL exit(1) … … 79 78 ! 80 79 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 84 82 PRINT*, 'Pb de lecture pour les sources BC' 85 83 CALL exit(1) … … 89 87 ! 90 88 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 94 91 PRINT*, 'Pb de lecture pour les sources BC low' 95 92 CALL exit(1) … … 99 96 ! 100 97 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 104 100 PRINT*, 'Pb de lecture pour les sources BC high' 105 101 CALL exit(1) … … 109 105 ! 110 106 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 114 109 PRINT*, 'Pb de lecture pour les sources BC' 115 110 CALL exit(1) … … 125 120 ! 126 121 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 130 124 PRINT*, 'Pb de lecture pour les sources OM' 131 125 CALL exit(1) … … 135 129 ! 136 130 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 140 133 PRINT*, 'Pb de lecture pour les sources OM' 141 134 CALL exit(1) … … 145 138 ! 146 139 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 150 142 PRINT*, 'Pb de lecture pour les sources OM low' 151 143 CALL exit(1) … … 155 147 ! 156 148 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 160 151 PRINT*, 'Pb de lecture pour les sources OM high' 161 152 CALL exit(1) … … 165 156 ! 166 157 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 170 160 PRINT*, 'Pb de lecture pour les sources OM ship' 171 161 CALL exit(1) … … 175 165 ! 176 166 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 180 169 PRINT*, 'Pb de lecture pour les sources Terpene' 181 170 CALL exit(1) -
LMDZ6/trunk/libf/phylmd/Dust/condsurfs.F
r5073 r5075 4 4 . lmt_dmsbio, lmt_h2sbio, lmt_dms, lmt_dmsconc) 5 5 USE dimphy 6 USE lmdz_netcdf, ONLY:nf_close,nf_noerr,nf_inq_varid,nf_open,nf_nowrite,nf90_get_var 6 7 IMPLICIT none 7 8 c … … 10 11 c 11 12 INCLUDE "dimensions.h" 12 INCLUDE "netcdf.inc"13 13 c 14 14 REAL lmt_so2h(klon), lmt_so2b(klon), lmt_so2bb(klon) -
LMDZ6/trunk/libf/phylmd/Dust/condsurfs_new.F
r4593 r5075 9 9 USE mod_phys_lmdz_para 10 10 USE dimphy 11 USE lmdz_netcdf, ONLY: nf90_get_var,nf_inq_varid,nf_close,nf_noerr,nf_open,nf_nowrite 11 12 IMPLICIT none 12 13 c … … 15 16 c 16 17 INCLUDE "dimensions.h" 17 INCLUDE "netcdf.inc"18 18 c 19 19 REAL lmt_so2b(klon), lmt_so2h(klon), lmt_so2nff(klon) … … 40 40 INTEGER debut(2),epais(2) 41 41 c 42 IF (jour .LT.0 .OR. jour.GT.(366-1)) THEN42 IF (jour<0 .OR. jour>(366-1)) THEN 43 43 PRINT*,'Le jour demande n est pas correcte:', jour 44 44 print *,'JE: FORCED TO CONTINUE (emissions have … … 62 62 ! 63 63 ierr = NF_OPEN ("sulphur_emissions_antro.nc", NF_NOWRITE, nid) 64 if (ierr .ne.NF_NOERR) then64 if (ierr/=NF_NOERR) then 65 65 write(6,*)' Pb d''ouverture du fichier sulphur_emissions_antro' 66 66 write(6,*)' ierr = ', ierr … … 72 72 ! 73 73 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) THEN74 ierr = nf90_get_var(nid, nvarid, lmt_so2b_glo, debut, epais) 75 IF (ierr /= NF_NOERR) THEN 76 76 PRINT*, 'Pb de lecture pour les sources so2 low' 77 77 print *,'JE klon, jour, debut ,epais ',klon_glo,jour,debut,epais … … 84 84 ! 85 85 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) THEN86 ierr = nf90_get_var(nid, nvarid, lmt_so2h_glo, debut, epais) 87 IF (ierr /= NF_NOERR) THEN 88 88 PRINT*, 'Pb de lecture pour les sources so2 high' 89 89 CALL exit(1) … … 93 93 ! 94 94 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 98 97 PRINT*, 'Pb de lecture pour les sources so2 BB high' 99 98 CALL exit(1) … … 103 102 ! 104 103 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 108 106 PRINT*, 'Pb de lecture pour les sources so2 BB low' 109 107 CALL exit(1) … … 113 111 ! 114 112 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) THEN113 ierr = nf90_get_var(nid, nvarid, lmt_so2ba_glo, debut, epais) 114 IF (ierr /= NF_NOERR) THEN 117 115 PRINT*, 'Pb de lecture pour les sources so2 ship' 118 116 CALL exit(1) … … 122 120 ! 123 121 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 127 124 PRINT*, 'Pb de lecture pour les sources so2 non FF' 128 125 CALL exit(1) … … 135 132 !======================================================================= 136 133 ierr = NF_OPEN ("sulphur_emissions_nat.nc", NF_NOWRITE, nid) 137 if (ierr .ne.NF_NOERR) then134 if (ierr/=NF_NOERR) then 138 135 write(6,*)' Pb d''ouverture du fichier sulphur_emissions_nat' 139 136 write(6,*)' ierr = ', ierr … … 144 141 c 145 142 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) THEN143 ierr = nf90_get_var(nid, nvarid, lmt_dmsbio_glo, debut, epais) 144 IF (ierr /= NF_NOERR) THEN 148 145 PRINT*, 'Pb de lecture pour les sources dms bio' 149 146 CALL exit(1) … … 153 150 c 154 151 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) THEN152 ierr = nf90_get_var(nid, nvarid, lmt_h2sbio_glo, debut, epais) 153 IF (ierr /= NF_NOERR) THEN 157 154 PRINT*, 'Pb de lecture pour les sources h2s bio' 158 155 CALL exit(1) … … 161 158 c Ocean surface concentration of dms (emissions are computed later) 162 159 c 163 IF (flag_dms .EQ.4) THEN160 IF (flag_dms==4) THEN 164 161 c 165 162 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) THEN163 ierr = nf90_get_var(nid, nvarid, lmt_dmsconc_glo, debut, epais) 164 IF (ierr /= NF_NOERR) THEN 168 165 PRINT*, 'Pb de lecture pour les sources dms conc 2' 169 166 CALL exit(1) … … 190 187 print *,' Jour = ',jour 191 188 ierr = NF_OPEN ("sulphur_emissions_volc.nc", NF_NOWRITE, nid) 192 if (ierr .ne.NF_NOERR) then189 if (ierr/=NF_NOERR) then 193 190 write(6,*)' Pb d''ouverture du fichier sulphur_emissions_volc' 194 191 write(6,*)' ierr = ', ierr … … 200 197 ! ierr = NF_INQ_VARID (nid, "VOLC", nvarid) 201 198 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 205 201 PRINT*, 'Pb de lecture pour les sources so2 volcan (cont)' 206 202 CALL exit(1) … … 214 210 ! ierr = NF_INQ_VARID (nid, "ALTI", nvarid) 215 211 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 219 214 PRINT*, 'Pb de lecture pour les altitudes volcan (cont)' 220 215 CALL exit(1) … … 224 219 c 225 220 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 229 223 PRINT*, 'Pb de lecture pour les sources so2 volcan (expl)' 230 224 CALL exit(1) … … 237 231 c 238 232 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 242 235 PRINT*, 'Pb de lecture pour les altitudes volcan' 243 236 CALL exit(1) -
LMDZ6/trunk/libf/phylmd/Dust/phys_output_write_spl_mod.F90
r5024 r5075 390 390 USE ioipsl, ONLY: histend, histsync 391 391 USE iophy, ONLY: set_itau_iophy, histwrite_phy 392 USE netcdf, ONLY: nf90_fill_real392 USE lmdz_netcdf, ONLY: nf90_fill_real 393 393 ! ug Pour les sorties XIOS 394 394 USE lmdz_xios, ONLY: xios_update_calendar, using_xios -
LMDZ6/trunk/libf/phylmd/Dust/phytracr_spl_mod.F90
r4618 r5075 1441 1441 call abort_gcm('phytracr_mod', 'pb in ok_chimdust 1 SCDU',1) 1442 1442 endif 1443 if ( (id_codu .le. 0) .or. ( id_fine.le.0) ) then1443 if ( (id_codu <= 0) .or. ( id_fine<=0) ) then 1444 1444 call abort_gcm('phytracr_mod', 'pb in ok_chimdust 1',1) 1445 1445 endif … … 2437 2437 ENDDO 2438 2438 ENDDO 2439 IF (iflag_conv .EQ.2) THEN2439 IF (iflag_conv==2) THEN 2440 2440 ! Tiedke 2441 2441 CALL cltrac_spl(pdtphys,coefh,yu1,yv1,t_seri,tmp_var, & 2442 2442 aux_var2,paprs,pplay,aux_var3) 2443 2443 2444 ELSE IF (iflag_conv .GE.3) THEN2444 ELSE IF (iflag_conv>=3) THEN 2445 2445 !KE 2446 2446 CALL cltrac(pdtphys, coefh,t_seri,tmp_var,aux_var2,paprs,pplay, & … … 2494 2494 2495 2495 2496 IF (iflag_conv .GE.3) THEN2496 IF (iflag_conv>=3) THEN 2497 2497 2498 2498 IF (logitime) THEN … … 2786 2786 2787 2787 2788 IF (iflag_conv .EQ.2) THEN2788 IF (iflag_conv==2) THEN 2789 2789 2790 2790 IF (logitime) THEN … … 2839 2839 print *,'iflag_conv bef incloud',iflag_conv 2840 2840 2841 IF (iflag_conv .EQ.2) THEN2841 IF (iflag_conv==2) THEN 2842 2842 ! Tiedke 2843 2843 CALL incloud_scav(.false.,qmin,qmax,masse,henry,kk,prfl, & … … 2877 2877 ! . his_dhbclsc,his_dhbccon,tr_seri) 2878 2878 2879 IF (iflag_conv .EQ.2) THEN2879 IF (iflag_conv==2) THEN 2880 2880 ! Tiedke 2881 2881 … … 2991 2991 ! . dtrconv,tr_seri) 2992 2992 ! ------------------------------------------------------------- 2993 IF (iflag_conv .EQ.2) THEN2993 IF (iflag_conv==2) THEN 2994 2994 ! Tiedke 2995 2995 CALL trconvect(pplay,t_seri,pdtphys,pmfu,pmfd,pen_u,pde_u, & … … 3000 3000 ENDDO 3001 3001 3002 ELSE IF (iflag_conv .GE.3) THEN3002 ELSE IF (iflag_conv>=3) THEN 3003 3003 ! KE 3004 3004 print *,'JE: KE in phytracr_spl' … … 3164 3164 3165 3165 3166 IF (iflag_conv .GE.3) THEN3166 IF (iflag_conv>=3) THEN 3167 3167 IF (logitime) THEN 3168 3168 CALL SYSTEM_CLOCK(COUNT=clock_start) … … 3195 3195 ql_incl = ql_incloud_ref 3196 3196 ! choix du lessivage 3197 IF (iflag_lscav .EQ. 3 .OR. iflag_lscav .EQ.4) THEN3197 IF (iflag_lscav == 3 .OR. iflag_lscav == 4) THEN 3198 3198 !IF (.false.) THEN ! test #DFB (Binta) sans lsc_scav_spl 3199 3199 print *,'JE iflag_lscav',iflag_lscav … … 3362 3362 CALL satellite_out_spla(jD_cur,jH_cur,pdtphys,rlat,rlon, & 3363 3363 masque_aqua_cur, masque_terra_cur ) 3364 IF (jH_cur-pdtphys/86400. .LT.0.) THEN3364 IF (jH_cur-pdtphys/86400. < 0.) THEN 3365 3365 !new utc day: put in 0 everything 3366 3366 !JE20150518<< … … 3470 3470 ENDDO 3471 3471 3472 IF (jH_cur+pdtphys/86400. .GE. 1.) THEN3472 IF (jH_cur+pdtphys/86400. >= 1.) THEN 3473 3473 ! print *,'last step of the day' 3474 3474 DO i=1,klon 3475 IF (masque_aqua(i) .GT.0) THEN3475 IF (masque_aqua(i)> 0) THEN 3476 3476 aod550_aqua(i)=aod550_aqua(i)/masque_aqua(i) 3477 3477 aod670_aqua(i)=aod670_aqua(i)/masque_aqua(i) … … 3506 3506 aod865_dustsco_aqua(i)= -999. 3507 3507 ENDIF 3508 IF (masque_terra(i) .GT.0) THEN3508 IF (masque_terra(i)> 0) THEN 3509 3509 aod550_terra(i)=aod550_terra(i)/masque_terra(i) 3510 3510 aod670_terra(i)=aod670_terra(i)/masque_terra(i) … … 3635 3635 fluxss(:)=0.0 3636 3636 DO i=1, klon 3637 IF (iregion_ind(i) .GT.0) THEN ! LAND3637 IF (iregion_ind(i)>0) THEN ! LAND 3638 3638 ! SULFUR EMISSIONS 3639 3639 fluxh2sff(i)= (lmt_so2ff_l(i)+lmt_so2ff_h(i))*frach2sofso2* & … … 3656 3656 fluxff(i)=fluxbcff(i)+fluxomff(i) 3657 3657 ENDIF 3658 IF (iregion_bb(i) .GT.0) THEN ! LAND3658 IF (iregion_bb(i)>0) THEN ! LAND 3659 3659 ! SULFUR EMISSIONS 3660 3660 fluxso2bb(i) =scale_param_bb(iregion_bb(i)) * fracso2emis * & … … 4515 4515 ENDIF 4516 4516 4517 IF (test_sca .EQ.0 ) THEN4517 IF (test_sca == 0 ) THEN 4518 4518 ! READ file!! 4519 4519 call read_scalenc(filescaleparams,paramname_ind, & … … 4556 4556 4557 4557 jH_sca=jH_sca+pdtphys/(24.*3600.) 4558 IF (jH_sca .GT.(sca_resol)/24.) THEN4558 IF (jH_sca>(sca_resol)/24.) THEN 4559 4559 test_sca=0 4560 4560 jH_sca=jH_ini … … 4568 4568 USE mod_grid_phy_lmdz 4569 4569 USE mod_phys_lmdz_para 4570 USE lmdz_netcdf, ONLY:nf_open,nf_close,nf_inq_varid,nf_nowrite,nf_noerr,nf90_get_var 4570 4571 IMPLICIT NONE 4571 4572 include "netcdf.inc"4573 4572 4574 4573 CHARACTER*800 filescaleparams … … 4589 4588 !nci=NCOPN(trim(adjustl(filescaleparams)),NCNOWRIT,rcode) 4590 4589 ierr = NF_OPEN (trim(adjustl(filescaleparams)),NF_NOWRITE, nid) 4591 if (ierr .EQ.NF_NOERR) THEN4590 if (ierr == NF_NOERR) THEN 4592 4591 debutread=step_sca 4593 4592 countread=1 … … 4598 4597 print *,varname 4599 4598 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 4603 4601 PRINT*, 'Pb de lecture pour modvalues' 4604 4602 print *,'JE scale_var, step_sca',trim(adjustl(varname)),step_sca -
LMDZ6/trunk/libf/phylmd/Dust/read_dust.F
r5073 r5075 3 3 USE mod_grid_phy_lmdz 4 4 USE mod_phys_lmdz_para 5 USE lmdz_netcdf, ONLY:nf90_get_var 5 6 IMPLICIT NONE 6 7 c 7 8 INCLUDE "dimensions.h" 8 9 INCLUDE "paramet.h" 9 INCLUDE "netcdf.inc"10 10 c 11 11 INTEGER step, nbjour … … 45 45 c 46 46 start(3)=step 47 c 48 ! status=NF_GET_VARA_DOUBLE(ncid1,varid1,start,count,dust_nc) 47 49 48 status=nf90_get_var(ncid1,varid1,dust_nc_glo,start,count) 50 c 49 51 50 ! call correctbid(iim,jjp1,dust_nc) 52 51 call correctbid(nbp_lon,nbp_lat,dust_nc_glo) -
LMDZ6/trunk/libf/phylmd/Dust/read_surface.F90
r5073 r5075 10 10 USE mod_phys_lmdz_para 11 11 USE iophy 12 ! USE netcdf 12 USE lmdz_netcdf, ONLY:nf_inq_varid,nf_noerr,nf90_get_var 13 13 IMPLICIT NONE 14 14 15 INCLUDE "netcdf.inc"16 15 INCLUDE "dimensions.h" 17 16 INCLUDE "paramet.h" -
LMDZ6/trunk/libf/phylmd/Dust/read_vent.F
r5073 r5075 3 3 USE mod_grid_phy_lmdz 4 4 USE mod_phys_lmdz_para 5 USE lmdz_netcdf, ONLY: nf90_get_var 5 6 ! USE write_field_phy 6 7 IMPLICIT NONE … … 8 9 c INCLUDE "dimphy.h" 9 10 INCLUDE "paramet.h" 10 INCLUDE "netcdf.inc"11 11 c 12 12 INTEGER step, nbjour -
LMDZ6/trunk/libf/phylmd/StratAer/interp_sulf_input.F90
r4625 r5075 6 6 USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, & 7 7 nf95_inq_varid, nf95_inquire_dimension, nf95_open 8 USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite8 USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite 9 9 10 10 USE mod_grid_phy_lmdz -
LMDZ6/trunk/libf/phylmd/StratAer/stratH2O_methox.F90
r4755 r5075 8 8 USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, & 9 9 nf95_inq_varid, nf95_inquire_dimension, nf95_open 10 USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite10 USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite 11 11 12 12 USE mod_grid_phy_lmdz … … 79 79 ! 80 80 81 IF (debutphy .OR. mth_cur .NE.mth_pre) THEN81 IF (debutphy .OR. mth_cur /= mth_pre) THEN 82 82 83 83 !--preparation of global fields -
LMDZ6/trunk/libf/phylmd/condsurf.F90
r5073 r5075 7 7 USE indice_sol_mod 8 8 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 10 10 IMPLICIT NONE 11 11 -
LMDZ6/trunk/libf/phylmd/create_etat0_unstruct_mod.F90
r4856 r5075 23 23 SUBROUTINE init_create_etat0_unstruct 24 24 USE lmdz_xios 25 USE netcdf25 USE lmdz_netcdf, ONLY: NF90_NOWRITE,nf90_close,nf90_noerr,nf90_open 26 26 USE mod_phys_lmdz_para 27 27 IMPLICIT NONE … … 126 126 CALL xios_recv_field("qs",qsol_mpi) 127 127 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) 129 129 ENDIF 130 130 CALL scatter_omp(tsol_mpi,tsol) 131 131 CALL scatter_omp(qsol_mpi,qsol) 132 132 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) 134 134 135 135 radsol(:) = 0.0 … … 143 143 144 144 pctsrf(:,:) = 0 145 IF (landice_opt .LT.2) THEN145 IF (landice_opt < 2) THEN 146 146 pctsrf(:,is_lic)=lic 147 147 WHERE(pctsrf(:,is_lic)<EPSFRA) pctsrf(:,is_lic)=0. … … 180 180 !--- The ocean and sea-ice fractions are not changed. 181 181 !--- This option is only available if landice_opt<2. 182 IF (landice_opt .LT.2) THEN182 IF (landice_opt < 2) THEN 183 183 no_ter_antartique=.FALSE. 184 184 CALL getin_p('no_ter_antartique',no_ter_antartique) -
LMDZ6/trunk/libf/phylmd/dyn1d/1DUTILS.h
r4650 r5075 673 673 USE logic_mod, ONLY: fxyhypb, ysinus 674 674 USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn 675 USE lmdz_netcdf, ONLY:nf_open,nf_write,nf_noerr 675 676 676 677 IMPLICIT NONE … … 682 683 include "dimensions.h" 683 684 !!#include "control.h" 684 include "netcdf.inc"685 685 686 686 ! Arguments: … … 820 820 USE logic_mod, ONLY: fxyhypb, ysinus 821 821 USE temps_mod, ONLY: annee_ref,day_end,day_ref,itau_dyn,itaufin 822 USE lmdz_netcdf, ONLY:nf_open,nf_write,nf_noerr 822 823 823 824 IMPLICIT NONE … … 829 830 include "dimensions.h" 830 831 !!#include "control.h" 831 include "netcdf.inc"832 832 833 833 ! Arguments: -
LMDZ6/trunk/libf/phylmd/dyn1d/1D_decl_cases.h
r4593 r5075 1 INCLUDE "netcdf.inc"2 1 3 2 ! Declarations specifiques au cas Toga -
LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_amma_read.F90
r5073 r5075 1 1 MODULE 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 3 4 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 4 5 !Declarations specifiques au cas AMMA … … 6 7 ! Option du cas AMMA ou on impose la discretisation verticale (Ap,Bp) 7 8 integer nlev_amma, nt_amma 8 9 9 10 10 integer year_ini_amma, day_ini_amma, mth_ini_amma … … 58 58 SUBROUTINE read_1D_cases 59 59 implicit none 60 61 INCLUDE "netcdf.inc"62 60 63 61 INTEGER nid,rid,ierr … … 172 170 173 171 174 END MODULE mod_1D_amma_read175 172 !===================================================================== 176 173 subroutine read_amma(nid,nlevel,ntime & … … 180 177 !program reading forcings of the AMMA case study 181 178 implicit none 182 INCLUDE "netcdf.inc"183 179 184 180 integer ntime,nlevel … … 459 455 END 460 456 457 END MODULE mod_1D_amma_read -
LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_cases_read.F90
r5073 r5075 1 !2 ! $Id$3 !4 1 MODULE 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 5 4 6 5 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 7 6 !Declarations specifiques au cas standard 8 7 character*80 :: fich_cas 9 ! Discr?tisation 8 ! Discr?tisation 10 9 integer nlev_cas, nt_cas 11 10 … … 57 56 real, allocatable:: q_prof_cas(:) 58 57 real, allocatable:: u_prof_cas(:) 59 real, allocatable:: v_prof_cas(:) 58 real, allocatable:: v_prof_cas(:) 60 59 61 60 real, allocatable:: vitw_prof_cas(:) … … 82 81 83 82 real lat_prof_cas,sens_prof_cas,ts_prof_cas,ustar_prof_cas 84 83 85 84 86 85 … … 88 87 89 88 SUBROUTINE read_1D_cas 90 implicit none91 92 INCLUDE "netcdf.inc"93 89 94 90 INTEGER nid,rid,ierr … … 137 133 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 138 134 !profils moyens: 139 allocate(plev_cas(nlev_cas,nt_cas)) 135 allocate(plev_cas(nlev_cas,nt_cas)) 140 136 allocate(z_cas(nlev_cas,nt_cas)) 141 137 allocate(t_cas(nlev_cas,nt_cas),q_cas(nlev_cas,nt_cas),rh_cas(nlev_cas,nt_cas)) … … 204 200 !profils environnementaux: 205 201 deallocate(plev_cas) 206 202 207 203 deallocate(z_cas) 208 204 deallocate(t_cas,q_cas,rh_cas) … … 210 206 deallocate(u_cas) 211 207 deallocate(v_cas) 212 208 213 209 !forcing 214 210 deallocate(ht_cas,vt_cas,dt_cas,dtrad_cas) … … 257 253 END SUBROUTINE deallocate_1D_cases 258 254 259 260 END MODULE mod_1D_cases_read 261 !===================================================================== 255 !===================================================================== 262 256 subroutine read_cas(nid,nlevel,ntime & 263 257 & ,zz,pp,temp,qv,rh,theta,rv,u,v,ug,vg,w, & … … 266 260 267 261 !program reading forcing of the case study 268 implicit none269 INCLUDE "netcdf.inc"270 262 271 263 integer ntime,nlevel … … 296 288 integer var3didin(nbvar3d) 297 289 298 ierr=NF_INQ_VARID(nid,"zz",var3didin(1)) 290 ierr=NF_INQ_VARID(nid,"zz",var3didin(1)) 299 291 if(ierr/=NF_NOERR) then 300 292 write(*,*) NF_STRERROR(ierr) 301 293 stop 'lev' 302 294 endif 303 304 ierr=NF_INQ_VARID(nid,"pp",var3didin(2)) 295 296 ierr=NF_INQ_VARID(nid,"pp",var3didin(2)) 305 297 if(ierr/=NF_NOERR) then 306 298 write(*,*) NF_STRERROR(ierr) … … 429 421 stop 'advq' 430 422 endif 431 423 432 424 ierr=NF_INQ_VARID(nid,"hq",var3didin(23)) 433 425 if(ierr/=NF_NOERR) then … … 465 457 stop 'advr' 466 458 endif 467 459 468 460 ierr=NF_INQ_VARID(nid,"hr",var3didin(29)) 469 461 if(ierr/=NF_NOERR) then … … 531 523 stop 'q2' 532 524 endif 533 525 534 526 ierr = nf90_get_var(nid,var3didin(1),zz) 535 527 if(ierr/=NF_NOERR) then … … 560 552 endif 561 553 ! write(*,*)'lecture qv ok',qv 562 554 563 555 ierr = nf90_get_var(nid,var3didin(5),rh) 564 556 if(ierr/=NF_NOERR) then … … 807 799 808 800 809 return 801 return 810 802 end subroutine read_cas 811 803 !====================================================================== … … 825 817 & ,hq_prof_cas,vq_prof_cas,lat_prof_cas,sens_prof_cas & 826 818 & ,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas) 827 819 828 820 829 821 implicit none … … 834 826 ! day: current julian day (e.g. 717538.2) 835 827 ! 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 837 829 ! pdt_cas: total time interval (in sec) between 2 forcing data 838 830 !--------------------------------------------------------------------------------------- … … 926 918 it_cas1=INT(timeit/pdt_cas)+1 927 919 IF (it_cas1 == nt_cas) THEN 928 it_cas2=it_cas1 920 it_cas2=it_cas1 929 921 ELSE 930 922 it_cas2=it_cas1 + 1 … … 952 944 953 945 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)) 955 947 sens_prof_cas = sens_cas(it_cas2) & 956 948 & -frac*(sens_cas(it_cas2)-sens_cas(it_cas1)) … … 1017 1009 1018 1010 !********************************************************************************************** 1011 END MODULE mod_1D_cases_read -
LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_cases_read2.F90
r4706 r5075 3 3 ! 4 4 MODULE 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 6 7 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 7 8 !Declarations specifiques au cas standard … … 81 82 implicit none 82 83 83 INCLUDE "netcdf.inc"84 85 84 INTEGER nid,rid,ierr 86 85 INTEGER ii,jj … … 90 89 ierr = NF_OPEN(fich_cas,NF_NOWRITE,nid) 91 90 print*,'fich_cas,NF_NOWRITE,nid ',fich_cas,NF_NOWRITE,nid 92 if (ierr .NE.NF_NOERR) then91 if (ierr/=NF_NOERR) then 93 92 write(*,*) 'ERROR: GROS Pb opening forcings nc file ' 94 93 write(*,*) NF_STRERROR(ierr) … … 97 96 !....................................................................... 98 97 ierr=NF_INQ_DIMID(nid,'lat',rid) 99 IF (ierr .NE.NF_NOERR) THEN98 IF (ierr/=NF_NOERR) THEN 100 99 print*, 'Oh probleme lecture dimension lat' 101 100 ENDIF … … 104 103 !....................................................................... 105 104 ierr=NF_INQ_DIMID(nid,'lon',rid) 106 IF (ierr .NE.NF_NOERR) THEN105 IF (ierr/=NF_NOERR) THEN 107 106 print*, 'Oh probleme lecture dimension lon' 108 107 ENDIF … … 111 110 !....................................................................... 112 111 ierr=NF_INQ_DIMID(nid,'lev',rid) 113 IF (ierr .NE.NF_NOERR) THEN112 IF (ierr/=NF_NOERR) THEN 114 113 print*, 'Oh probleme lecture dimension zz' 115 114 ENDIF … … 120 119 print*,'nid,rid',nid,rid 121 120 nt_cas=0 122 IF (ierr .NE.NF_NOERR) THEN121 IF (ierr/=NF_NOERR) THEN 123 122 stop 'probleme lecture dimension sens' 124 123 ENDIF … … 192 191 implicit none 193 192 194 INCLUDE "netcdf.inc"195 196 193 INTEGER nid,rid,ierr 197 194 INTEGER ii,jj … … 201 198 ierr = NF_OPEN(fich_cas,NF_NOWRITE,nid) 202 199 print*,'fich_cas,NF_NOWRITE,nid ',fich_cas,NF_NOWRITE,nid 203 if (ierr .NE.NF_NOERR) then200 if (ierr/=NF_NOERR) then 204 201 write(*,*) 'ERROR: GROS Pb opening forcings nc file ' 205 202 write(*,*) NF_STRERROR(ierr) … … 208 205 !....................................................................... 209 206 ierr=NF_INQ_DIMID(nid,'lat',rid) 210 IF (ierr .NE.NF_NOERR) THEN207 IF (ierr/=NF_NOERR) THEN 211 208 print*, 'Oh probleme lecture dimension lat' 212 209 ENDIF … … 215 212 !....................................................................... 216 213 ierr=NF_INQ_DIMID(nid,'lon',rid) 217 IF (ierr .NE.NF_NOERR) THEN214 IF (ierr/=NF_NOERR) THEN 218 215 print*, 'Oh probleme lecture dimension lon' 219 216 ENDIF … … 222 219 !....................................................................... 223 220 ierr=NF_INQ_DIMID(nid,'nlev',rid) 224 IF (ierr .NE.NF_NOERR) THEN221 IF (ierr/=NF_NOERR) THEN 225 222 print*, 'Oh probleme lecture dimension nlev' 226 223 ENDIF … … 230 227 ierr=NF_INQ_DIMID(nid,'time',rid) 231 228 nt_cas=0 232 IF (ierr .NE.NF_NOERR) THEN229 IF (ierr/=NF_NOERR) THEN 233 230 stop 'Oh probleme lecture dimension time' 234 231 ENDIF … … 317 314 !********************************************************************************************** 318 315 SUBROUTINE old_read_SCM_cas 319 use netcdf, only: nf90_get_var320 316 implicit none 321 317 322 INCLUDE "netcdf.inc"323 318 INCLUDE "date_cas.h" 324 319 … … 331 326 ierr = NF_OPEN(fich_cas,NF_NOWRITE,nid) 332 327 print*,'fich_cas,NF_NOWRITE,nid ',fich_cas,NF_NOWRITE,nid 333 if (ierr .NE.NF_NOERR) then328 if (ierr/=NF_NOERR) then 334 329 write(*,*) 'ERROR: GROS Pb opening forcings nc file ' 335 330 write(*,*) NF_STRERROR(ierr) … … 338 333 !....................................................................... 339 334 ierr=NF_INQ_DIMID(nid,'lat',rid) 340 IF (ierr .NE.NF_NOERR) THEN335 IF (ierr/=NF_NOERR) THEN 341 336 print*, 'Oh probleme lecture dimension lat' 342 337 ENDIF … … 345 340 !....................................................................... 346 341 ierr=NF_INQ_DIMID(nid,'lon',rid) 347 IF (ierr .NE.NF_NOERR) THEN342 IF (ierr/=NF_NOERR) THEN 348 343 print*, 'Oh probleme lecture dimension lon' 349 344 ENDIF … … 352 347 !....................................................................... 353 348 ierr=NF_INQ_DIMID(nid,'lev',rid) 354 IF (ierr .NE.NF_NOERR) THEN349 IF (ierr/=NF_NOERR) THEN 355 350 print*, 'Oh probleme lecture dimension nlev' 356 351 ENDIF … … 364 359 ierr=NF_INQ_DIMID(nid,'time',rid) 365 360 nt_cas=0 366 IF (ierr .NE.NF_NOERR) THEN361 IF (ierr/=NF_NOERR) THEN 367 362 stop 'Oh probleme lecture dimension time' 368 363 ENDIF … … 533 528 534 529 535 END MODULE mod_1D_cases_read2536 530 !===================================================================== 537 531 subroutine read_cas2(nid,nlevel,ntime & … … 541 535 542 536 !program reading forcing of the case study 543 use netcdf, only: nf90_get_var544 537 implicit none 545 INCLUDE "netcdf.inc"546 538 547 539 integer ntime,nlevel … … 589 581 do i=1,nbvar3d 590 582 print *,'Dans read_cas2, on va lire ',var3didin(i),name_var(i) 591 if(i .LE.35) then583 if(i<=35) then 592 584 ierr = NF90_GET_VAR(nid,var3didin(i),resul, count = [1, 1, nlevel, ntime]) 593 585 print *,'Dans read_cas2, on a lu ',ierr,var3didin(i),name_var(i) … … 658 650 659 651 !program reading forcing of the case study 660 use netcdf, only: nf90_get_var661 652 implicit none 662 INCLUDE "netcdf.inc"663 653 664 654 integer ntime,nlevel … … 711 701 else 712 702 !----------------------------------------------------------------------- 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) 714 704 ierr = NF90_GET_VAR(nid,var3didin(i),apbp, count = [1, 1, nlevel + 1]) 715 705 print *,'read2_cas(apbp), on a lu ',i,name_var(i) … … 719 709 endif 720 710 !----------------------------------------------------------------------- 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) 722 712 ierr = NF90_GET_VAR(nid,var3didin(i),resul, count = [1, 1, nlevel, ntime]) 723 713 print *,'read2_cas(resul), on a lu ',i,name_var(i) … … 727 717 endif 728 718 !----------------------------------------------------------------------- 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) 730 720 ierr = NF90_GET_VAR(nid,var3didin(i),resul2, count = [1, 1, ntime]) 731 721 print *,'read2_cas(resul2), on a lu ',i,name_var(i) … … 829 819 830 820 !program reading forcing of the case study 831 use netcdf, only: nf90_get_var832 821 implicit none 833 INCLUDE "netcdf.inc"834 822 835 823 integer ntime,nlevel,k,t … … 888 876 else 889 877 !----------------------------------------------------------------------- 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) 891 879 ierr = NF90_GET_VAR(nid,var3didin(i),apbp) 892 880 print *,'read2_cas(apbp), on a lu ',i,name_var(i) … … 896 884 endif 897 885 !----------------------------------------------------------------------- 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) 899 887 ierr = NF90_GET_VAR(nid,var3didin(i),resul1) 900 888 print *,'read2_cas(resul1), on a lu ',i,name_var(i) … … 905 893 print*,'Lecture de la variable #i ',i,name_var(i),minval(resul1),maxval(resul1) 906 894 !----------------------------------------------------------------------- 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) 908 896 ierr = NF90_GET_VAR(nid,var3didin(i),resul) 909 897 print *,'read2_cas(resul), on a lu ',i,name_var(i) … … 914 902 print*,'Lecture de la variable #i ',i,name_var(i),minval(resul),maxval(resul) 915 903 !----------------------------------------------------------------------- 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) 917 905 ierr = NF90_GET_VAR(nid,var3didin(i),resul2) 918 906 print *,'read2_cas(resul2), on a lu ',i,name_var(i) … … 1148 1136 1149 1137 it_cas1=INT(timeit/pdt_cas)+1 1150 IF (it_cas1 .EQ.nt_cas) THEN1138 IF (it_cas1 == nt_cas) THEN 1151 1139 it_cas2=it_cas1 1152 1140 ELSE … … 1157 1145 !print *,'it_cas1,it_cas2,time_cas1,time_cas2=',it_cas1,it_cas2,time_cas1,time_cas2 1158 1146 1159 if (it_cas1 .gt.nt_cas) then1147 if (it_cas1 > nt_cas) then 1160 1148 write(*,*) 'PB-stop: day, day_ju_ini_cas,it_cas1, it_cas2, timeit: ' & 1161 1149 ,day,day_ju_ini_cas,it_cas1,it_cas2,timeit … … 1164 1152 1165 1153 ! time interpolation: 1166 IF (it_cas1 .EQ.it_cas2) THEN1154 IF (it_cas1 == it_cas2) THEN 1167 1155 frac=0. 1168 1156 ELSE … … 1363 1351 1364 1352 it_cas1=INT(timeit/pdt_cas)+1 1365 IF (it_cas1 .EQ.nt_cas) THEN1353 IF (it_cas1 == nt_cas) THEN 1366 1354 it_cas2=it_cas1 1367 1355 ELSE … … 1373 1361 !print *,'it_cas1,it_cas2,time_cas1,time_cas2=',it_cas1,it_cas2,time_cas1,time_cas2 1374 1362 1375 if (it_cas1 .gt. nt_cas) then1363 if (it_cas1 > nt_cas) then 1376 1364 write(*,*) 'PB-stop: day, day_ju_ini_cas,it_cas1, it_cas2, timeit: ' & 1377 1365 ,day,day_ju_ini_cas,it_cas1,it_cas2,timeit … … 1380 1368 1381 1369 ! time interpolation: 1382 IF (it_cas1 .EQ.it_cas2) THEN1370 IF (it_cas1 == it_cas2) THEN 1383 1371 frac=0. 1384 1372 ELSE … … 1475 1463 !********************************************************************************************** 1476 1464 1465 END MODULE mod_1D_cases_read2 -
LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_cases_read_std.F90
r4706 r5075 3 3 ! 4 4 MODULE 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 5 7 6 8 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 87 89 !********************************************************************************************** 88 90 SUBROUTINE read_SCM_cas 89 use netcdf, only: nf90_get_var90 91 implicit none 91 92 92 INCLUDE "netcdf.inc"93 93 INCLUDE "date_cas.h" 94 94 … … 101 101 ierr = NF_OPEN(fich_cas,NF_NOWRITE,nid) 102 102 print*,'fich_cas,NF_NOWRITE,nid ',fich_cas,NF_NOWRITE,nid 103 if (ierr .NE.NF_NOERR) then103 if (ierr/=NF_NOERR) then 104 104 write(*,*) 'ERROR: GROS Pb opening forcings nc file ' 105 105 write(*,*) NF_STRERROR(ierr) … … 108 108 !....................................................................... 109 109 ierr=NF_INQ_DIMID(nid,'lat',rid) 110 IF (ierr .NE.NF_NOERR) THEN110 IF (ierr/=NF_NOERR) THEN 111 111 print*, 'Oh probleme lecture dimension lat' 112 112 ENDIF … … 115 115 !....................................................................... 116 116 ierr=NF_INQ_DIMID(nid,'lon',rid) 117 IF (ierr .NE.NF_NOERR) THEN117 IF (ierr/=NF_NOERR) THEN 118 118 print*, 'Oh probleme lecture dimension lon' 119 119 ENDIF … … 122 122 !....................................................................... 123 123 ierr=NF_INQ_DIMID(nid,'lev',rid) 124 IF (ierr .NE.NF_NOERR) THEN124 IF (ierr/=NF_NOERR) THEN 125 125 print*, 'Oh probleme lecture dimension nlev' 126 126 ENDIF … … 134 134 ierr=NF_INQ_DIMID(nid,'time',rid) 135 135 nt_cas=0 136 IF (ierr .NE.NF_NOERR) THEN136 IF (ierr/=NF_NOERR) THEN 137 137 stop 'Oh probleme lecture dimension time' 138 138 ENDIF … … 329 329 330 330 !program reading forcing of the case study 331 use netcdf, only: nf90_get_var332 331 implicit none 333 INCLUDE "netcdf.inc"334 332 INCLUDE "compar1d.h" 335 333 … … 455 453 ! Reading variables 1D (N+1) vertical variables (nlevelp1,lat,lon) 456 454 !----------------------------------------------------------------------- 457 if(i .LE.4) then455 if(i<=4) then 458 456 ierr = NF90_GET_VAR(nid,var3didin(i),apbp) 459 457 print *,'read_SCM(apbp), on a lu ',i,name_var(i) … … 466 464 ! Reading 1D (N) vertical varialbes (nlevel,lat,lon) 467 465 !----------------------------------------------------------------------- 468 else if(i .gt.4.and.i.LE.12) then466 else if(i>4.and.i<=12) then 469 467 ierr = NF90_GET_VAR(nid,var3didin(i),resul1) 470 468 print *,'read_SCM(resul1), on a lu ',i,name_var(i) … … 479 477 ! TBD : seems to be the same as above. 480 478 !----------------------------------------------------------------------- 481 else if(i .gt.12.and.i.LE.61) then479 else if(i>12.and.i<=61) then 482 480 ierr = NF90_GET_VAR(nid,var3didin(i),resul) 483 481 print *,'read_SCM(resul), on a lu ',i,name_var(i) … … 491 489 ! Reading 1D time variables (time,lat,lon) 492 490 !----------------------------------------------------------------------- 493 else if (i .gt.62.and.i.LE.75) then491 else if (i>62.and.i<=75) then 494 492 ierr = NF90_GET_VAR(nid,var3didin(i),resul2) 495 493 print *,'read_SCM(resul2), on a lu ',i,name_var(i) … … 777 775 778 776 it_cas1=INT(timeit/pdt_cas)+1 779 IF (it_cas1 .EQ.nt_cas) THEN777 IF (it_cas1 == nt_cas) THEN 780 778 it_cas2=it_cas1 781 779 ELSE … … 787 785 ! print *,'it_cas1,it_cas2,time_cas1,time_cas2=',it_cas1,it_cas2,time_cas1,time_cas2 788 786 789 if (it_cas1 .gt. nt_cas) then787 if (it_cas1 > nt_cas) then 790 788 write(*,*) 'PB-stop: day, day_ju_ini_cas,it_cas1, it_cas2, timeit: ' & 791 789 ,day,day_ju_ini_cas,it_cas1,it_cas2,timeit … … 794 792 795 793 ! time interpolation: 796 IF (it_cas1 .EQ.it_cas2) THEN794 IF (it_cas1 == it_cas2) THEN 797 795 frac=0. 798 796 ELSE … … 989 987 do l = 1, llm 990 988 991 if (play(l) .ge.plev_prof_cas(nlev_cas)) then989 if (play(l)>=plev_prof_cas(nlev_cas)) then 992 990 993 991 mxcalc=l … … 996 994 k2=0 997 995 998 if (play(l) .le.plev_prof_cas(1)) then996 if (play(l)<=plev_prof_cas(1)) then 999 997 1000 998 do k = 1, nlev_cas-1 1001 if (play(l) .le.plev_prof_cas(k).and. play(l).gt.plev_prof_cas(k+1)) then999 if (play(l)<=plev_prof_cas(k).and. play(l)>plev_prof_cas(k+1)) then 1002 1000 k1=k 1003 1001 k2=k+1 … … 1005 1003 enddo 1006 1004 1007 if (k1 .eq.0 .or. k2.eq.0) then1005 if (k1==0 .or. k2==0) then 1008 1006 write(*,*) 'PB! k1, k2 = ',k1,k2 1009 1007 write(*,*) 'l,play(l) = ',l,play(l)/100 … … 1019 1017 t_mod_cas(l)= t_prof_cas(k2) - frac*(t_prof_cas(k2)-t_prof_cas(k1)) 1020 1018 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) 1022 1020 thv_mod_cas(l)= thv_prof_cas(k2) - frac*(thv_prof_cas(k2)-thv_prof_cas(k1)) 1023 1021 thl_mod_cas(l)= thl_prof_cas(k2) - frac*(thl_prof_cas(k2)-thl_prof_cas(k1)) … … 1068 1066 t_mod_cas(l)= frac1*t_prof_cas(k1) - frac2*t_prof_cas(k2) 1069 1067 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) 1071 1069 thv_mod_cas(l)= frac1*thv_prof_cas(k1) - frac2*thv_prof_cas(k2) 1072 1070 thl_mod_cas(l)= frac1*thl_prof_cas(k1) - frac2*thl_prof_cas(k2) … … 1165 1163 do l = 1, llm+1 1166 1164 1167 if (plev(l) .ge.plev_prof_cas(nlev_cas)) then1165 if (plev(l)>=plev_prof_cas(nlev_cas)) then 1168 1166 1169 1167 mxcalc=l … … 1171 1169 k2=0 1172 1170 1173 if (plev(l) .le.plev_prof_cas(1)) then1171 if (plev(l)<=plev_prof_cas(1)) then 1174 1172 1175 1173 do k = 1, nlev_cas-1 1176 if (plev(l) .le.plev_prof_cas(k).and. plev(l).gt.plev_prof_cas(k+1)) then1174 if (plev(l)<=plev_prof_cas(k).and. plev(l)>plev_prof_cas(k+1)) then 1177 1175 k1=k 1178 1176 k2=k+1 … … 1180 1178 enddo 1181 1179 1182 if (k1 .eq.0 .or. k2.eq.0) then1180 if (k1==0 .or. k2==0) then 1183 1181 write(*,*) 'PB! k1, k2 = ',k1,k2 1184 1182 write(*,*) 'l,plev(l) = ',l,plev(l)/100 -
LMDZ6/trunk/libf/phylmd/dyn1d/old_1DUTILS_read_interp.h
r4593 r5075 146 146 !program reading forcings of the TWP-ICE experiment 147 147 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 149 151 150 152 implicit none 151 152 INCLUDE "netcdf.inc"153 153 154 154 integer ntime,nlevel … … 492 492 subroutine catchaxis(nid,ttm,llm,time,lev,ierr) 493 493 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 495 496 496 497 implicit none 497 INCLUDE "netcdf.inc"498 498 integer nid,ttm,llm 499 499 real*8 time(ttm) … … 2170 2170 2171 2171 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 2173 2174 implicit none 2174 2175 INCLUDE "netcdf.inc"2176 2175 2177 2176 integer ntime,nlevel … … 2381 2380 !program reading initial profils and forcings of the Dice case study 2382 2381 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 2384 2384 2385 2385 implicit none 2386 2386 2387 INCLUDE "netcdf.inc"2388 2387 INCLUDE "YOMCST.h" 2389 2388 … … 2715 2714 !program reading initial profils and forcings of the Gabls4 case study 2716 2715 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 2718 2718 2719 2719 implicit none 2720 2721 INCLUDE "netcdf.inc"2722 2720 2723 2721 integer ntime,nlevel,nsol -
LMDZ6/trunk/libf/phylmd/dyn1d/old_1D_decl_cases.h
r4593 r5075 1 INCLUDE "netcdf.inc"2 1 3 2 ! Declarations specifiques au cas Toga -
LMDZ6/trunk/libf/phylmd/dyn1d/old_lmdz1d.F90
r4744 r5075 44 44 USE temps_mod, ONLY: annee_ref, calend, day_end, day_ini, day_ref, & 45 45 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 47 49 48 50 implicit none … … 366 368 if (forcing_type <=0) THEN 367 369 forcing_les = .true. 368 elseif (forcing_type .eq.1) THEN370 elseif (forcing_type ==1) THEN 369 371 forcing_radconv = .true. 370 elseif (forcing_type .eq.2) THEN372 elseif (forcing_type ==2) THEN 371 373 forcing_toga = .true. 372 elseif (forcing_type .eq.3) THEN374 elseif (forcing_type ==3) THEN 373 375 forcing_GCM2SCM = .true. 374 elseif (forcing_type .eq.4) THEN376 elseif (forcing_type ==4) THEN 375 377 forcing_twpice = .true. 376 elseif (forcing_type .eq.5) THEN378 elseif (forcing_type ==5) THEN 377 379 forcing_rico = .true. 378 elseif (forcing_type .eq.6) THEN380 elseif (forcing_type ==6) THEN 379 381 forcing_amma = .true. 380 elseif (forcing_type .eq.7) THEN382 elseif (forcing_type ==7) THEN 381 383 forcing_dice = .true. 382 elseif (forcing_type .eq.8) THEN384 elseif (forcing_type ==8) THEN 383 385 forcing_gabls4 = .true. 384 elseif (forcing_type .eq.101) THEN ! Cindynamo starts 1-10-2011 0h386 elseif (forcing_type ==101) THEN ! Cindynamo starts 1-10-2011 0h 385 387 forcing_case = .true. 386 388 year_ini_cas=2011 … … 389 391 heure_ini_cas=0. 390 392 pdt_cas=3*3600. ! forcing frequency 391 elseif (forcing_type .eq.102) THEN ! Bomex starts 24-6-1969 0h393 elseif (forcing_type ==102) THEN ! Bomex starts 24-6-1969 0h 392 394 forcing_case = .true. 393 395 year_ini_cas=1969 … … 396 398 heure_ini_cas=0. 397 399 pdt_cas=1800. ! forcing frequency 398 elseif (forcing_type .eq.103) THEN ! Arm_cu starts 21-6-1997 11h30400 elseif (forcing_type ==103) THEN ! Arm_cu starts 21-6-1997 11h30 399 401 forcing_case2 = .true. 400 402 year_ini_cas=1997 … … 403 405 heure_ini_cas=11.5 404 406 pdt_cas=1800. ! forcing frequency 405 elseif (forcing_type .eq.104) THEN ! rico starts 16-12-2004 0h407 elseif (forcing_type ==104) THEN ! rico starts 16-12-2004 0h 406 408 forcing_case2 = .true. 407 409 year_ini_cas=2004 … … 410 412 heure_ini_cas=0. 411 413 pdt_cas=1800. ! forcing frequency 412 elseif (forcing_type .eq.105) THEN ! bomex starts 16-12-2004 0h414 elseif (forcing_type ==105) THEN ! bomex starts 16-12-2004 0h 413 415 forcing_case2 = .true. 414 416 year_ini_cas=1969 … … 417 419 heure_ini_cas=0. 418 420 pdt_cas=1800. ! forcing frequency 419 elseif (forcing_type .eq.106) THEN ! ayotte_24SC starts 6-11-1992 0h421 elseif (forcing_type ==106) THEN ! ayotte_24SC starts 6-11-1992 0h 420 422 forcing_case2 = .true. 421 423 year_ini_cas=1992 … … 424 426 heure_ini_cas=10. 425 427 pdt_cas=86400. ! forcing frequency 426 elseif (forcing_type .eq.113) THEN ! Arm_cu starts 21-6-1997 11h30428 elseif (forcing_type ==113) THEN ! Arm_cu starts 21-6-1997 11h30 427 429 forcing_SCM = .true. 428 430 year_ini_cas=1997 … … 432 434 mth_ini_cas=1 ! pour le moment on compte depuis le debut de l'annee 433 435 call getin('time_ini',heure_ini_cas) 434 elseif (forcing_type .eq.40) THEN436 elseif (forcing_type ==40) THEN 435 437 forcing_GCSSold = .true. 436 elseif (forcing_type .eq.50) THEN438 elseif (forcing_type ==50) THEN 437 439 forcing_fire = .true. 438 elseif (forcing_type .eq.59) THEN440 elseif (forcing_type ==59) THEN 439 441 forcing_sandu = .true. 440 elseif (forcing_type .eq.60) THEN442 elseif (forcing_type ==60) THEN 441 443 forcing_astex = .true. 442 elseif (forcing_type .eq.61) THEN444 elseif (forcing_type ==61) THEN 443 445 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 !!' 445 447 else 446 448 write (*,*) 'ERROR : unknown forcing_type ', forcing_type … … 461 463 jcode = iflag_nudge 462 464 do i = 1,nudge_max 463 nudge(i) = mod(jcode,10) .ge.1465 nudge(i) = mod(jcode,10) >= 1 464 466 jcode = jcode/10 465 467 enddo … … 528 530 529 531 ! 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. 532 534 ! 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. 534 536 ! 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. 536 538 annee_ref = anneeref 537 539 mois = 1 … … 544 546 day_end = day_ini + int(fnday) 545 547 546 IF (forcing_type .eq.2) THEN548 IF (forcing_type ==2) THEN 547 549 ! Convert the initial date of Toga-Coare to Julian day 548 550 call ymds2ju & 549 551 & (year_ini_toga,mth_ini_toga,day_ini_toga,heure,day_ju_ini_toga) 550 552 551 ELSEIF (forcing_type .eq.4) THEN553 ELSEIF (forcing_type ==4) THEN 552 554 ! Convert the initial date of TWPICE to Julian day 553 555 call ymds2ju & 554 556 & (year_ini_twpi,mth_ini_twpi,day_ini_twpi,heure_ini_twpi & 555 557 & ,day_ju_ini_twpi) 556 ELSEIF (forcing_type .eq.6) THEN558 ELSEIF (forcing_type ==6) THEN 557 559 ! Convert the initial date of AMMA to Julian day 558 560 call ymds2ju & 559 561 & (year_ini_amma,mth_ini_amma,day_ini_amma,heure_ini_amma & 560 562 & ,day_ju_ini_amma) 561 ELSEIF (forcing_type .eq.7) THEN563 ELSEIF (forcing_type ==7) THEN 562 564 ! Convert the initial date of DICE to Julian day 563 565 call ymds2ju & 564 566 & (year_ini_dice,mth_ini_dice,day_ini_dice,heure_ini_dice & 565 567 & ,day_ju_ini_dice) 566 ELSEIF (forcing_type .eq.8 ) THEN568 ELSEIF (forcing_type ==8 ) THEN 567 569 ! Convert the initial date of GABLS4 to Julian day 568 570 call ymds2ju & 569 571 & (year_ini_gabls4,mth_ini_gabls4,day_ini_gabls4,heure_ini_gabls4 & 570 572 & ,day_ju_ini_gabls4) 571 ELSEIF (forcing_type .gt.100) THEN573 ELSEIF (forcing_type >100) THEN 572 574 ! Convert the initial date to Julian day 573 575 day_ini_cas=day_deb … … 577 579 & ,day_ju_ini_cas) 578 580 print*,'time case 2',day_ini_cas,day_ju_ini_cas 579 ELSEIF (forcing_type .eq.59) THEN581 ELSEIF (forcing_type ==59) THEN 580 582 ! Convert the initial date of Sandu case to Julian day 581 583 call ymds2ju & … … 583 585 & time_ini*3600.,day_ju_ini_sandu) 584 586 585 ELSEIF (forcing_type .eq.60) THEN587 ELSEIF (forcing_type ==60) THEN 586 588 ! Convert the initial date of Astex case to Julian day 587 589 call ymds2ju & … … 589 591 & time_ini*3600.,day_ju_ini_astex) 590 592 591 ELSEIF (forcing_type .eq.61) THEN593 ELSEIF (forcing_type ==61) THEN 592 594 ! Convert the initial date of Arm_cu case to Julian day 593 595 call ymds2ju & … … 596 598 ENDIF 597 599 598 IF (forcing_type .gt.100) THEN600 IF (forcing_type >100) THEN 599 601 daytime = day + heure_ini_cas/24. ! 1st day and initial time of the simulation 600 602 ELSE … … 638 640 call phys_state_var_init(read_climoz) 639 641 640 if (ngrid .ne.klon) then642 if (ngrid/=klon) then 641 643 print*,'stop in inifis' 642 644 print*,'Probleme de dimensions :' … … 702 704 zlay=-rd*300.*log(play/psurf)/rg ! moved after reading profiles 703 705 704 IF (forcing_type .eq.59) THEN706 IF (forcing_type == 59) THEN 705 707 ! pour forcing_sandu, on cherche l'indice le plus proche de 700hpa#3000m 706 708 write(*,*) '***********************' 707 709 do l = 1, llm 708 710 write(*,*) 'l,play(l),presnivs(l): ',l,play(l),presnivs(l) 709 if (trouve_700 .and. play(l) .le.70000) then711 if (trouve_700 .and. play(l)<=70000) then 710 712 llm700=l 711 713 print *,'llm700,play=',llm700,play(l)/100. … … 826 828 print*,'avant phyredem' 827 829 pctsrf(1,:)=0. 828 if (nat_surf .eq.0.) then830 if (nat_surf==0.) then 829 831 pctsrf(1,is_oce)=1. 830 832 pctsrf(1,is_ter)=0. 831 833 pctsrf(1,is_lic)=0. 832 834 pctsrf(1,is_sic)=0. 833 else if (nat_surf .eq. 1) then835 else if (nat_surf == 1) then 834 836 pctsrf(1,is_oce)=0. 835 837 pctsrf(1,is_ter)=1. 836 838 pctsrf(1,is_lic)=0. 837 839 pctsrf(1,is_sic)=0. 838 else if (nat_surf .eq. 2) then840 else if (nat_surf == 2) then 839 841 pctsrf(1,is_oce)=0. 840 842 pctsrf(1,is_ter)=0. 841 843 pctsrf(1,is_lic)=1. 842 844 pctsrf(1,is_sic)=0. 843 else if (nat_surf .eq. 3) then845 else if (nat_surf == 3) then 844 846 pctsrf(1,is_oce)=0. 845 847 pctsrf(1,is_ter)=0. … … 870 872 pbl_tke(:,2,:)=1.e-2 871 873 PRINT *, ' pbl_tke dans lmdz1d ' 872 if (prt_level .ge. 5) then874 if (prt_level >= 5) then 873 875 DO nsrf = 1,4 874 876 PRINT *,'pbl_tke(1,:,',nsrf,') ',pbl_tke(1,:,nsrf) … … 1021 1023 endif 1022 1024 !Al1 ================ end restart ================================= 1023 IF (ecrit_slab_oc .eq.1) then1025 IF (ecrit_slab_oc==1) then 1024 1026 open(97,file='div_slab.dat',STATUS='UNKNOWN') 1025 elseif (ecrit_slab_oc .eq.0) then1027 elseif (ecrit_slab_oc==0) then 1026 1028 open(97,file='div_slab.dat',STATUS='OLD') 1027 1029 endif … … 1046 1048 it_end = nint(fnday*day_step) 1047 1049 !test JLD it_end = 10 1048 do while(it .le.it_end)1049 1050 if (prt_level .ge.1) then1050 do while(it<=it_end) 1051 1052 if (prt_level>=1) then 1051 1053 print*,'XXXXXXXXXXXXXXXXXXX ITAP,day,time=', & 1052 1054 & it,day,time,it_end,day_step … … 1054 1056 endif 1055 1057 !Al1 demande de restartphy.nc 1056 if (it .eq.it_end) lastcall=.True.1058 if (it==it_end) lastcall=.True. 1057 1059 1058 1060 !--------------------------------------------------------------------- … … 1149 1151 1150 1152 if (forcing_toga .or. forcing_GCSSold .or. forcing_twpice & 1151 & .or.forcing_amma .or. forcing_type .eq.101) then1153 & .or.forcing_amma .or. forcing_type==101) then 1152 1154 fcoriolis=0.0 ; ug=0. ; vg=0. 1153 1155 endif … … 1164 1166 !on calcule dt_cooling 1165 1167 do l=1,llm 1166 if (play(l) .ge.20000.) then1168 if (play(l)>=20000.) then 1167 1169 dt_cooling(l)=-1.5/86400. 1168 elseif ((play(l) .ge.10000.).and.((play(l).lt.20000.))) then1170 elseif ((play(l)>=10000.).and.((play(l)<20000.))) then 1169 1171 dt_cooling(l)=-1.5/86400.*(play(l)-10000.)/(10000.)-1./86400.*(20000.-play(l))/10000.*(temp(l)-200.) 1170 1172 else … … 1273 1275 & +d_q_nudge(1:mxcalc,:) ) 1274 1276 1275 if (prt_level .ge.3) then1277 if (prt_level>=3) then 1276 1278 print *, & 1277 1279 & 'physiq-> temp(1),dt_phys(1),d_t_adv(1),dt_cooling(1) ', & … … 1351 1353 1352 1354 !Al1 1353 if (ecrit_slab_oc .ne.-1) close(97)1355 if (ecrit_slab_oc/=-1) close(97) 1354 1356 1355 1357 !Al1 Call to 1D equivalent of dynredem (an,mois,jour,heure ?) -
LMDZ6/trunk/libf/phylmd/grid_noro_m.F90
r3435 r5075 435 435 ! Purpose: Read parameters usually determined with grid_noro from a file. 436 436 !=============================================================================== 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, & 438 438 NF90_NOERR, NF90_CLOSE, NF90_INQ_VARID, NF90_GET_VAR, NF90_STRERROR, & 439 439 NF90_NOWRITE -
LMDZ6/trunk/libf/phylmd/ice_sursat_mod.F90
r4535 r5075 96 96 USE mod_phys_lmdz_para, ONLY: scatter, bcast 97 97 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 98 100 99 101 IMPLICIT NONE 100 102 101 103 INCLUDE "YOMCST.h" 102 INCLUDE 'netcdf.inc'103 104 104 105 !-------------------------------------------------------- … … 168 169 iret = nf_inq_varid(ncida, 'lev', varid) 169 170 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) 171 172 IF (iret /= NF_NOERR) CALL abort_physic(modname,'problem to read zmida file',1) 172 173 ! 173 174 iret = nf_inq_varid(ncida, 'emi_co2_aircraft', varid) !--CO2 as a proxy for m flown - 174 175 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) 176 177 IF (iret /= NF_NOERR) CALL abort_physic(modname,'problem to read pkm_airpl file',1) 177 178 ! 178 179 iret = nf_inq_varid(ncida, 'emi_h2o_aircraft', varid) 179 180 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) 181 182 IF (iret /= NF_NOERR) CALL abort_physic(modname,'problem to read ph2o_airpl file',1) 182 183 ! … … 276 277 ! 277 278 DO i=1, klon 278 IF (latitude_deg(i) .GE.42.0.AND.latitude_deg(i).LE.48.0) THEN279 IF (latitude_deg(i)>=42.0.AND.latitude_deg(i)<=48.0) THEN 279 280 flight_m(i,38) = 50000.0 !--5000 m of flight/second in grid cell x 10 scaling 280 281 ENDIF … … 412 413 pdf_b = pdf_k/(2.*sqrt(2.)) 413 414 pdf_e1 = pdf_a+pdf_b 414 IF (abs(pdf_e1) .GE.erf_lim) THEN415 IF (abs(pdf_e1)>=erf_lim) THEN 415 416 pdf_e1 = sign(1.,pdf_e1) 416 417 pdf_N = max(0.,sign(rneb,pdf_e1)) … … 425 426 ! On perd la memoire sur la temperature (sur qvc) pour garder 426 427 ! celle sur alpha_cld 427 IF (pdf_N .GT.1.) THEN428 IF (pdf_N>1.) THEN 428 429 ! On inverse alpha_cld = int_qvc^infty P(q) dq 429 430 ! pour determiner qvc = f(alpha_cld) … … 441 442 pdf_a = log(qvc/q)/(pdf_k*sqrt(2.)) 442 443 pdf_e1 = pdf_a+pdf_b 443 IF (abs(pdf_e1) .GE.erf_lim) THEN444 IF (abs(pdf_e1)>=erf_lim) THEN 444 445 pdf_e1 = sign(1.,pdf_e1) 445 446 ELSE … … 461 462 pdf_a = log(qvc*gamma_prec/q)/(pdf_k*sqrt(2.)) 462 463 pdf_e2 = pdf_a+pdf_b 463 IF (abs(pdf_e2) .GE.erf_lim) THEN464 IF (abs(pdf_e2)>=erf_lim) THEN 464 465 pdf_e2 = sign(1.,pdf_e2) 465 466 ELSE … … 468 469 pdf_e2 = 0.5*(1.+pdf_e2) ! integrale sous P pour q > gamma qsat 469 470 470 IF (abs(pdf_e1-pdf_e2) .LT.eps) THEN471 IF (abs(pdf_e1-pdf_e2)<eps) THEN 471 472 pdf_N1 = pdf_N2 472 473 ELSE … … 475 476 476 477 ! Barriere qui traite le cas gamma_prec = 1. 477 IF (pdf_N1 .LE.0.) THEN478 IF (pdf_N1<=0.) THEN 478 479 pdf_N1 = 0. 479 IF (pdf_e2 .GT.eps) THEN480 IF (pdf_e2>eps) THEN 480 481 pdf_N2 = rneb/pdf_e2 481 482 ELSE … … 487 488 ! Physique 1 488 489 ! Sublimation 489 IF (qvc .LT.qsat) THEN490 IF (qvc<qsat) THEN 490 491 pdf_a = log(qvc/q)/(pdf_k*sqrt(2.)) 491 492 pdf_e1 = pdf_a+pdf_b 492 IF (abs(pdf_e1) .GE.erf_lim) THEN493 IF (abs(pdf_e1)>=erf_lim) THEN 493 494 pdf_e1 = sign(1.,pdf_e1) 494 495 ELSE … … 498 499 pdf_a = log(qsat/q)/(pdf_k*sqrt(2.)) 499 500 pdf_e2 = pdf_a+pdf_b 500 IF (abs(pdf_e2) .GE.erf_lim) THEN501 IF (abs(pdf_e2)>=erf_lim) THEN 501 502 pdf_e2 = sign(1.,pdf_e2) 502 503 ELSE … … 516 517 517 518 ! Condensation 518 IF (gamma_ss*qsat .LT.gamma_prec*qvc) THEN519 IF (gamma_ss*qsat<gamma_prec*qvc) THEN 519 520 520 521 pdf_a = log(gamma_ss*qsat/q)/(pdf_k*sqrt(2.)) 521 522 pdf_e1 = pdf_a+pdf_b 522 IF (abs(pdf_e1) .GE.erf_lim) THEN523 IF (abs(pdf_e1)>=erf_lim) THEN 523 524 pdf_e1 = sign(1.,pdf_e1) 524 525 ELSE … … 528 529 pdf_a = log(gamma_prec*qvc/q)/(pdf_k*sqrt(2.)) 529 530 pdf_e2 = pdf_a+pdf_b 530 IF (abs(pdf_e2) .GE.erf_lim) THEN531 IF (abs(pdf_e2)>=erf_lim) THEN 531 532 pdf_e2 = sign(1.,pdf_e2) 532 533 ELSE … … 545 546 pdf_a = log(gamma_ss*qsat/q)/(pdf_k*sqrt(2.)) 546 547 pdf_e1 = pdf_a+pdf_b 547 IF (abs(pdf_e1) .GE.erf_lim) THEN548 IF (abs(pdf_e1)>=erf_lim) THEN 548 549 pdf_e1 = sign(1.,pdf_e1) 549 550 ELSE … … 562 563 pdf_a = log(qsat/q)/(pdf_k*sqrt(2.)) 563 564 pdf_e1 = pdf_a+pdf_b 564 IF (abs(pdf_e1) .GE.erf_lim) THEN565 IF (abs(pdf_e1)>=erf_lim) THEN 565 566 pdf_e1 = sign(1.,pdf_e1) 566 567 ELSE … … 570 571 571 572 pdf_e2 = pdf_a-pdf_b 572 IF (abs(pdf_e2) .GE.erf_lim) THEN573 IF (abs(pdf_e2)>=erf_lim) THEN 573 574 pdf_e2 = sign(1.,pdf_e2) 574 575 ELSE … … 584 585 pdf_a = log(max(qsat,qvc)/q)/(pdf_k*sqrt(2.)) 585 586 pdf_e1 = pdf_a-pdf_b 586 IF (abs(pdf_e1) .GE.erf_lim) THEN587 IF (abs(pdf_e1)>=erf_lim) THEN 587 588 pdf_e1 = sign(1.,pdf_e1) 588 589 ELSE … … 592 593 pdf_a = log(min(gamma_ss*qsat,gamma_prec*qvc)/q)/(pdf_k*sqrt(2.)) 593 594 pdf_e2 = pdf_a-pdf_b 594 IF (abs(pdf_e2) .GE.erf_lim) THEN595 IF (abs(pdf_e2)>=erf_lim) THEN 595 596 pdf_e2 = sign(1.,pdf_e2) 596 597 ELSE … … 603 604 604 605 ! Partie 2 (sous condition) 605 IF (gamma_ss*qsat .GT.gamma_prec*qvc) THEN606 IF (gamma_ss*qsat>gamma_prec*qvc) THEN 606 607 pdf_a = log(gamma_ss*qsat/q)/(pdf_k*sqrt(2.)) 607 608 pdf_e1 = pdf_a-pdf_b 608 IF (abs(pdf_e1) .GE.erf_lim) THEN609 IF (abs(pdf_e1)>=erf_lim) THEN 609 610 pdf_e1 = sign(1.,pdf_e1) 610 611 ELSE … … 632 633 633 634 ! Physique 2 : Turbulence 634 IF (rneb .GT.eps.AND.rneb.LT.1.-eps) THEN ! rneb != 0 and != 1635 IF (rneb>eps.AND.rneb<1.-eps) THEN ! rneb != 0 and != 1 635 636 ! 636 637 tke = pbl_tke(i,k,is_ave) … … 642 643 b_tur = (rneb*V_cell/4./PI/N_cld)**(1./3.) 643 644 ! On verifie que la longeur de melange n'est pas trop grande 644 IF (L_tur .GT.b_tur) THEN645 IF (L_tur>b_tur) THEN 645 646 L_tur = b_tur 646 647 ENDIF … … 665 666 q_eq = q_eq/(V_env + V_cld) 666 667 667 IF (q_eq .GT.qsat) THEN668 IF (q_eq>qsat) THEN 668 669 drnebclr = - V_clr/V_cell 669 670 dqclr = drnebclr*qclr/MAX(eps,rnebclr) … … 703 704 ! Barrieres 704 705 ! ISSR trop petite 705 IF (rnebss .LT.eps) THEN706 IF (rnebss<eps) THEN 706 707 rneb = MIN(rneb + rnebss,1.0-eps) !--ajout OB barriere 707 708 qcld = qcld + qss … … 711 712 712 713 ! le nuage est trop petit 713 IF (rneb .LT.eps) THEN714 IF (rneb<eps) THEN 714 715 ! s'il y a une ISSR on met tout dans l'ISSR, sinon dans le 715 716 ! clear sky 716 IF (rnebss .LT.eps) THEN717 IF (rnebss<eps) THEN 717 718 rnebclr = 1. 718 719 rnebss = 0. !--ajout OB … … 749 750 !--critical T_LM below which no liquid contrail can form in exhaust 750 751 !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) THEN752 IF (Gcontr > 0.1) THEN 752 753 ! 753 754 Tcontr = 226.69+9.43*log(Gcontr-0.053)+0.72*(log(Gcontr-0.053))**2 !--K … … 775 776 !qcontr2 = eps_w*qcontr / (pplay+eps_w*qcontr) 776 777 ! 777 IF (t .LT.Tcontr) THEN !--contrail formation is possible778 IF (t < Tcontr) THEN !--contrail formation is possible 778 779 ! 779 780 !--compute fractions of persistent (P) and non-persistent(N) contrail potential regions 780 781 !!IF (qcontr(i,k).GE.qsat) THEN 781 IF (qcontr2 .GE.qsat) THEN782 IF (qcontr2>=qsat) THEN 782 783 !--none of the unsaturated clear sky is prone for contrail formation 783 784 !!fcontrN(i,k) = 0.0 … … 787 788 pdf_a = log(qsat/q)/(pdf_k*sqrt(2.)) 788 789 pdf_e1 = pdf_a+pdf_b 789 IF (abs(pdf_e1) .GE.erf_lim) THEN790 IF (abs(pdf_e1)>=erf_lim) THEN 790 791 pdf_e1 = sign(1.,pdf_e1) 791 792 ELSE … … 796 797 pdf_a = log(MIN(qcontr2,qvc)/q)/(pdf_k*sqrt(2.)) 797 798 pdf_e2 = pdf_a+pdf_b 798 IF (abs(pdf_e2) .GE.erf_lim) THEN799 IF (abs(pdf_e2)>=erf_lim) THEN 799 800 pdf_e2 = sign(1.,pdf_e2) 800 801 ELSE … … 807 808 pdf_a = log(qsat/q)/(pdf_k*sqrt(2.)) 808 809 pdf_e1 = pdf_a+pdf_b 809 IF (abs(pdf_e1) .GE.erf_lim) THEN810 IF (abs(pdf_e1)>=erf_lim) THEN 810 811 pdf_e1 = sign(1.,pdf_e1) 811 812 ELSE … … 816 817 pdf_a = log(MIN(qcontr2,qvc)/q)/(pdf_k*sqrt(2.)) 817 818 pdf_e2 = pdf_a+pdf_b 818 IF (abs(pdf_e2) .GE.erf_lim) THEN819 IF (abs(pdf_e2)>=erf_lim) THEN 819 820 pdf_e2 = sign(1.,pdf_e2) 820 821 ELSE … … 827 828 pdf_a = log(MAX(qsat,qvc)/q)/(pdf_k*sqrt(2.)) 828 829 pdf_e1 = pdf_a+pdf_b 829 IF (abs(pdf_e1) .GE.erf_lim) THEN830 IF (abs(pdf_e1)>=erf_lim) THEN 830 831 pdf_e1 = sign(1.,pdf_e1) 831 832 ELSE … … 836 837 pdf_a = log(MIN(qcontr2,MIN(gamma_prec*qvc,gamma_ss*qsat))/q)/(pdf_k*sqrt(2.)) 837 838 pdf_e2 = pdf_a+pdf_b 838 IF (abs(pdf_e2) .GE.erf_lim) THEN839 IF (abs(pdf_e2)>=erf_lim) THEN 839 840 pdf_e2 = sign(1.,pdf_e2) 840 841 ELSE … … 847 848 pdf_a = log(gamma_prec*qvc/q)/(pdf_k*sqrt(2.)) 848 849 pdf_e1 = pdf_a+pdf_b 849 IF (abs(pdf_e1) .GE.erf_lim) THEN850 IF (abs(pdf_e1)>=erf_lim) THEN 850 851 pdf_e1 = sign(1.,pdf_e1) 851 852 ELSE … … 856 857 pdf_a = log(MIN(qcontr2,gamma_ss*qsat)/q)/(pdf_k*sqrt(2.)) 857 858 pdf_e2 = pdf_a+pdf_b 858 IF (abs(pdf_e2) .GE.erf_lim) THEN859 IF (abs(pdf_e2)>=erf_lim) THEN 859 860 pdf_e2 = sign(1.,pdf_e2) 860 861 ELSE … … 875 876 pdf_a = log(qcontr2/q)/(pdf_k*sqrt(2.)) 876 877 pdf_e1 = pdf_a+pdf_b !--normalement pdf_b est deja defini 877 IF (abs(pdf_e1) .GE.erf_lim) THEN878 IF (abs(pdf_e1)>=erf_lim) THEN 878 879 pdf_e1 = sign(1.,pdf_e1) 879 880 ELSE … … 883 884 pdf_a = log(qsat/q)/(pdf_k*sqrt(2.)) 884 885 pdf_e2 = pdf_a+pdf_b 885 IF (abs(pdf_e2) .GE.erf_lim) THEN886 IF (abs(pdf_e2)>=erf_lim) THEN 886 887 pdf_e2 = sign(1.,pdf_e2) 887 888 ELSE -
LMDZ6/trunk/libf/phylmd/inlandsis/surf_inlandsis_mod.F90
r3900 r5075 638 638 END DO 639 639 640 IF (sissnow(ikl) .LE.sn_low) THEN !add snow641 IF (isnoSV(ikl) .GE.1) THEN640 IF (sissnow(ikl) <= sn_low) THEN !add snow 641 IF (isnoSV(ikl)>=1) THEN 642 642 dzsnSV(ikl, 1) = dzsnSV(ikl, 1) + sn_add / max(ro__SV(ikl, 1), epsi) 643 643 toicSV(ikl) = toicSV(ikl) - sn_add … … 657 657 END IF 658 658 659 IF (sissnow(ikl) .ge.sn_upp) THEN !thinnen snow layer below659 IF (sissnow(ikl) >= sn_upp) THEN !thinnen snow layer below 660 660 dzsnSV(ikl, 1) = dzsnSV(ikl, 1) / sn_div 661 661 toicSV(ikl) = toicSV(ikl) + dzsnSV(ikl, 1) * ro__SV(ikl, 1) / sn_div … … 1049 1049 ! Objet: Lecture du fichier de conditions initiales pour SISVAT 1050 1050 !====================================================================== 1051 include "netcdf.inc"1052 1051 ! include "indicesol.h" 1053 1052 … … 1118 1117 1119 1118 DO isn = 1, nsno 1120 IF (isn .LE.99) THEN1119 IF (isn<=99) THEN 1121 1120 WRITE(str2, '(i2.2)') isn 1122 1121 CALL get_field("AGESNOW" // str2, & … … 1128 1127 ENDDO 1129 1128 DO isn = 1, nsno 1130 IF (isn .LE.99) THEN1129 IF (isn<=99) THEN 1131 1130 WRITE(str2, '(i2.2)') isn 1132 1131 CALL get_field("DZSNOW" // str2, & … … 1138 1137 ENDDO 1139 1138 DO isn = 1, nsno 1140 IF (isn .LE.99) THEN1139 IF (isn<=99) THEN 1141 1140 WRITE(str2, '(i2.2)') isn 1142 1141 CALL get_field("G2SNOW" // str2, & … … 1148 1147 ENDDO 1149 1148 DO isn = 1, nsno 1150 IF (isn .LE.99) THEN1149 IF (isn<=99) THEN 1151 1150 WRITE(str2, '(i2.2)') isn 1152 1151 CALL get_field("G1SNOW" // str2, & … … 1158 1157 ENDDO 1159 1158 DO isn = 1, nsismx 1160 IF (isn .LE.99) THEN1159 IF (isn<=99) THEN 1161 1160 WRITE(str2, '(i2.2)') isn 1162 1161 CALL get_field("ETA" // str2, & … … 1168 1167 ENDDO 1169 1168 DO isn = 1, nsismx 1170 IF (isn .LE.99) THEN1169 IF (isn<=99) THEN 1171 1170 WRITE(str2, '(i2.2)') isn 1172 1171 CALL get_field("RO" // str2, & … … 1178 1177 ENDDO 1179 1178 DO isn = 1, nsismx 1180 IF (isn .LE.99) THEN1179 IF (isn<=99) THEN 1181 1180 WRITE(str2, '(i2.2)') isn 1182 1181 CALL get_field("TSS" // str2, & … … 1188 1187 ENDDO 1189 1188 DO isn = 1, nsno 1190 IF (isn .LE.99) THEN1189 IF (isn<=99) THEN 1191 1190 WRITE(str2, '(i2.2)') isn 1192 1191 CALL get_field("HISTORY" // str2, & … … 1287 1286 IMPLICIT none 1288 1287 1289 include "netcdf.inc"1290 1288 ! include "indicesol.h" 1291 1289 ! include "dimsoil.h" … … 1403 1401 1404 1402 DO isn = 1, nsno 1405 IF (isn .LE.99) THEN1403 IF (isn<=99) THEN 1406 1404 WRITE(str2, '(i2.2)') isn 1407 1405 CALL put_field(pass, "AGESNOW" // str2, & … … 1414 1412 ENDDO 1415 1413 DO isn = 1, nsno 1416 IF (isn .LE.99) THEN1414 IF (isn<=99) THEN 1417 1415 WRITE(str2, '(i2.2)') isn 1418 1416 CALL put_field(pass, "DZSNOW" // str2, & … … 1425 1423 ENDDO 1426 1424 DO isn = 1, nsno 1427 IF (isn .LE.99) THEN1425 IF (isn<=99) THEN 1428 1426 WRITE(str2, '(i2.2)') isn 1429 1427 CALL put_field(pass, "G2SNOW" // str2, & … … 1436 1434 ENDDO 1437 1435 DO isn = 1, nsno 1438 IF (isn .LE.99) THEN1436 IF (isn<=99) THEN 1439 1437 WRITE(str2, '(i2.2)') isn 1440 1438 CALL put_field(pass, "G1SNOW" // str2, & … … 1447 1445 ENDDO 1448 1446 DO isn = 1, nsismx 1449 IF (isn .LE.99) THEN1447 IF (isn<=99) THEN 1450 1448 WRITE(str2, '(i2.2)') isn 1451 1449 CALL put_field(pass, "ETA" // str2, & … … 1458 1456 ENDDO 1459 1457 DO isn = 1, nsismx !nsno 1460 IF (isn .LE.99) THEN1458 IF (isn<=99) THEN 1461 1459 WRITE(str2, '(i2.2)') isn 1462 1460 CALL put_field(pass, "RO" // str2, & … … 1469 1467 ENDDO 1470 1468 DO isn = 1, nsismx 1471 IF (isn .LE.99) THEN1469 IF (isn<=99) THEN 1472 1470 WRITE(str2, '(i2.2)') isn 1473 1471 CALL put_field(pass, "TSS" // str2, & … … 1480 1478 ENDDO 1481 1479 DO isn = 1, nsno 1482 IF (isn .LE.99) THEN1480 IF (isn<=99) THEN 1483 1481 WRITE(str2, '(i2.2)') isn 1484 1482 CALL put_field(pass, "HISTORY" // str2, & -
LMDZ6/trunk/libf/phylmd/interfoce_lim.F90
r5073 r5075 10 10 USE mod_phys_lmdz_para 11 11 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 13 13 14 14 IMPLICIT NONE -
LMDZ6/trunk/libf/phylmd/iostart.F90
r5073 r5075 30 30 31 31 SUBROUTINE Open_startphy(filename) 32 USE lmdz_netcdf 32 USE lmdz_netcdf, ONLY: nf90_nowrite, nf90_noerr,nf90_open 33 33 USE mod_phys_lmdz_para 34 34 IMPLICIT NONE … … 48 48 49 49 SUBROUTINE Close_startphy 50 USE lmdz_netcdf 50 USE lmdz_netcdf, ONLY: nf90_close 51 51 USE mod_phys_lmdz_para 52 52 IMPLICIT NONE … … 61 61 62 62 FUNCTION Inquire_Field(Field_name) 63 USE lmdz_netcdf 63 USE lmdz_netcdf, ONLY: nf90_noerr,nf90_inq_varid 64 64 USE mod_phys_lmdz_para 65 65 IMPLICIT NONE … … 115 115 116 116 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 118 118 USE dimphy 119 119 USE geometry_mod … … 251 251 252 252 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 254 254 USE dimphy 255 255 USE mod_grid_phy_lmdz … … 301 301 302 302 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 304 305 USE mod_phys_lmdz_para, ONLY: is_master 305 306 USE mod_grid_phy_lmdz, ONLY: klon_glo … … 332 333 333 334 SUBROUTINE enddef_restartphy 334 USE lmdz_netcdf 335 USE lmdz_netcdf, ONLY: nf90_enddef 335 336 USE mod_phys_lmdz_para 336 337 IMPLICIT NONE … … 342 343 343 344 SUBROUTINE close_restartphy 344 USE lmdz_netcdf 345 USE lmdz_netcdf, ONLY: nf90_close 345 346 USE mod_phys_lmdz_para 346 347 IMPLICIT NONE … … 385 386 386 387 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 388 389 USE dimphy 389 390 USE geometry_mod … … 508 509 509 510 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 511 512 USE dimphy 512 513 USE mod_phys_lmdz_para -
LMDZ6/trunk/libf/phylmd/iotd_ecrit.F90
r4593 r5075 22 22 !================================================================= 23 23 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 25 26 implicit none 26 27 27 28 ! Commons 28 29 29 INCLUDE "netcdf.inc"30 30 INCLUDE "iotd.h" 31 31 … … 90 90 91 91 !! Quand on tombe sur la premiere variable on ajoute un pas de temps 92 if (nom .eq.firstnom) then92 if (nom==firstnom) then 93 93 ! We have identified a "first call" (at given date) 94 94 … … 114 114 ! print*,'IOTD Date ,varid,nid,ntime,date',varid,nid,ntime,date 115 115 116 if (ierr .ne.NF_NOERR) then116 if (ierr/=NF_NOERR) then 117 117 write(*,*) "***** PUT_VAR matter in writediagfi_nc" 118 118 write(*,*) "***** with time" … … 175 175 ierr= NF90_PUT_VAR(nid,varid,zx,corner,edges) 176 176 177 if (ierr .ne.NF_NOERR) then177 if (ierr/=NF_NOERR) then 178 178 write(*,*) "***** PUT_VAR problem in writediagfi" 179 179 write(*,*) "***** with ",nom -
LMDZ6/trunk/libf/phylmd/iotd_fin.F90
r4593 r5075 1 2 IMPLICIT NONE1 SUBROUTINE iotd_fin 2 USE lmdz_netcdf, ONLY : nf_close 3 3 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 14 5 6 !======================================================================= 7 ! 8 ! Auteur: F. Hourdin 9 ! ------- 10 ! 11 ! Objet: 12 ! ------ 13 ! Light interface for netcdf outputs. can be used outside LMDZ 14 ! 15 !======================================================================= 15 16 16 INCLUDE "netcdf.inc" 17 INCLUDE "iotd.h" 18 integer ierr 17 INCLUDE "iotd.h" 18 integer ierr 19 19 20 ! Arguments:21 ! ----------20 ! Arguments: 21 ! ---------- 22 22 23 ierr=NF_close(nid)23 ierr = NF_close(nid) 24 24 25 25 END -
LMDZ6/trunk/libf/phylmd/iotd_ini.F90
r4593 r5075 1 1 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 2 4 IMPLICIT NONE 3 5 … … 16 18 ! ------------- 17 19 18 INCLUDE "netcdf.inc"19 20 INCLUDE "iotd.h" 20 21 … … 31 32 real px(1000) 32 33 character (len=10) :: nom 33 real *4rlon(iim),rlat(jjm),coordv(llm)34 real(kind=4) rlon(iim),rlat(jjm),coordv(llm) 34 35 35 36 ! Local: … … 71 72 n_names_iotd_def=0 72 73 open(99,file='iotd.def',form='formatted',status='old',iostat=ierr) 73 if ( ierr .eq.0 ) then74 if ( ierr==0 ) then 74 75 ierr=0 75 76 do while (ierr==0) … … 112 113 ierr=NF_PUT_ATT_TEXT(nid,nvarid,'units',12,"degrees_east") 113 114 ierr=NF_ENDDEF(nid) 114 ierr= NF_PUT_VAR_REAL(nid,nvarid,rlon)115 ierr=nf90_put_var(nid,nvarid,rlon) 115 116 print*,ierr 116 117 … … 121 122 ierr=NF_PUT_ATT_TEXT(nid,nvarid,'units',13,"degrees_north") 122 123 ierr=NF_ENDDEF(nid) 123 ierr= NF_PUT_VAR_REAL(nid,nvarid,rlat)124 ierr=nf90_put_var(nid,nvarid,rlat) 124 125 ! 125 126 ! ---- vertical ------------ … … 135 136 endif 136 137 ierr=NF_ENDDEF(nid) 137 ierr= NF_PUT_VAR_REAL(nid,nvarid,coordv)138 ierr=nf90_put_var(nid,nvarid,coordv) 138 139 139 140 ! -
LMDZ6/trunk/libf/phylmd/limit_read_mod.F90
r4619 r5075 165 165 USE mod_phys_lmdz_para 166 166 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 168 169 USE indice_sol_mod 169 170 USE phys_cal_mod, ONLY : calend, year_len -
LMDZ6/trunk/libf/phylmd/limit_slab.F90
r3102 r5075 6 6 USE mod_grid_phy_lmdz, ONLY: klon_glo 7 7 USE mod_phys_lmdz_para 8 USE netcdf8 USE lmdz_netcdf, ONLY: nf90_close,nf90_get_var,nf90_inq_varid,nf90_nowrite,nf90_noerr,nf90_open 9 9 USE indice_sol_mod 10 10 USE ocean_slab_mod, ONLY: nslay … … 99 99 END IF 100 100 ! Try next layers if more than 1 101 IF ((nslay .GT.1).AND.read_bils) THEN101 IF ((nslay>1).AND.read_bils) THEN 102 102 DO i=2,nslay 103 103 WRITE(str2,'(i2.2)') i 104 104 ierr = NF90_INQ_VARID(nid,'BILS_OCE'//str2, nvarid) 105 IF (ierr .EQ.NF90_NOERR) THEN105 IF (ierr==NF90_NOERR) THEN 106 106 ierr = NF90_GET_VAR(nid,nvarid,bils_glo(:,i),start,epais) 107 107 ENDIF -
LMDZ6/trunk/libf/phylmd/mo_simple_plumes.F90
r4164 r5075 24 24 MODULE MO_SIMPLE_PLUMES 25 25 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 27 28 28 29 IMPLICIT NONE -
LMDZ6/trunk/libf/phylmd/moy_undefSTD.F90
r4619 r5075 3 3 4 4 SUBROUTINE moy_undefstd(itap, itapm1) 5 USE netcdf5 USE lmdz_netcdf, ONLY: nf90_fill_real 6 6 USE dimphy 7 7 #ifdef CPP_IOIPSL -
LMDZ6/trunk/libf/phylmd/open_climoz_m.F90
r4489 r5075 13 13 !------------------------------------------------------------------------------- 14 14 USE netcdf95, ONLY: nf95_open, nf95_close, nf95_gw_var, nf95_inq_varid 15 USE netcdf, ONLY: nf90_nowrite15 USE lmdz_netcdf, ONLY: nf90_nowrite 16 16 USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root 17 17 USE mod_phys_lmdz_mpi_transfert, ONLY: bcast_mpi -
LMDZ6/trunk/libf/phylmd/pbl_surface_mod.F90
r5039 r5075 415 415 use lmdz_blowing_snow_ini, only : zeta_bs 416 416 USE wxios, ONLY: missing_val_xios => missing_val, using_xios 417 USE netcdf, only: missing_val_netcdf => nf90_fill_real417 USE lmdz_netcdf, only: missing_val_netcdf => nf90_fill_real 418 418 419 419 -
LMDZ6/trunk/libf/phylmd/phyetat0_mod.F90
r4744 r5075 40 40 USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy 41 41 USE wxios, ONLY: missing_val_xios => missing_val, using_xios 42 use netcdf, only: missing_val_netcdf => nf90_fill_real42 use lmdz_netcdf, only: missing_val_netcdf => nf90_fill_real 43 43 use config_ocean_skin_m, only: activate_ocean_skin 44 44 … … 152 152 tab_cntrl(6)=nbapp_rad 153 153 154 IF (iflag_cycle_diurne .GE.1) tab_cntrl( 7) = iflag_cycle_diurne154 IF (iflag_cycle_diurne>=1) tab_cntrl( 7) = iflag_cycle_diurne 155 155 IF (soil_model) tab_cntrl( 8) =1. 156 156 IF (new_oliq) tab_cntrl( 9) =1. … … 251 251 + pctsrf(1 : klon, is_lic) 252 252 DO i = 1 , klon 253 IF ( abs(fractint(i) - zmasq(i) ) .GT.EPSFRA ) THEN253 IF ( abs(fractint(i) - zmasq(i) ) > EPSFRA ) THEN 254 254 WRITE(*, *) 'phyetat0: attention fraction terre pas ', & 255 255 'coherente ', i, zmasq(i), pctsrf(i, is_ter) & … … 262 262 + pctsrf(1 : klon, is_sic) 263 263 DO i = 1 , klon 264 IF ( abs( fractint(i) - (1. - zmasq(i))) .GT.EPSFRA ) THEN264 IF ( abs( fractint(i) - (1. - zmasq(i))) > EPSFRA ) THEN 265 265 WRITE(*, *) 'phyetat0 attention fraction ocean pas ', & 266 266 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) & … … 290 290 DO nsrf = 1, nbsrf 291 291 DO isw=1, nsw 292 IF (isw .GT.99) THEN292 IF (isw>99) THEN 293 293 PRINT*, "Trop de bandes SW" 294 294 call abort_physic("phyetat0", "", 1) … … 313 313 314 314 DO isoil=1, nsoilmx 315 IF (isoil .GT.99) THEN315 IF (isoil>99) THEN 316 316 PRINT*, "Trop de couches " 317 317 call abort_physic("phyetat0", "", 1) … … 416 416 ! dummy values (as is the case when generated by ce0l, 417 417 ! 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)) ) THEN418 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 426 426 ancien_ok=.false. 427 427 ENDIF 428 428 429 429 IF (ok_bs) THEN 430 IF ( (maxval(qbs_ancien) .EQ.minval(qbs_ancien)) .OR. &431 (maxval(prbsw_ancien) .EQ.minval(prbsw_ancien)) ) THEN430 IF ( (maxval(qbs_ancien)==minval(qbs_ancien)) .OR. & 431 (maxval(prbsw_ancien)==minval(prbsw_ancien)) ) THEN 432 432 ancien_ok=.false. 433 433 ENDIF … … 549 549 IF ( type_ocean == 'slab' ) THEN 550 550 CALL ocean_slab_init(phys_tstep, pctsrf) 551 IF (nslay .EQ.1) THEN551 IF (nslay==1) THEN 552 552 found=phyetat0_get(tslab,["tslab01","tslab "],"tslab",0.) 553 553 ELSE … … 578 578 PRINT*, "Initialisation a 0/1m suivant fraction glace" 579 579 seaice(:)=0. 580 WHERE (pctsrf(:,is_sic) .GT.EPSFRA)580 WHERE (pctsrf(:,is_sic)>EPSFRA) 581 581 seaice=917. 582 582 ENDWHERE -
LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90
r5050 r5075 456 456 USE ioipsl, ONLY: histend, histsync 457 457 USE iophy, ONLY: set_itau_iophy, histwrite_phy 458 USE netcdf, ONLY: nf90_fill_real458 USE lmdz_netcdf, ONLY: nf90_fill_real 459 459 USE print_control_mod, ONLY: prt_level,lunout 460 460 ! ug Pour les sorties XIOS … … 555 555 kmax_100m=1 556 556 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 margin557 IF (presnivs(k)>0.97*101325.) kmax_100m = k !--finding out max level for 100 m with a good margin 558 558 ENDDO 559 559 ENDIF … … 782 782 DO k=1, kmax_100m-1 !--we could stop much lower 783 783 DO i=1,klon 784 IF (z(i,k) .LT.100..AND.z(i,k+1).GE.100.) THEN784 IF (z(i,k)<100..AND.z(i,k+1)>=100.) THEN 785 785 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 + & 786 786 (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 ) … … 794 794 !--polynomial fit for 14,Vestas,1074,V136/3450 kW windmill - Olivier 795 795 DO i=1,klon 796 IF (pctsrf(i,is_ter) .GT.0.05 .AND. wind100m(i).NE.missing_val) THEN796 IF (pctsrf(i,is_ter)>0.05 .AND. wind100m(i)/=missing_val) THEN 797 797 x=wind100m(i) 798 IF (x .LE.3.0 .OR. x.GE.22.5) THEN798 IF (x<=3.0 .OR. x>=22.5) THEN 799 799 zx_tmp_fi2d(i)=0.0 800 ELSE IF (x .GE.10.0) THEN800 ELSE IF (x>=10.0) THEN 801 801 zx_tmp_fi2d(i)=1.0 802 802 ELSE … … 815 815 !--polynomial fit for 14,Vestas,867,V164/8000 kW - Olivier 816 816 DO i=1,klon 817 IF (pctsrf(i,is_oce) .GT.0.05 .AND. wind100m(i).NE.missing_val) THEN817 IF (pctsrf(i,is_oce)>0.05 .AND. wind100m(i)/=missing_val) THEN 818 818 x=wind100m(i) 819 IF (x .LE.3.0 .OR. x.GE.25.5) THEN819 IF (x<=3.0 .OR. x>=25.5) THEN 820 820 zx_tmp_fi2d(i)=0.0 821 ELSE IF (x .GE.12.5) THEN821 ELSE IF (x>=12.5) THEN 822 822 zx_tmp_fi2d(i)=1.0 823 823 ELSE … … 1407 1407 CALL histwrite_phy(o_uwat, uwat) 1408 1408 CALL histwrite_phy(o_vwat, vwat) 1409 IF (iflag_con .GE.3) THEN ! sb1409 IF (iflag_con>=3) THEN ! sb 1410 1410 CALL histwrite_phy(o_cape, cape) 1411 1411 CALL histwrite_phy(o_pbase, ema_pcb) … … 1512 1512 DO k=1, nlevSTD 1513 1513 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") THEN1514 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 1518 1518 ll=ll+1 1519 1519 CALL histwrite_phy(o_uSTDlevs(ll),ulevSTD(:,k)) … … 1530 1530 IF (vars_defined) THEN 1531 1531 DO i=1, klon 1532 IF (pctsrf(i,is_oce) .GT.epsfra.OR. &1533 pctsrf(i,is_sic) .GT.epsfra) THEN1532 IF (pctsrf(i,is_oce)>epsfra.OR. & 1533 pctsrf(i,is_sic)>epsfra) THEN 1534 1534 zx_tmp_fi2d(i) = (ftsol(i, is_oce) * pctsrf(i,is_oce)+ & 1535 1535 ftsol(i, is_sic) * pctsrf(i,is_sic))/ & … … 1543 1543 1544 1544 ! Couplage convection-couche limite 1545 IF (iflag_con .GE.3) THEN1545 IF (iflag_con>=3) THEN 1546 1546 IF (iflag_coupl>=1) THEN 1547 1547 CALL histwrite_phy(o_ale_bl, ale_bl) … … 1550 1550 ENDIF !(iflag_con.GE.3) 1551 1551 ! Wakes 1552 IF (iflag_con .EQ.3) THEN1552 IF (iflag_con==3) THEN 1553 1553 CALL histwrite_phy(o_Mipsh, Mipsh) 1554 1554 IF (iflag_wake>=1) THEN … … 1620 1620 CALL histwrite_phy(o_fqd, fqd) 1621 1621 ENDIF !(iflag_con.EQ.3) 1622 IF (iflag_con .EQ.3.OR.iflag_con.EQ.30) THEN1622 IF (iflag_con==3.OR.iflag_con==30) THEN 1623 1623 ! sortie RomP convection descente insaturee iflag_con=30 1624 1624 ! etendue a iflag_con=3 (jyg) … … 1651 1651 IF (type_ocean=='slab ') THEN 1652 1652 CALL histwrite_phy(o_slab_bils, slab_wfbils) 1653 IF (nslay .EQ.1) THEN1653 IF (nslay==1) THEN 1654 1654 IF (vars_defined) zx_tmp_fi2d(:)=tslab(:,1) 1655 1655 CALL histwrite_phy(o_tslab, zx_tmp_fi2d) … … 1669 1669 ENDIF 1670 1670 IF (slab_hdiff) THEN 1671 IF (nslay .EQ.1) THEN1671 IF (nslay==1) THEN 1672 1672 IF (vars_defined) zx_tmp_fi2d(:)=dt_hdiff(:,1) 1673 1673 CALL histwrite_phy(o_slab_hdiff, zx_tmp_fi2d) … … 1676 1676 ENDIF 1677 1677 ENDIF 1678 IF (slab_ekman .GT.0) THEN1679 IF (nslay .EQ.1) THEN1678 IF (slab_ekman>0) THEN 1679 IF (nslay==1) THEN 1680 1680 IF (vars_defined) zx_tmp_fi2d(:)=dt_ekman(:,1) 1681 1681 CALL histwrite_phy(o_slab_ekman, zx_tmp_fi2d) … … 1702 1702 IF (vars_defined) THEN 1703 1703 DO i=1, klon 1704 IF (zt2m(i) .LE.273.15) then1704 IF (zt2m(i)<=273.15) then 1705 1705 zx_tmp_fi2d(i)=MAX(0.,rh2m(i)*100.) 1706 1706 ELSE … … 1744 1744 !This is warranted by treating INCA aerosols as offline aerosols 1745 1745 #ifndef CPP_ECRAD 1746 IF (flag_aerosol .GT.0) THEN1746 IF (flag_aerosol>0) THEN 1747 1747 IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN 1748 1748 … … 1777 1777 ENDIF 1778 1778 !--STRAT AER 1779 IF (flag_aerosol .GT.0.OR.flag_aerosol_strat.GT.0) THEN1779 IF (flag_aerosol>0.OR.flag_aerosol_strat>0) THEN 1780 1780 DO naero = 1, naero_tot 1781 1781 CALL histwrite_phy(o_tausumaero(naero),tausum_aero(:,2,naero)) 1782 1782 ENDDO 1783 1783 ENDIF 1784 IF (flag_aerosol_strat .GT.0) THEN1784 IF (flag_aerosol_strat>0) THEN 1785 1785 CALL histwrite_phy(o_tausumaero_lw,tausum_aero(:,6,id_STRAT_phy)) 1786 1786 ENDIF … … 1933 1933 CALL histwrite_phy(o_sollwai, zx_tmp_fi2d) 1934 1934 ENDIF 1935 IF (flag_aerosol .GT.0.AND.ok_cdnc) THEN1935 IF (flag_aerosol>0.AND.ok_cdnc) THEN 1936 1936 CALL histwrite_phy(o_scdnc, scdnc) 1937 1937 CALL histwrite_phy(o_cldncl, cldncl) … … 2002 2002 #endif 2003 2003 2004 IF (flag_aerosol_strat .EQ.2) THEN2004 IF (flag_aerosol_strat==2) THEN 2005 2005 CALL histwrite_phy(o_stratomask, stratomask) 2006 2006 ENDIF … … 2030 2030 CALL histwrite_phy(o_rnebjn, zx_tmp_fi3d) 2031 2031 CALL histwrite_phy(o_rhum, zx_rh) 2032 IF (iflag_ice_thermo .GT.0) THEN2032 IF (iflag_ice_thermo > 0) THEN 2033 2033 IF (vars_defined) zx_tmp_fi3d = zx_rhl * 100. 2034 2034 CALL histwrite_phy(o_rhl, zx_tmp_fi3d) … … 2111 2111 CALL histwrite_phy(o_dqlphy2d, zx_tmp_fi2d) 2112 2112 2113 IF (nqo .EQ.3) THEN2113 IF (nqo==3) THEN 2114 2114 CALL histwrite_phy(o_dqsphy, d_qx(:,:,isol)) 2115 2115 IF (vars_defined) CALL water_int(klon,klev,d_qx(:,:,isol),zmasse,zx_tmp_fi2d) … … 2195 2195 ENDIF 2196 2196 CALL histwrite_phy(o_dtcon, zx_tmp_fi3d) 2197 IF (iflag_thermals .EQ.0) THEN2197 IF (iflag_thermals==0) THEN 2198 2198 IF (vars_defined) THEN 2199 2199 zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + & … … 2201 2201 ENDIF 2202 2202 CALL histwrite_phy(o_tntc, zx_tmp_fi3d) 2203 ELSE IF(iflag_thermals .GE.1.AND.iflag_wake.EQ.1) THEN2203 ELSE IF(iflag_thermals>=1.AND.iflag_wake==1) THEN 2204 2204 IF (vars_defined) THEN 2205 2205 zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + & … … 2218 2218 CALL histwrite_phy(o_dqcon2d, zx_tmp_fi2d) 2219 2219 2220 IF (iflag_thermals .EQ.0) THEN2220 IF (iflag_thermals==0) THEN 2221 2221 IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys 2222 2222 CALL histwrite_phy(o_tnhusc, zx_tmp_fi3d) 2223 ELSE IF (iflag_thermals .GE.1.AND.iflag_wake.EQ.1) THEN2223 ELSE IF (iflag_thermals>=1.AND.iflag_wake==1) THEN 2224 2224 IF (vars_defined) THEN 2225 2225 zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys + & … … 2694 2694 DO k=1, nlevSTD 2695 2695 DO i=1, klon 2696 IF (O3STD(i,k) .NE.missing_val) THEN2696 IF (O3STD(i,k)/=missing_val) THEN 2697 2697 zx_tmp_fi3d_STD(i,k) = O3STD(i,k) * 1.e+9 2698 2698 ELSE … … 2707 2707 DO k=1, nlevSTD 2708 2708 DO i=1, klon 2709 IF (O3daySTD(i,k) .NE.missing_val) THEN2709 IF (O3daySTD(i,k)/=missing_val) THEN 2710 2710 zx_tmp_fi3d_STD(i,k) = O3daySTD(i,k) * 1.e+9 2711 2711 ELSE -
LMDZ6/trunk/libf/phylmd/phys_state_var_mod.F90
r4984 r5075 10 10 ! Declaration des variables 11 11 USE dimphy 12 USE netcdf, only: nf90_fill_real12 USE lmdz_netcdf, only: nf90_fill_real 13 13 INTEGER, PARAMETER :: nlevSTD=17 14 14 INTEGER, PARAMETER :: nlevSTD8=8 -
LMDZ6/trunk/libf/phylmd/physiq_mod.F90
r5066 r5075 48 48 USE mod_phys_lmdz_para 49 49 USE netcdf95, only: nf95_close 50 USE netcdf, only: nf90_fill_real ! IM for NMC files50 USE lmdz_netcdf, only: nf90_fill_real ! IM for NMC files 51 51 USE open_climoz_m, only: open_climoz ! ozone climatology from a file 52 52 USE ozonecm_m, only: ozonecm ! ozone of J.-F. Royer -
LMDZ6/trunk/libf/phylmd/plevel.F90
r4619 r5075 7 7 ! ================================================================ 8 8 ! ================================================================ 9 USE netcdf9 USE lmdz_netcdf, ONLY: nf90_fill_real 10 10 USE dimphy 11 11 #ifdef CPP_IOIPSL -
LMDZ6/trunk/libf/phylmd/plevel_new.F90
r4619 r5075 8 8 ! ================================================================ 9 9 ! ================================================================ 10 USE netcdf11 10 USE dimphy 12 11 #ifdef CPP_IOIPSL -
LMDZ6/trunk/libf/phylmd/press_coefoz_m.F90
r4489 r5075 24 24 25 25 use netcdf95, only: nf95_open, nf95_close, nf95_gw_var, nf95_inq_varid 26 use netcdf, only: nf90_nowrite26 use lmdz_netcdf, only: nf90_nowrite 27 27 28 28 use mod_phys_lmdz_mpi_data, only: is_mpi_root -
LMDZ6/trunk/libf/phylmd/read_map2D.F90
r2311 r5075 3 3 ! Return variable for the given timestep. 4 4 USE dimphy 5 USE netcdf5 USE lmdz_netcdf, ONLY: nf90_open,nf90_close,nf90_nowrite,nf90_noerr,nf90_get_var,nf90_inq_varid 6 6 USE mod_grid_phy_lmdz 7 7 USE mod_phys_lmdz_para -
LMDZ6/trunk/libf/phylmd/read_pstoke.F90
r4262 r5075 17 17 ! ****************************************************************************** 18 18 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 20 21 USE dimphy 21 22 USE indice_sol_mod … … 23 24 24 25 IMPLICIT NONE 25 26 include "netcdf.inc"27 26 28 27 INTEGER klono, klevo, imo, jmo -
LMDZ6/trunk/libf/phylmd/read_pstoke0.F90
r5073 r5075 16 16 ! ****************************************************************************** 17 17 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 19 20 USE dimphy 20 21 USE indice_sol_mod … … 22 23 23 24 IMPLICIT NONE 24 25 include "netcdf.inc"26 25 27 26 INTEGER kon, kev, zkon, zkev … … 253 252 ! niveaux de pression 254 253 255 status = nf _get_vara_real(ncidp, varidpl, 1, kev, pl)254 status = nf90_get_var(ncidp, varidpl, pl, [1], [kev]) 256 255 257 256 ! lecture de aire et phis -
LMDZ6/trunk/libf/phylmd/readaerosol_mod.F90
r4627 r5075 2 2 ! 3 3 MODULE 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 4 7 5 8 REAL, SAVE :: not_valid=-333. … … 86 89 ! Read data depending on actual year and interpolate if necessary 87 90 !**************************************************************************************** 88 IF (iyr_in .LT.1850) THEN91 IF (iyr_in < 1850) THEN 89 92 cyear='.nat' 90 93 WRITE(lunout,*) 'get_aero 1 iyr_in=', iyr_in,' ',cyear … … 93 96 CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, pt_out, psurf, load) 94 97 95 ELSE IF (iyr_in .GE.2100) THEN98 ELSE IF (iyr_in >= 2100) THEN 96 99 cyear='2100' 97 100 WRITE(lunout,*) 'get_aero 2 iyr_in=', iyr_in,' ',cyear … … 103 106 ! Read data from 2 decades and interpolate to actual year 104 107 ! a) from actual 10-yr-period 105 IF (iyr_in .LT.1900) THEN108 IF (iyr_in<1900) THEN 106 109 iyr1 = 1850 107 110 iyr2 = 1900 108 ELSE IF (iyr_in .GE.1900.AND.iyr_in.LT.1920) THEN111 ELSE IF (iyr_in>=1900.AND.iyr_in<1920) THEN 109 112 iyr1 = 1900 110 113 iyr2 = 1920 … … 174 177 175 178 SUBROUTINE init_aero_fromfile(flag_aerosol, aerosol_couple) 176 USE netcdf177 179 USE mod_phys_lmdz_para 178 180 USE mod_grid_phy_lmdz, ONLY: grid_type, unstructured … … 265 267 !**************************************************************************************** 266 268 267 USE netcdf268 269 USE dimphy 269 270 USE mod_grid_phy_lmdz, ONLY: nbp_lon_=>nbp_lon, nbp_lat_=>nbp_lat, klon_glo, & … … 507 508 !**************************************************************************************** 508 509 DO imth=1, 12 509 IF (imth .EQ.1) THEN510 IF (imth==1) THEN 510 511 cvar=TRIM(varname)//'JAN' 511 ELSE IF (imth .EQ.2) THEN512 ELSE IF (imth==2) THEN 512 513 cvar=TRIM(varname)//'FEB' 513 ELSE IF (imth .EQ.3) THEN514 ELSE IF (imth==3) THEN 514 515 cvar=TRIM(varname)//'MAR' 515 ELSE IF (imth .EQ.4) THEN516 ELSE IF (imth==4) THEN 516 517 cvar=TRIM(varname)//'APR' 517 ELSE IF (imth .EQ.5) THEN518 ELSE IF (imth==5) THEN 518 519 cvar=TRIM(varname)//'MAY' 519 ELSE IF (imth .EQ.6) THEN520 ELSE IF (imth==6) THEN 520 521 cvar=TRIM(varname)//'JUN' 521 ELSE IF (imth .EQ.7) THEN522 ELSE IF (imth==7) THEN 522 523 cvar=TRIM(varname)//'JUL' 523 ELSE IF (imth .EQ.8) THEN524 ELSE IF (imth==8) THEN 524 525 cvar=TRIM(varname)//'AUG' 525 ELSE IF (imth .EQ.9) THEN526 ELSE IF (imth==9) THEN 526 527 cvar=TRIM(varname)//'SEP' 527 ELSE IF (imth .EQ.10) THEN528 ELSE IF (imth==10) THEN 528 529 cvar=TRIM(varname)//'OCT' 529 ELSE IF (imth .EQ.11) THEN530 ELSE IF (imth==11) THEN 530 531 cvar=TRIM(varname)//'NOV' 531 ELSE IF (imth .EQ.12) THEN532 ELSE IF (imth==12) THEN 532 533 cvar=TRIM(varname)//'DEC' 533 534 END IF … … 716 717 717 718 SUBROUTINE check_err(status,text) 718 USE netcdf719 719 USE print_control_mod, ONLY: lunout 720 720 IMPLICIT NONE -
LMDZ6/trunk/libf/phylmd/readaerosolstrato.F90
r4619 r5075 3 3 use netcdf95, only: nf95_close, nf95_gw_var, nf95_inq_dimid, & 4 4 nf95_inq_varid, nf95_open 5 use netcdf, only: nf90_get_var, nf90_noerr, nf90_nowrite5 use lmdz_netcdf, only: nf90_get_var, nf90_noerr, nf90_nowrite 6 6 7 7 USE phys_cal_mod, ONLY : mth_cur … … 68 68 69 69 !--only read file if beginning of run or start of new month 70 IF (debut.OR.mth_cur .NE.mth_pre) THEN70 IF (debut.OR.mth_cur/=mth_pre) THEN 71 71 72 72 !--only root reads 73 73 IF (is_mpi_root.AND.is_omp_root) THEN 74 74 75 IF (nbands .NE.2) THEN75 IF (nbands/=2) THEN 76 76 abort_message='nbands doit etre egal a 2 dans readaerosolstrat' 77 77 CALL abort_physic(modname,abort_message,1) … … 83 83 CALL nf95_gw_var(ncid_in, varid, lev) 84 84 n_lev = size(lev) 85 IF (n_lev .NE.klev) THEN85 IF (n_lev/=klev) THEN 86 86 abort_message='Le nombre de niveaux n est pas egal a klev' 87 87 CALL abort_physic(modname,abort_message,1) … … 93 93 WRITE(lunout,*) 'LAT aerosol strato=', n_lat, latitude 94 94 IF (grid_type/=unstructured) THEN 95 IF (n_lat .NE.nbp_lat) THEN95 IF (n_lat/=nbp_lat) THEN 96 96 abort_message='Le nombre de lat n est pas egal a nbp_lat' 97 97 CALL abort_physic(modname,abort_message,1) … … 104 104 IF (grid_type/=unstructured) THEN 105 105 WRITE(lunout,*) 'LON aerosol strato=', n_lon, longitude 106 IF (n_lon .NE.nbp_lon) THEN106 IF (n_lon/=nbp_lon) THEN 107 107 abort_message='Le nombre de lon n est pas egal a nbp_lon' 108 108 CALL abort_physic(modname,abort_message,1) … … 114 114 n_month = size(time) 115 115 WRITE(lunout,*) 'TIME aerosol strato=', n_month, time 116 IF (n_month .NE.12) THEN116 IF (n_month/=12) THEN 117 117 abort_message='Le nombre de month n est pas egal a 12' 118 118 CALL abort_physic(modname,abort_message,1) … … 131 131 132 132 !---select the correct month 133 IF (mth_cur .LT.1.OR.mth_cur.GT.12) THEN133 IF (mth_cur<1.OR.mth_cur>12) THEN 134 134 WRITE(lunout,*) 'probleme avec le mois dans readaerosolstrat =', mth_cur 135 135 ENDIF -
LMDZ6/trunk/libf/phylmd/readaerosolstrato_m.F90
r4619 r5075 24 24 25 25 SUBROUTINE init_readaerosolstrato1 26 USE netcdf27 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, & 28 28 nf95_inq_varid, nf95_open 29 29 USE mod_phys_lmdz_para … … 67 67 68 68 SUBROUTINE init_readaerosolstrato2 69 USE netcdf70 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, & 71 71 nf95_inq_varid, nf95_open 72 72 USE mod_phys_lmdz_para -
LMDZ6/trunk/libf/phylmd/readchlorophyll.F90
r4489 r5075 8 8 9 9 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_nowrite10 USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite 11 11 USE phys_cal_mod, ONLY: mth_cur 12 12 USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, grid2dto1d_glo … … 50 50 51 51 !--only read file if beginning of run or start of new month 52 IF (debut.OR.mth_cur .NE.mth_pre) THEN52 IF (debut.OR.mth_cur/=mth_pre) THEN 53 53 54 54 IF (is_mpi_root.AND.is_omp_root) THEN … … 59 59 CALL nf95_gw_var(ncid_in, varid, longitude) 60 60 n_lon = size(longitude) 61 IF (n_lon .NE.nbp_lon) THEN61 IF (n_lon/=nbp_lon) THEN 62 62 abort_message='Le nombre de lon n est pas egal a nbp_lon' 63 63 CALL abort_physic(modname,abort_message,1) … … 67 67 CALL nf95_gw_var(ncid_in, varid, latitude) 68 68 n_lat = size(latitude) 69 IF (n_lat .NE.nbp_lat) THEN69 IF (n_lat/=nbp_lat) THEN 70 70 abort_message='Le nombre de lat n est pas egal a jnbp_lat' 71 71 CALL abort_physic(modname,abort_message,1) … … 75 75 CALL nf95_gw_var(ncid_in, varid, time) 76 76 n_month = size(time) 77 IF (n_month .NE.12) THEN77 IF (n_month/=12) THEN 78 78 abort_message='Le nombre de month n est pas egal a 12' 79 79 CALL abort_physic(modname,abort_message,1) … … 92 92 93 93 !---select the correct month 94 IF (mth_cur .LT.1.OR.mth_cur.GT.12) THEN94 IF (mth_cur<1.OR.mth_cur>12) THEN 95 95 WRITE(lunout,*)'probleme avec le mois dans readchlorophyll =', mth_cur 96 96 ENDIF … … 104 104 ! if(isnan(chlorocon_mois_glo(i)))then ! isnan() is not in the Fortran standard... 105 105 ! 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. 107 107 ENDDO 108 108 -
LMDZ6/trunk/libf/phylmd/regr_horiz_time_climoz_m.F90
r4847 r5075 4 4 USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, grid_type, unstructured 5 5 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, & 7 7 NF90_NOWRITE, NF90_NOERR, NF90_GET_ATT, NF90_GLOBAL 8 8 USE netcdf95, ONLY: NF95_DEF_DIM, NF95_INQ_DIMID, NF95_INQUIRE_DIMENSION, & … … 702 702 ! 703 703 !------------------------------------------------------------------------------- 704 USE netcdf, ONLY: NF90_NOERR, NF90_strerror704 USE lmdz_netcdf, ONLY: NF90_NOERR, NF90_strerror 705 705 !------------------------------------------------------------------------------- 706 706 ! Arguments: -
LMDZ6/trunk/libf/phylmd/regr_lat_time_coefoz_m.F90
r4489 r5075 45 45 use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, nf95_get_var, & 46 46 nf95_put_var, nf95_gw_var 47 use netcdf, only: nf90_nowrite47 use lmdz_netcdf, only: nf90_nowrite 48 48 use nrtype, only: pi 49 49 use regular_lonlat_mod, only: boundslat_reg, south … … 245 245 use netcdf95, only: nf95_create, nf95_def_dim, nf95_def_var, & 246 246 nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var 247 use netcdf, only: nf90_clobber, nf90_float, nf90_copy_att, nf90_global247 use lmdz_netcdf, only: nf90_clobber, nf90_float, nf90_copy_att, nf90_global 248 248 use nrtype, only: pi 249 249 use regular_lonlat_mod, only : lat_reg … … 328 328 subroutine handle_err_copy_att(att_name) 329 329 330 use netcdf, only: nf90_noerr, nf90_strerror330 use lmdz_netcdf, only: nf90_noerr, nf90_strerror 331 331 332 332 character(len=*), intent(in):: att_name -
LMDZ6/trunk/libf/phylmd/regr_pr_comb_coefoz_m.F90
r3086 r5075 72 72 73 73 use netcdf95, only: nf95_open, nf95_close 74 use netcdf, only: nf90_nowrite74 use lmdz_netcdf, only: nf90_nowrite 75 75 use assert_m, only: assert 76 76 use dimphy, only: klon -
LMDZ6/trunk/libf/phylmd/regr_pr_o3_m.F90
r4489 r5075 26 26 27 27 use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, nf95_get_var 28 use netcdf, only: nf90_nowrite28 use lmdz_netcdf, only: nf90_nowrite 29 29 use assert_m, only: assert 30 30 use regr_conserv_m, only: regr_conserv -
LMDZ6/trunk/libf/phylmd/regr_pr_time_av_m.F90
r4489 r5075 115 115 USE netcdf95, ONLY: NF95_INQ_VARID, NF95_INQUIRE_VARIABLE, & 116 116 NF95_INQ_DIMID, NF95_INQUIRE_DIMENSION, nf95_get_var 117 USE netcdf, ONLY: NF90_INQ_VARID, NF90_NOERR117 USE lmdz_netcdf, ONLY: NF90_INQ_VARID, NF90_NOERR 118 118 USE assert_m, ONLY: assert 119 119 USE assert_eq_m, ONLY: assert_eq -
LMDZ6/trunk/libf/phylmd/rrtm/read_rsun_rrtm.F90
r4489 r5075 8 8 9 9 USE netcdf95, ONLY: nf95_close, nf95_inq_varid, nf95_open, nf95_gw_var 10 USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite10 USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite 11 11 12 12 USE phys_cal_mod, ONLY : days_elapsed, year_len -
LMDZ6/trunk/libf/phylmd/rrtm/readaerosolstrato1_rrtm.F90
r4619 r5075 7 7 USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, & 8 8 nf95_inq_varid, nf95_open 9 USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite9 USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite 10 10 11 11 USE phys_cal_mod, ONLY : mth_cur -
LMDZ6/trunk/libf/phylmd/rrtm/readaerosolstrato2_rrtm.F90
r4619 r5075 6 6 USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, & 7 7 nf95_inq_varid, nf95_open 8 USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite8 USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite 9 9 10 10 USE phys_cal_mod, ONLY : mth_cur -
LMDZ6/trunk/libf/phylmd/tracco2i_mod.F90
r4489 r5075 104 104 105 105 ! Initialization of tr_seri(id_CO2) If it is not initialized 106 IF (MAXVAL(tr_seri(:,:,id_CO2)) .LT.1.e-15) THEN106 IF (MAXVAL(tr_seri(:,:,id_CO2))<1.e-15) THEN 107 107 tr_seri(:,:,id_CO2)=co2_ppm0*1.e-6/RMD*RMCO2 !--initialised from co2_ppm0 in rdem 108 108 ENDIF … … 299 299 !--for every timestep comment out the IF ENDIF statements 300 300 !--otherwise this is updated every day 301 IF (debutphy.OR.day_cur .NE.day_pre) THEN301 IF (debutphy.OR.day_cur/=day_pre) THEN 302 302 303 303 CALL gather(tr_seri(:,:,id_CO2),co2_glo) … … 351 351 352 352 USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_varid, nf95_open 353 USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite353 USE lmdz_netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite 354 354 355 355 USE carbon_cycle_mod, ONLY : fco2_ff, fco2_bb, fco2_land, fco2_ocean … … 401 401 CALL nf95_gw_var(ncid_in, varid, vector) 402 402 n_glo = size(vector) 403 IF (n_glo .NE.klon_glo) THEN403 IF (n_glo/=klon_glo) THEN 404 404 abort_message='sflx_lmdz_co2_ff: le nombre de points n est pas egal a klon_glo' 405 405 CALL abort_physic(modname,abort_message,1) … … 409 409 CALL nf95_gw_var(ncid_in, varid, time) 410 410 n_month = size(time) 411 IF (n_month .NE.12) THEN411 IF (n_month/=12) THEN 412 412 abort_message='sflx_lmdz_co2_ff: le nombre de month n est pas egal a 12' 413 413 CALL abort_physic(modname,abort_message,1) … … 434 434 CALL nf95_gw_var(ncid_in, varid, vector) 435 435 n_glo = size(vector) 436 IF (n_glo .NE.klon_glo) THEN436 IF (n_glo/=klon_glo) THEN 437 437 abort_message='sflx_lmdz_co2_bb: le nombre de points n est pas egal a klon_glo' 438 438 CALL abort_physic(modname,abort_message,1) … … 442 442 CALL nf95_gw_var(ncid_in, varid, time) 443 443 n_month = size(time) 444 IF (n_month .NE.12) THEN444 IF (n_month/=12) THEN 445 445 abort_message='sflx_lmdz_co2_bb: le nombre de month n est pas egal a 12' 446 446 CALL abort_physic(modname,abort_message,1) … … 474 474 475 475 !---select the correct month 476 IF (mth_cur .LT.1.OR.mth_cur.GT.12) THEN476 IF (mth_cur<1.OR.mth_cur>12) THEN 477 477 PRINT *,'probleme avec le mois dans co2_ini =', mth_cur 478 478 ENDIF -
LMDZ6/trunk/libf/phylmd/undefSTD.F90
r4619 r5075 3 3 4 4 SUBROUTINE undefstd(itap, read_climoz) 5 USE netcdf5 USE lmdz_netcdf, ONLY: nf90_fill_real 6 6 USE dimphy 7 7 #ifdef CPP_IOIPSL -
LMDZ6/trunk/libf/phylmdiso/isotopes_routines_mod.F90
r4982 r5075 15871 15871 USE isotopes_verif_mod 15872 15872 #endif 15873 15874 15873 implicit none 15875 15874 15876 15875 ! equivalent de phyetat0 pour les isotopes 15877 15876 15878 #include "netcdf.inc"15879 15877 #include "dimsoil.h" 15880 15878 #include "clesphys.h" … … 16429 16427 IMPLICIT NONE 16430 16428 16431 #include "netcdf.inc"16432 16429 #include "dimsoil.h" 16433 16430 #include "clesphys.h" -
LMDZ6/trunk/libf/phylmdiso/limit_read_mod.F90
r4619 r5075 274 274 USE mod_phys_lmdz_para 275 275 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 277 278 USE indice_sol_mod 278 279 #ifdef ISO -
LMDZ6/trunk/libf/phylmdiso/phyaqua_mod.F90
r5073 r5075 147 147 !END IF 148 148 149 if (year_len .ne.360) then149 if (year_len/=360) then 150 150 write (*,*) year_len 151 151 write (*,*) 'iniaqua: 360 day calendar is required !' … … 960 960 END IF 961 961 962 if (type_profil .EQ.20) then962 if (type_profil==20) then 963 963 print*,'Profile SST 20' 964 964 ! Méthode 13 "Qmax2K" plateau réel �| l'Equateur augmenté +2K … … 969 969 endif 970 970 971 if (type_profil .EQ.21) then971 if (type_profil==21) then 972 972 print*,'Profile SST 21' 973 973 ! Méthode 13 "Qmax2K" plateau réel �| l'Equateur augmenté +2K -
LMDZ6/trunk/libf/phylmdiso/phyetat0_mod.F90
r4982 r5075 48 48 USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy 49 49 USE wxios, ONLY: missing_val_xios => missing_val, using_xios 50 use netcdf, only: missing_val_netcdf => nf90_fill_real50 use lmdz_netcdf, only: missing_val_netcdf => nf90_fill_real 51 51 use config_ocean_skin_m, only: activate_ocean_skin 52 52 #ifdef ISO -
LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90
r5066 r5075 48 48 USE mod_phys_lmdz_para 49 49 USE netcdf95, only: nf95_close 50 USE netcdf, only: nf90_fill_real ! IM for NMC files50 USE lmdz_netcdf, only: nf90_fill_real ! IM for NMC files 51 51 USE open_climoz_m, only: open_climoz ! ozone climatology from a file 52 52 USE ozonecm_m, only: ozonecm ! ozone of J.-F. Royer -
LMDZ6/trunk/tools/make_sso/make_sso_SpherePack.f90
r4168 r5075 6 6 ! Purpose: Project ETOPO file (GMT4 axes conventions) on spherical harmonics. 7 7 !------------------------------------------------------------------------------- 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 9 11 ! USE sphpack 10 12 IMPLICIT NONE -
LMDZ6/trunk/tools/netcdf95/Attributes/nf95_copy_att.f90
r4918 r5075 8 8 subroutine nf95_copy_att(ncid_in, varid_in, name, ncid_out, varid_out, ncerr) 9 9 10 use netcdf, only: nf90_copy_att10 use lmdz_netcdf, only: nf90_copy_att 11 11 12 12 use nf95_abort_m, only: nf95_abort -
LMDZ6/trunk/tools/netcdf95/Attributes/nf95_get_att.f90
r4918 r5075 2 2 3 3 use nf95_abort_m, only: nf95_abort 4 use netcdf, only: nf90_get_att, nf90_noerr4 use lmdz_netcdf, only: nf90_get_att, nf90_noerr 5 5 use nf95_inquire_attribute_m, only: nf95_inquire_attribute 6 6 use nf95_constants, only: nf95_noerr -
LMDZ6/trunk/tools/netcdf95/Attributes/nf95_get_missing.F90
r4918 r5075 1 1 module nf95_get_missing_m 2 2 3 use netcdf, only: nf90_noerr3 use lmdz_netcdf, only: nf90_noerr 4 4 use nf95_get_att_m, only: nf95_get_att 5 5 … … 18 18 subroutine nf95_get_missing_real(ncid, varid, missing) 19 19 20 use netcdf, only: NF90_FILL_REAL20 use lmdz_netcdf, only: NF90_FILL_REAL 21 21 use typesizes, only: FourByteReal 22 22 … … 44 44 subroutine nf95_get_missing_dble(ncid, varid, missing) 45 45 46 use netcdf, only: NF90_FILL_double46 use lmdz_netcdf, only: NF90_FILL_double 47 47 use typesizes, only: EightByteReal 48 48 … … 70 70 subroutine nf95_get_missing_short_int(ncid, varid, missing) 71 71 72 use netcdf, only: NF90_FILL_short72 use lmdz_netcdf, only: NF90_FILL_short 73 73 use typesizes, only: TwoByteInt 74 74 … … 96 96 subroutine nf95_get_missing_int(ncid, varid, missing) 97 97 98 use netcdf, only: NF90_FILL_INT98 use lmdz_netcdf, only: NF90_FILL_INT 99 99 100 100 integer, intent(in):: ncid, varid … … 121 121 subroutine nf95_get_missing_char(ncid, varid, missing) 122 122 123 use netcdf, only: NF90_FILL_char123 use lmdz_netcdf, only: NF90_FILL_char 124 124 125 125 integer, intent(in):: ncid, varid -
LMDZ6/trunk/tools/netcdf95/Attributes/nf95_inquire_attribute.f90
r4918 r5075 10 10 11 11 use nf95_abort_m, only: nf95_abort 12 use netcdf, only: nf90_inquire_attribute12 use lmdz_netcdf, only: nf90_inquire_attribute 13 13 use nf95_constants, only: nf95_noerr 14 14 -
LMDZ6/trunk/tools/netcdf95/Attributes/nf95_put_att.f90
r4918 r5075 1 1 module nf95_put_att_m 2 2 3 use netcdf, only: nf90_put_att3 use lmdz_netcdf, only: nf90_put_att 4 4 use nf95_abort_m, only: nf95_abort 5 5 use nf95_constants, only: nf95_noerr -
LMDZ6/trunk/tools/netcdf95/Datasets/nf95_close.f90
r4918 r5075 10 10 ! call it. 11 11 12 use netcdf, only: nf90_close, nf90_strerror12 use lmdz_netcdf, only: nf90_close, nf90_strerror 13 13 14 14 use nf95_constants, only: nf95_noerr -
LMDZ6/trunk/tools/netcdf95/Datasets/nf95_create.f90
r4918 r5075 8 8 9 9 use nf95_abort_m, only: nf95_abort 10 use netcdf, only: nf90_create10 use lmdz_netcdf, only: nf90_create 11 11 use nf95_constants, only: nf95_noerr 12 12 -
LMDZ6/trunk/tools/netcdf95/Datasets/nf95_create_single.f90
r4918 r5075 1 1 module nf95_create_single_m 2 2 3 use netcdf, only: NF90_MAX_NAME3 use lmdz_netcdf, only: NF90_MAX_NAME 4 4 5 5 implicit none … … 19 19 ! Shortcut to create a file containing a single primary variable. 20 20 21 use netcdf, only: NF90_CLOBBER, NF90_FLOAT21 use lmdz_netcdf, only: NF90_CLOBBER, NF90_FLOAT 22 22 23 23 use nf95_create_m, only: nf95_create -
LMDZ6/trunk/tools/netcdf95/Datasets/nf95_enddef.f90
r4918 r5075 8 8 9 9 use nf95_abort_m, only: nf95_abort 10 use netcdf, only: nf90_enddef10 use lmdz_netcdf, only: nf90_enddef 11 11 use nf95_constants, only: nf95_noerr 12 12 -
LMDZ6/trunk/tools/netcdf95/Datasets/nf95_find_coord.f90
r4918 r5075 15 15 ! attribute "std_name". 16 16 17 use netcdf, only: NF90_MAX_NAME, NF90_NOERR17 use lmdz_netcdf, only: NF90_MAX_NAME, NF90_NOERR 18 18 use nf95_get_att_m, only: nf95_get_att 19 19 use nf95_inq_varid_m, only: nf95_inq_varid -
LMDZ6/trunk/tools/netcdf95/Datasets/nf95_inquire.f90
r4918 r5075 10 10 11 11 use nf95_abort_m, only: nf95_abort 12 use netcdf, only: nf90_inquire12 use lmdz_netcdf, only: nf90_inquire 13 13 use nf95_constants, only: nf95_noerr 14 14 -
LMDZ6/trunk/tools/netcdf95/Datasets/nf95_open.f90
r4918 r5075 8 8 9 9 use nf95_abort_m, only: nf95_abort 10 use netcdf, only: nf90_open10 use lmdz_netcdf, only: nf90_open 11 11 use nf95_constants, only: nf95_noerr 12 12 -
LMDZ6/trunk/tools/netcdf95/Datasets/nf95_redef.f90
r4918 r5075 8 8 9 9 use nf95_abort_m, only: nf95_abort 10 use netcdf, only: nf90_redef10 use lmdz_netcdf, only: nf90_redef 11 11 use nf95_constants, only: nf95_noerr 12 12 -
LMDZ6/trunk/tools/netcdf95/Datasets/nf95_sync.f90
r4918 r5075 8 8 9 9 use nf95_abort_m, only: nf95_abort 10 use netcdf, only: nf90_sync10 use lmdz_netcdf, only: nf90_sync 11 11 use nf95_constants, only: nf95_noerr 12 12 -
LMDZ6/trunk/tools/netcdf95/Groups/nf95_inq_file_ncid.f90
r4918 r5075 11 11 ! by nf95_abort, so it cannot call it. 12 12 13 use netcdf, only: nf90_strerror13 use lmdz_netcdf, only: nf90_strerror 14 14 15 15 use nf95_constants, only: Nf95_ENOGRP, nf95_noerr -
LMDZ6/trunk/tools/netcdf95/Groups/nf95_inq_grp_parent.f90
r4918 r5075 12 12 use, intrinsic:: ISO_C_BINDING 13 13 14 use netcdf, only: nf90_strerror14 use lmdz_netcdf, only: nf90_strerror 15 15 16 16 use nc_constants, only: NC_NOERR -
LMDZ6/trunk/tools/netcdf95/Groups/nf95_inq_grps.f90
r4918 r5075 26 26 use, intrinsic:: ISO_C_BINDING 27 27 28 use netcdf, only: nf90_noerr28 use lmdz_netcdf, only: nf90_noerr 29 29 30 30 use nc_constants, only: nc_noerr -
LMDZ6/trunk/tools/netcdf95/Variables/check_start_count.f90
r4918 r5075 19 19 use nf95_close_m, only: nf95_close 20 20 use nf95_inquire_variable_m, only: nf95_inquire_variable 21 use netcdf, only: nf90_noerr21 use lmdz_netcdf, only: nf90_noerr 22 22 23 23 character(len=*), intent(in):: name_calling ! name of calling procedure -
LMDZ6/trunk/tools/netcdf95/Variables/nf95_def_var.f90
r4918 r5075 7 7 ! "nf95_def_var_scalar" cannot be distinguished from "nf95_def_var_oneDim". 8 8 9 use netcdf, only: nf90_def_var9 use lmdz_netcdf, only: nf90_def_var 10 10 use nf95_abort_m, only: nf95_abort 11 11 use nf95_constants, only: nf95_noerr -
LMDZ6/trunk/tools/netcdf95/Variables/nf95_get_var.f90
r4918 r5075 1 1 module nf95_get_var_m 2 2 3 use netcdf, only: nf90_get_var, NF90_NOERR3 use lmdz_netcdf, only: nf90_get_var, NF90_NOERR 4 4 5 5 use nf95_abort_m, only: nf95_abort -
LMDZ6/trunk/tools/netcdf95/Variables/nf95_inq_varid.f90
r4918 r5075 8 8 9 9 use nf95_abort_m, only: nf95_abort 10 use netcdf, only: nf90_inq_varid10 use lmdz_netcdf, only: nf90_inq_varid 11 11 use nf95_constants, only: nf95_noerr 12 12 -
LMDZ6/trunk/tools/netcdf95/Variables/nf95_inquire_variable.f90
r4918 r5075 16 16 17 17 use nf95_abort_m, only: nf95_abort 18 use netcdf, only: nf90_inquire_variable, nf90_max_var_dims18 use lmdz_netcdf, only: nf90_inquire_variable, nf90_max_var_dims 19 19 use nf95_constants, only: nf95_noerr 20 20 -
LMDZ6/trunk/tools/netcdf95/Variables/nf95_put_var.f90
r4918 r5075 1 1 module nf95_put_var_m 2 2 3 use netcdf, only: nf90_put_var3 use lmdz_netcdf, only: nf90_put_var 4 4 use nf95_abort_m, only: nf95_abort 5 5 use check_start_count_m, only: check_start_count -
LMDZ6/trunk/tools/netcdf95/nf95_abort.f90
r4918 r5075 10 10 11 11 ! Libraries: 12 use netcdf, only: nf90_strerror12 use lmdz_netcdf, only: nf90_strerror 13 13 14 14 use nf95_close_m, only: nf95_close -
LMDZ6/trunk/tools/netcdf95/nf95_def_dim.f90
r4918 r5075 8 8 9 9 use nf95_abort_m, only: nf95_abort 10 use netcdf, only: nf90_def_dim10 use lmdz_netcdf, only: nf90_def_dim 11 11 use nf95_constants, only: nf95_noerr 12 12 -
LMDZ6/trunk/tools/netcdf95/nf95_inq_dimid.f90
r4918 r5075 8 8 9 9 use nf95_abort_m, only: nf95_abort 10 use netcdf, only: nf90_inq_dimid10 use lmdz_netcdf, only: nf90_inq_dimid 11 11 use nf95_constants, only: nf95_noerr 12 12 -
LMDZ6/trunk/tools/netcdf95/nf95_inquire_dimension.f90
r4918 r5075 8 8 9 9 use nf95_abort_m, only: nf95_abort 10 use netcdf, only: nf90_inquire_dimension10 use lmdz_netcdf, only: nf90_inquire_dimension 11 11 use nf95_constants, only: nf95_noerr 12 12
Note: See TracChangeset
for help on using the changeset viewer.