Changeset 3928


Ignore:
Timestamp:
Oct 13, 2025, 4:47:04 PM (7 weeks ago)
Author:
jmauxion
Message:

Generic PCM:
Adding a slow_diagfi flag to the run.def/rcm1d.def file for 1D models only. When False, the netcdf
file is opened/closed once, thus saving significant computing time. When true,
the opening frequency is at output frequency (recommended in debug mode). Also
fixing a redundant loop on tracers when writing outputs in physiq_mod.
JM

Location:
trunk/LMDZ.GENERIC
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/changelog.txt

    r3908 r3928  
    21032103option "Lmodif=2" when calling tabi from newstart to skip some checks
    21042104which only make sense when called during a regular GCM run.
     2105
     2106== 13/10/2025 == JM
     2107Adding a slow_diagfi flag to the run.def/rcm1d.def file for 1D models only. When False, the netcdf
     2108file is opened/closed once, thus saving significant computing time. When true,
     2109the opening frequency is at output frequency (recommended in debug mode). Also
     2110fixing a redundant loop on tracers when writing outputs in physiq_mod.
  • trunk/LMDZ.GENERIC/libf/phystd/inifis_mod.F90

    r3922 r3928  
    1717  use comgeomfi_h, only: totarea, totarea_planet
    1818  use comsoil_h, only: ini_comsoil_h, nsoilmx, lay1_soil, alpha_soil
    19   use time_phylmdz_mod, only: diagfi_output_rate, &
     19  use time_phylmdz_mod, only: diagfi_output_rate, slow_diagfi, &
    2020                              init_time, daysec, dtphys
    2121  use comcstfi_mod, only: rad, cpp, g, r, rcp, &
     
    155155                               diagfi_output_rate
    156156
     157     if ((is_master).and.(ngrid.eq.1)) write(*,*) trim(rname)//&
     158       ": Open/close diagfi.nc at output rate (rather than once) ?"
     159     slow_diagfi =.false. ! default value, open/close diagfi once (1D only)
     160     call getin_p("slow_diagfi",slow_diagfi) ! if true, open/close the diagfi.nc
     161                                             ! at output frequency instead of once
     162                                             ! (slower but required for debug)
     163     if ((is_master).and.(ngrid.eq.1)) write(*,*) trim(rname)//&
     164       ": slow_diagfi = ", slow_diagfi
     165
    157166     if (is_master) write(*,*) trim(rname)//&
    158167       ": Run with or without atm mass update "//&
  • trunk/LMDZ.GENERIC/libf/phystd/physiq_mod.F90

    r3922 r3928  
    27052705            ! call write_output(trim(noms(iq))//'_surf',trim(noms(iq))//'_surf',  &
    27062706            !              'kg m^-2',qsurf(:,iq) )
    2707 
    2708             if(watercond.or.CLFvarying)then
    2709                call write_output("rneb_man","H2O cloud fraction (conv)"," ",rneb_man)
    2710                call write_output("rneb_lsc","H2O cloud fraction (large scale)"," ",rneb_lsc)
    2711                call write_output("CLF","H2O cloud fraction"," ",cloudfrac)
    2712                call write_output("CLFt","H2O column cloud fraction"," ",totcloudfrac)
    2713                call write_output("RH","relative humidity"," ",RH)
    2714                call write_output("vteta","virtual potential temperature","K",zh * (1.+(1./epsi-1.) * &
    2715                        zq(1:ngrid,1:nlayer,1)))
    2716             endif
    2717 
    2718             if(waterrain)then
    2719                call write_output("rain","rainfall","kg m-2 s-1",zdqsrain)
    2720                call write_output("snow","snowfall","kg m-2 s-1",zdqssnow)
    2721                call write_output("reevap","reevaporation of precipitation","kg m-2 s-1",reevap_precip)
    2722             endif
    2723 
    2724             if(generic_condensation)then
    2725                call write_output("CLF","GCS cloud fraction"," ",cloudfrac)
    2726                !AF24: TODO fix rneb_generic and RH_generic failure with write_output()
    2727                ! call write_output("rneb_generic","GCS cloud fraction (generic condensation)"," ",rneb_generic)
    2728                ! call write_output("RH_generic","GCS relative humidity"," ",RH_generic)
    2729                call writediagfi(ngrid,"rneb_generic","GCS cloud fraction (generic condensation)"," ",3,rneb_generic)
    2730                call writediagfi(ngrid,"RH_generic","GCS relative humidity"," ",3,RH_generic)
    2731                call write_output("vteta","virtual potential temperature","K",zh * (1.+(1./epsi_generic-1.) * &
    2732                        zq(1:ngrid,1:nlayer,1) ))
    2733             endif
    2734 
    2735             if(generic_rain)then
    2736                call write_output("rain","generic rainfall","kg m-2 s-1",zdqsrain_generic)
    2737                call write_output("snow","generic snowfall","kg m-2 s-1",zdqssnow_generic)
    2738                call write_output("reevap","generic reevaporation of precipitation","kg m-2 s-1",reevap_precip_generic)
    2739             endif
    2740 
    2741             if((hydrology).and.(.not.ok_slab_ocean))then
    2742                call write_output("hice","oceanic ice height","m",hice)
    2743             endif
    2744 
    2745             call write_output("tau_col","Total aerosol optical depth","[]",tau_col)
    27462707         enddo ! end of 'nq' loop
     2708
     2709         if(watercond.or.CLFvarying)then
     2710            call write_output("rneb_man","H2O cloud fraction (conv)"," ",rneb_man)
     2711            call write_output("rneb_lsc","H2O cloud fraction (large scale)"," ",rneb_lsc)
     2712            call write_output("CLF","H2O cloud fraction"," ",cloudfrac)
     2713            call write_output("CLFt","H2O column cloud fraction"," ",totcloudfrac)
     2714            call write_output("RH","relative humidity"," ",RH)
     2715            call write_output("vteta","virtual potential temperature","K",zh * (1.+(1./epsi-1.) * &
     2716                     zq(1:ngrid,1:nlayer,1)))
     2717         endif
     2718
     2719         if(waterrain)then
     2720            call write_output("rain","rainfall","kg m-2 s-1",zdqsrain)
     2721            call write_output("snow","snowfall","kg m-2 s-1",zdqssnow)
     2722            call write_output("reevap","reevaporation of precipitation","kg m-2 s-1",reevap_precip)
     2723         endif
     2724
     2725         if(generic_condensation)then
     2726            call write_output("CLF","GCS cloud fraction"," ",cloudfrac)
     2727            !AF24: TODO fix rneb_generic and RH_generic failure with write_output()
     2728            ! call write_output("rneb_generic","GCS cloud fraction (generic condensation)"," ",rneb_generic)
     2729            ! call write_output("RH_generic","GCS relative humidity"," ",RH_generic)
     2730            call writediagfi(ngrid,"rneb_generic","GCS cloud fraction (generic condensation)"," ",3,rneb_generic)
     2731            call writediagfi(ngrid,"RH_generic","GCS relative humidity"," ",3,RH_generic)
     2732            call write_output("vteta","virtual potential temperature","K",zh * (1.+(1./epsi_generic-1.) * &
     2733                     zq(1:ngrid,1:nlayer,1) ))
     2734         endif
     2735
     2736         if(generic_rain)then
     2737            call write_output("rain","generic rainfall","kg m-2 s-1",zdqsrain_generic)
     2738            call write_output("snow","generic snowfall","kg m-2 s-1",zdqssnow_generic)
     2739            call write_output("reevap","generic reevaporation of precipitation","kg m-2 s-1",reevap_precip_generic)
     2740         endif
     2741
     2742         if((hydrology).and.(.not.ok_slab_ocean))then
     2743            call write_output("hice","oceanic ice height","m",hice)
     2744         endif
     2745
     2746         call write_output("tau_col","Total aerosol optical depth","[]",tau_col)
    27472747       endif ! end of 'tracer'
    27482748
  • trunk/LMDZ.GENERIC/libf/phystd/time_phylmdz_mod.F90

    r3725 r3928  
    1515                                    ! (set via inifis)
    1616!$OMP THREADPRIVATE(diagfi_output_rate)
     17
     18    LOGICAL,SAVE :: slow_diagfi ! to handle wether the netcdf file is
     19                                ! opened/close once or at output frequency
     20!$OMP THREADPRIVATE(slow_diagfi)
    1721
    1822CONTAINS
  • trunk/LMDZ.GENERIC/libf/phystd/writediagfi.F

    r3725 r3928  
    4242      use geometry_mod, only: cell_area
    4343      use time_phylmdz_mod, only: diagfi_output_rate, dtphys, daysec
    44       use time_phylmdz_mod, only: day_ini
     44      use time_phylmdz_mod, only: day_ini, nday, slow_diagfi
    4545      USE mod_phys_lmdz_para, only : is_parallel, is_mpi_root,
    4646     &                               is_master, gather
     
    7878
    7979      integer,save :: zitau=0
    80       character(len=40),save :: firstnom='1234567890'
    81 !$OMP THREADPRIVATE(zitau,firstnom)
     80      integer,save :: lastzitau=0
     81      character(len=27),save :: firstnom='1234567890'
     82      character(len=27),save :: prevnom='1234567890'
     83      character(len=27),save :: lastnom='1234567890'
     84!$OMP THREADPRIVATE(zitau,lastzitau,firstnom,prevnom,lastnom)
    8285
    8386! Ajouts
     
    8588!$OMP THREADPRIVATE(ntime)
    8689      integer :: idim,varid
    87       integer :: nid
     90      integer, save :: nid
     91!$OMP THREADPRIVATE(nid)
    8892      character(len=*),parameter :: fichnom="diagfi.nc"
    8993      integer, dimension(4) :: id
     
    127131         firstcall=.false.
    128132
     133         ! Compute the lastzitau (i.e. last timestep-1)
     134         lastzitau=nday*nint(daysec/dtphys)-1
     135         if (MOD(lastzitau+1,diagfi_output_rate).ne.0.) then
     136           ! If so, output rate is less than once per sol
     137           ! We must adjust zitau to
     138           lastzitau=lastzitau-MOD(lastzitau+1,diagfi_output_rate)
     139         endif
    129140!$OMP MASTER
    130141  !      Open diagfi.def definition file if there is one:
     
    245256         ENDIF
    246257
     258         ierr= NF_CLOSE(nid) ! Close the NETCDF file once initialized
     259
    247260         endif ! of if (is_master)
    248 
    249       else
    250 
    251          if (is_master) then
    252            ! only the master is required to do this
    253 
    254            ! Open the NetCDF file
    255            ierr = NF_OPEN(fichnom,NF_WRITE,nid)
    256          endif ! of if (is_master)
    257 
    258261      endif ! if (firstnom.eq.'1234567890')
     262
     263      ! Find lastnom
     264      if (lastnom.eq.'1234567890') then
     265         if (nom.eq.firstnom) then
     266            if (prevnom.ne.'1234567890') then
     267               lastnom=prevnom
     268            endif
     269         endif
     270         prevnom=nom
     271      endif
    259272
    260273! Increment time index 'zitau' if it is the "fist call" (at given time level)
     
    277290
    278291        if (is_master) then
    279            ! only the master is required to do this
     292          ! only the master is required to do this
     293
     294          ! 1D and slow_diagfi=.false. => open/close once
     295          if ((klon_glo.eq.1).and.(.not.slow_diagfi)) then
     296            ! if the very first time to write, open
     297            if ((nom.eq.firstnom).and.
     298     &         (((zitau+1)/diagfi_output_rate).eq.1)) then
     299              write(*,*) "Open NETCDF file for firstnom=", firstnom
     300              write(*,*) "zitau=", zitau
     301              ierr=NF_OPEN(fichnom,NF_WRITE,nid) ! open once in all simu
     302            endif
     303          else ! 3D or slow_diagfi=.true. => open/close at output frequency
     304            ierr=NF_OPEN(fichnom,NF_WRITE,nid)           
     305          endif
     306
    280307        if (nom.eq.firstnom) then
    281308        ! We have identified a "first call" (at given date)
     
    614641        endif ! of if (dim.eq.3) elseif(dim.eq.2)...
    615642
     643        ! Only the master do it
     644        if (is_master) then
     645          ! 1D and slow_diagfi=.false. => open/close once
     646          if ((klon_glo.eq.1).and.(.not.slow_diagfi)) then
     647            ! if the very last time to write, close
     648            if ((nom.eq.lastnom).and.(zitau.eq.lastzitau)) then
     649              write(*,*) "Close NETCDF file for lastnom=",lastnom
     650              write(*,*) "zitau=",zitau
     651              ierr = NF_CLOSE(nid) ! close once in all simu
     652            endif
     653          else ! 3D or slow_diagfi=.true. => open/close at output frequency
     654            ierr = NF_CLOSE(nid)
     655          endif
     656        endif
     657
    616658      endif ! of if ( MOD(zitau+1,diagfi_output_rate) .eq.0.)
    617659
    618       if (is_master) then
    619         ierr= NF_CLOSE(nid)
    620       endif
    621 
    622660      end
  • trunk/LMDZ.GENERIC/libf/phystd/writediagspecIR.F

    r3893 r3928  
    181181           call iniwrite_specIR(nid,day_ini,areafi_glo(1),1,1)
    182182         ENDIF
     183           ! Close the NetCDF file
     184           ierr= NF_CLOSE(nid)
    183185         endif ! of if (is_master)
    184186
    185187         zitau = -1 ! initialize zitau
    186       else
    187          if (is_master) then
    188            ! Open the NetCDF file
    189            ierr = NF_OPEN(fichnom,NF_WRITE,nid)
    190          endif
    191188      endif ! if (firstnom.eq.'1234567890')
    192189
     
    203200
    204201      if ( MOD(zitau+1,isample) .eq.0.) then
     202
     203         if (is_master) then
     204           ! Open the NetCDF file
     205           ierr = NF_OPEN(fichnom,NF_WRITE,nid)
     206         endif
    205207
    206208! Compute/write/extend 'Time' coordinate (date given in days)
     
    336338        endif ! of if (dimpx.eq.3)
    337339
     340        ! Close the NetCDF file
     341        if (is_master) then
     342          ierr= NF_CLOSE(nid)
     343        endif
     344
    338345      endif ! of if ( MOD(zitau+1,isample) .eq.0.)
    339346
    340       ! Close the NetCDF file
    341       if (is_master) then
    342         ierr= NF_CLOSE(nid)
    343       endif
    344 
    345347      end
  • trunk/LMDZ.GENERIC/libf/phystd/writediagspecVI.F

    r3893 r3928  
    180180           call iniwrite_specVI(nid,day_ini,areafi_glo(1),1,1)
    181181         ENDIF
     182           ! Close the NetCDF file
     183           ierr= NF_CLOSE(nid)
    182184         endif ! of if (is_master)
    183185
    184186         zitau = -1 ! initialize zitau
    185       else
    186          if (is_master) then
    187            ! Open the NetCDF file
    188            ierr = NF_OPEN(fichnom,NF_WRITE,nid)
    189          endif
    190187      endif ! if (firstnom.eq.'1234567890')
    191188
     
    208205!       (like the 'histoire' outputs)
    209206!--------------------------------------------------------
     207
     208         if (is_master) then
     209           ! Open the NetCDF file
     210           ierr = NF_OPEN(fichnom,NF_WRITE,nid)
     211         endif
    210212
    211213        if (nom.eq.firstnom) then
     
    335337        endif ! of if (dimpx.eq.3)
    336338
     339        ! Close the NetCDF file
     340        if (is_master) then
     341          ierr= NF_CLOSE(nid)
     342        endif
     343
    337344      endif ! of if ( MOD(zitau+1,isample) .eq.0.)
    338345
    339       ! Close the NetCDF file
    340       if (is_master) then
    341         ierr= NF_CLOSE(nid)
    342       endif
    343 
    344346      end
Note: See TracChangeset for help on using the changeset viewer.