Ignore:
Timestamp:
Jul 19, 2024, 6:40:44 PM (4 months ago)
Author:
Laurent Fairhead
Message:

Reverting to r4065. Updating fortran standard broke too much stuff. Will do it by smaller chunks
AB, LF

Location:
LMDZ6/trunk/libf/phylmdiso
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmdiso/isotopes_routines_mod.F90

    r5075 r5084  
    1587115871  USE isotopes_verif_mod
    1587215872#endif
     15873
    1587315874       implicit none   
    1587415875
    1587515876      ! equivalent de phyetat0 pour les isotopes 
    1587615877
     15878#include "netcdf.inc"
    1587715879#include "dimsoil.h"
    1587815880#include "clesphys.h"
     
    1642716429   IMPLICIT NONE
    1642816430
     16431#include "netcdf.inc"
    1642916432#include "dimsoil.h"
    1643016433#include "clesphys.h"
  • LMDZ6/trunk/libf/phylmdiso/limit_read_mod.F90

    r5076 r5084  
    274274    USE mod_phys_lmdz_para
    275275    USE surface_data, ONLY : type_ocean, ok_veget
    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,nf90_get_att,nf90_inquire
     276    USE netcdf
    278277    USE indice_sol_mod
    279278#ifdef ISO
  • LMDZ6/trunk/libf/phylmdiso/phyaqua_mod.F90

    r5076 r5084  
    147147    !END IF
    148148   
    149     if (year_len/=360) then
     149    if (year_len.ne.360) then
    150150      write (*,*) year_len
    151151      write (*,*) 'iniaqua: 360 day calendar is required !'
     
    539539    IMPLICIT NONE
    540540
     541    include "netcdf.inc"
     542
    541543    INTEGER, INTENT (IN) :: klon
    542544    REAL, INTENT (IN) :: phy_nat(klon, 360)
     
    591593    USE mod_phys_lmdz_transfert_para, ONLY: gather
    592594    USE phys_cal_mod, ONLY: year_len
    593     USE lmdz_netcdf, ONLY:nf_clobber,nf_close,nf_noerr,nf_strerror,nf_put_att_text,nf_def_var,&
    594             nf_def_dim,nf_create,nf90_put_var,nf_unlimited,nf_global,nf_64bit_offset,nf90_format,&
    595             nf_enddef
    596595    IMPLICIT NONE
     596    include "netcdf.inc"
    597597
    598598    INTEGER, INTENT (IN) :: klon
     
    636636      dims(2) = ntim
    637637
    638       ierr = nf_def_var(nid, 'TEMPS', NF90_FORMAT, 1, ntim, id_tim)
     638#ifdef NC_DOUBLE
     639      ierr = nf_def_var(nid, 'TEMPS', nf_double, 1, ntim, id_tim)
     640#else
     641      ierr = nf_def_var(nid, 'TEMPS', nf_float, 1, ntim, id_tim)
     642#endif
    639643      ierr = nf_put_att_text(nid, id_tim, 'title', 17, 'Jour dans l annee')
    640644
    641       ierr = nf_def_var(nid, 'NAT', NF90_FORMAT, 2, dims, id_nat)
     645#ifdef NC_DOUBLE
     646      ierr = nf_def_var(nid, 'NAT', nf_double, 2, dims, id_nat)
     647#else
     648      ierr = nf_def_var(nid, 'NAT', nf_float, 2, dims, id_nat)
     649#endif
    642650      ierr = nf_put_att_text(nid, id_nat, 'title', 23, &
    643651        'Nature du sol (0,1,2,3)')
    644652
    645       ierr = nf_def_var(nid, 'SST', NF90_FORMAT, 2, dims, id_sst)
     653#ifdef NC_DOUBLE
     654      ierr = nf_def_var(nid, 'SST', nf_double, 2, dims, id_sst)
     655#else
     656      ierr = nf_def_var(nid, 'SST', nf_float, 2, dims, id_sst)
     657#endif
    646658      ierr = nf_put_att_text(nid, id_sst, 'title', 35, &
    647659        'Temperature superficielle de la mer')
    648660
    649       ierr = nf_def_var(nid, 'BILS', NF90_FORMAT, 2, dims, id_bils)
     661#ifdef NC_DOUBLE
     662      ierr = nf_def_var(nid, 'BILS', nf_double, 2, dims, id_bils)
     663#else
     664      ierr = nf_def_var(nid, 'BILS', nf_float, 2, dims, id_bils)
     665#endif
    650666      ierr = nf_put_att_text(nid, id_bils, 'title', 32, &
    651667        'Reference flux de chaleur au sol')
    652668
    653       ierr = nf_def_var(nid, 'ALB', NF90_FORMAT, 2, dims, id_alb)
     669#ifdef NC_DOUBLE
     670      ierr = nf_def_var(nid, 'ALB', nf_double, 2, dims, id_alb)
     671#else
     672      ierr = nf_def_var(nid, 'ALB', nf_float, 2, dims, id_alb)
     673#endif
    654674      ierr = nf_put_att_text(nid, id_alb, 'title', 19, 'Albedo a la surface')
    655675
    656       ierr = nf_def_var(nid, 'RUG', NF90_FORMAT, 2, dims, id_rug)
     676#ifdef NC_DOUBLE
     677      ierr = nf_def_var(nid, 'RUG', nf_double, 2, dims, id_rug)
     678#else
     679      ierr = nf_def_var(nid, 'RUG', nf_float, 2, dims, id_rug)
     680#endif
    657681      ierr = nf_put_att_text(nid, id_rug, 'title', 8, 'Rugosite')
    658682
    659       ierr = nf_def_var(nid, 'FTER', NF90_FORMAT, 2, dims, id_fter)
     683#ifdef NC_DOUBLE
     684      ierr = nf_def_var(nid, 'FTER', nf_double, 2, dims, id_fter)
     685#else
     686      ierr = nf_def_var(nid, 'FTER', nf_float, 2, dims, id_fter)
     687#endif
    660688      ierr = nf_put_att_text(nid, id_fter, 'title',10,'Frac. Land')
    661       ierr = nf_def_var(nid, 'FOCE', NF90_FORMAT, 2, dims, id_foce)
     689#ifdef NC_DOUBLE
     690      ierr = nf_def_var(nid, 'FOCE', nf_double, 2, dims, id_foce)
     691#else
     692      ierr = nf_def_var(nid, 'FOCE', nf_float, 2, dims, id_foce)
     693#endif
    662694      ierr = nf_put_att_text(nid, id_foce, 'title',11,'Frac. Ocean')
    663       ierr = nf_def_var(nid, 'FSIC', NF90_FORMAT, 2, dims, id_fsic)
     695#ifdef NC_DOUBLE
     696      ierr = nf_def_var(nid, 'FSIC', nf_double, 2, dims, id_fsic)
     697#else
     698      ierr = nf_def_var(nid, 'FSIC', nf_float, 2, dims, id_fsic)
     699#endif
    664700      ierr = nf_put_att_text(nid, id_fsic, 'title',13,'Frac. Sea Ice')
    665       ierr = nf_def_var(nid, 'FLIC', NF90_FORMAT, 2, dims, id_flic)
     701#ifdef NC_DOUBLE
     702      ierr = nf_def_var(nid, 'FLIC', nf_double, 2, dims, id_flic)
     703#else
     704      ierr = nf_def_var(nid, 'FLIC', nf_float, 2, dims, id_flic)
     705#endif
    666706      ierr = nf_put_att_text(nid, id_flic, 'title',14,'Frac. Land Ice')
    667707
     
    675715      ! write the 'times'
    676716      DO k = 1, year_len
    677         ierr = nf90_put_var(nid, id_tim, k, [k])
     717#ifdef NC_DOUBLE
     718        ierr = nf_put_var1_double(nid, id_tim, k, dble(k))
     719#else
     720        ierr = nf_put_var1_real(nid, id_tim, k, float(k))
     721#endif
    678722        IF (ierr/=nf_noerr) THEN
    679723          WRITE (*, *) 'writelim error with temps(k),k=', k
     
    688732    CALL gather(phy_nat, phy_glo)
    689733    IF (is_master) THEN
    690       ierr = nf90_put_var(nid, id_nat, phy_glo)
     734#ifdef NC_DOUBLE
     735      ierr = nf_put_var_double(nid, id_nat, phy_glo)
     736#else
     737      ierr = nf_put_var_real(nid, id_nat, phy_glo)
     738#endif
    691739      IF (ierr/=nf_noerr) THEN
    692740        WRITE (*, *) 'writelim error with phy_nat'
     
    697745    CALL gather(phy_sst, phy_glo)
    698746    IF (is_master) THEN
    699       ierr = nf90_put_var(nid, id_sst, phy_glo)
     747#ifdef NC_DOUBLE
     748      ierr = nf_put_var_double(nid, id_sst, phy_glo)
     749#else
     750      ierr = nf_put_var_real(nid, id_sst, phy_glo)
     751#endif
    700752      IF (ierr/=nf_noerr) THEN
    701753        WRITE (*, *) 'writelim error with phy_sst'
     
    706758    CALL gather(phy_bil, phy_glo)
    707759    IF (is_master) THEN
    708       ierr = nf90_put_var(nid, id_bils, phy_glo)
     760#ifdef NC_DOUBLE
     761      ierr = nf_put_var_double(nid, id_bils, phy_glo)
     762#else
     763      ierr = nf_put_var_real(nid, id_bils, phy_glo)
     764#endif
    709765      IF (ierr/=nf_noerr) THEN
    710766        WRITE (*, *) 'writelim error with phy_bil'
     
    715771    CALL gather(phy_alb, phy_glo)
    716772    IF (is_master) THEN
    717       ierr = nf90_put_var(nid, id_alb, phy_glo)
     773#ifdef NC_DOUBLE
     774      ierr = nf_put_var_double(nid, id_alb, phy_glo)
     775#else
     776      ierr = nf_put_var_real(nid, id_alb, phy_glo)
     777#endif
    718778      IF (ierr/=nf_noerr) THEN
    719779        WRITE (*, *) 'writelim error with phy_alb'
     
    724784    CALL gather(phy_rug, phy_glo)
    725785    IF (is_master) THEN
    726       ierr = nf90_put_var(nid, id_rug, phy_glo)
     786#ifdef NC_DOUBLE
     787      ierr = nf_put_var_double(nid, id_rug, phy_glo)
     788#else
     789      ierr = nf_put_var_real(nid, id_rug, phy_glo)
     790#endif
    727791      IF (ierr/=nf_noerr) THEN
    728792        WRITE (*, *) 'writelim error with phy_rug'
     
    733797    CALL gather(phy_fter, phy_glo)
    734798    IF (is_master) THEN
    735       ierr = nf90_put_var(nid, id_fter, phy_glo)
     799#ifdef NC_DOUBLE
     800      ierr = nf_put_var_double(nid, id_fter, phy_glo)
     801#else
     802      ierr = nf_put_var_real(nid, id_fter, phy_glo)
     803#endif
    736804      IF (ierr/=nf_noerr) THEN
    737805        WRITE (*, *) 'writelim error with phy_fter'
     
    742810    CALL gather(phy_foce, phy_glo)
    743811    IF (is_master) THEN
    744       ierr = nf90_put_var(nid, id_foce, phy_glo)
     812#ifdef NC_DOUBLE
     813      ierr = nf_put_var_double(nid, id_foce, phy_glo)
     814#else
     815      ierr = nf_put_var_real(nid, id_foce, phy_glo)
     816#endif
    745817      IF (ierr/=nf_noerr) THEN
    746818        WRITE (*, *) 'writelim error with phy_foce'
     
    751823    CALL gather(phy_fsic, phy_glo)
    752824    IF (is_master) THEN
    753       ierr = nf90_put_var(nid, id_fsic, phy_glo)
     825#ifdef NC_DOUBLE
     826      ierr = nf_put_var_double(nid, id_fsic, phy_glo)
     827#else
     828      ierr = nf_put_var_real(nid, id_fsic, phy_glo)
     829#endif
    754830      IF (ierr/=nf_noerr) THEN
    755831        WRITE (*, *) 'writelim error with phy_fsic'
     
    760836    CALL gather(phy_flic, phy_glo)
    761837    IF (is_master) THEN
    762       ierr = nf90_put_var(nid, id_flic, phy_glo)
     838#ifdef NC_DOUBLE
     839      ierr = nf_put_var_double(nid, id_flic, phy_glo)
     840#else
     841      ierr = nf_put_var_real(nid, id_flic, phy_glo)
     842#endif
    763843      IF (ierr/=nf_noerr) THEN
    764844        WRITE (*, *) 'writelim error with phy_flic'
     
    9601040      END IF
    9611041
    962       if (type_profil==20) then
     1042      if (type_profil.EQ.20) then
    9631043      print*,'Profile SST 20'
    9641044!     Méthode 13 "Qmax2K" plateau réel �|  l'Equateur augmenté +2K
     
    9691049      endif
    9701050
    971       if (type_profil==21) then
     1051      if (type_profil.EQ.21) then
    9721052      print*,'Profile SST 21'
    9731053!     Méthode 13 "Qmax2K" plateau réel �|  l'Equateur augmenté +2K
  • LMDZ6/trunk/libf/phylmdiso/phyetat0_mod.F90

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

    r5066 r5084  
    351351!$OMP THREADPRIVATE(d_deltat_vdf, d_deltaq_vdf)
    352352!!!      REAL,ALLOCATABLE,SAVE,DIMENSION(:)          :: d_s_vdf, d_dens_vdf
    353 !!!$OMP THREADPRIVATE(d_s_vdf, d_dens_vdf)
     353!!!OMP THREADPRIVATE(d_s_vdf, d_dens_vdf)
    354354    REAL, SAVE, ALLOCATABLE,DIMENSION(:,:)          :: d_deltat_the, d_deltaq_the
    355355!$OMP THREADPRIVATE(d_deltat_the, d_deltaq_the)
    356356!!!      REAL,ALLOCATABLE,SAVE,DIMENSION(:)          :: d_s_the, d_dens_the
    357 !!!$OMP THREADPRIVATE(d_s_the, d_dens_the)
     357!!!OMP THREADPRIVATE(d_s_the, d_dens_the)
    358358      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:)           :: d_deltat_ajs_cv, d_deltaq_ajs_cv
    359359!$OMP THREADPRIVATE(d_deltat_ajs_cv, d_deltaq_ajs_cv)                       
  • LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90

    r5075 r5084  
    4848    USE mod_phys_lmdz_para
    4949    USE netcdf95, only: nf95_close
    50     USE lmdz_netcdf, only: nf90_fill_real     ! IM for NMC files
     50    USE netcdf, only: nf90_fill_real     ! IM for NMC files
    5151    USE open_climoz_m, only: open_climoz ! ozone climatology from a file
    5252    USE ozonecm_m, only: ozonecm ! ozone of J.-F. Royer
     
    13551355    !lwoff=y : offset LW CRE for radiation code and other schemes
    13561356    REAL, SAVE :: betalwoff
    1357     !$OMP THREADPRIVATE(betalwoff)
     1357    !OMP THREADPRIVATE(betalwoff)
    13581358!
    13591359    INTEGER :: nbtr_tmp ! Number of tracer inside concvl
Note: See TracChangeset for help on using the changeset viewer.