Changeset 3749


Ignore:
Timestamp:
Apr 30, 2025, 5:54:41 PM (3 months ago)
Author:
afalco
Message:

Pluto: ecritphy changed into diagfi_output_rate (followup of generic model), which defines the output rate of the diagfi in physical timesteps rather than dynamical ones.
AF

Location:
trunk/LMDZ.PLUTO/libf/phypluto
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.PLUTO/libf/phypluto/dyn1d/rcm1d.F

    r3718 r3749  
    2020      use comcstfi_mod, only: pi, cpp, rad, g, r,
    2121     &                        mugaz, rcp, omeg
    22       use time_phylmdz_mod, only: daysec, dtphys, day_step, ecritphy,
     22      use time_phylmdz_mod, only: daysec, dtphys, diagfi_output_rate,
    2323     &                            nday, iphysiq
    2424      use callkeys_mod, only: tracer, specOLR,pceil,haze
     
    8080      INTEGER lecttsoil     ! lecture of tsoil from proftsoil
    8181      INTEGER lecthaze      ! lecture of haze from profhaze
    82       REAL day              ! date durant le run
     82      REAL day              ! date during the run
     83      INTEGER day_step      ! number of time steps per day
    8384      REAL time             ! time (0<time<1 ; time=0.5 a midi)
    8485      REAL play(llm)        ! Pressure at the middle of the layers (Pa)
     
    528529      write(*,*) " day_step = ",day_step
    529530
    530       iphysiq=1 ! in 1D model physics are called evry time step
    531       ecritphy=day_step ! default value for ecritphy
     531      diagfi_output_rate=24 ! default value for diagfi_output_rate
    532532      PRINT *,'Nunber of steps between writediagfi ?'
    533       call getin("ecritphy",ecritphy)
    534       write(*,*) " ecritphy = ",ecritphy
     533      call getin("diagfi_output_rate",diagfi_output_rate)
     534      write(*,*) " diagfi_output_rate = ",diagfi_output_rate
    535535
    536536      ndt=10 ! default value for ndt
  • trunk/LMDZ.PLUTO/libf/phypluto/inifis_mod.F90

    r3684 r3749  
    1818  use comgeomfi_h, only: totarea, totarea_planet
    1919  use comsoil_h, only: ini_comsoil_h, nsoilmx, lay1_soil, alpha_soil
    20   use time_phylmdz_mod, only: ecritphy,day_step,iphysiq, &
     20  use time_phylmdz_mod, only: diagfi_output_rate, &
    2121                              init_time, daysec, dtphys
    2222  use comcstfi_mod, only: rad, cpp, g, r, rcp, &
     
    8383  REAL SSUM
    8484
    85   ! deprecated parameter
     85  ! deprecated parameters
     86  REAL :: ecritphy ! to check that this obsolete flag is no longer used...
    8687  logical aerohaze
    8788
     
    104105#endif
    105106
     107
    106108  ! read in some parameters from "run.def" for physics,
    107109  ! or shared between dynamics and physics.
     110  ecritphy=-666 ! dummy default value
    108111  call getin_p("ecritphy",ecritphy) ! frequency of outputs in physics,
    109112                                    ! in dynamical steps
    110   call getin_p("day_step",day_step) ! number of dynamical steps per day
    111   call getin_p("iphysiq",iphysiq) ! call physics every iphysiq dyn step
     113  if (ecritphy/=-666) then
     114    call abort_physic(rname, &
     115         "Error: parameter ecritphy is obsolete! Remove it! "//&
     116         "And use diagfi_output_rate instead",1)
     117  endif
    112118
    113119  ! do we read a startphy.nc file? (default: .true.)
     
    164170     call getin_p("tracer",tracer)
    165171     if (is_master) write(*,*) trim(rname)//": tracer = ",tracer
     172
     173     if (is_master) write(*,*) trim(rname)//&
     174       ": Output rate for diagfi.nc file (in physics steps) ?"
     175     diagfi_output_rate=24 !default value
     176     call getin_p("diagfi_output_rate",diagfi_output_rate)
     177     if (is_master) write(*,*) trim(rname)//": diagfi_output_rate = ",&
     178                               diagfi_output_rate
    166179
    167180     if (is_master) write(*,*) trim(rname)//&
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3698 r3749  
    3535                          alpha_lift, alpha_devil, qextrhor, &
    3636                          nesp, is_chim
    37       use time_phylmdz_mod, only: ecritphy, iphysiq, nday
     37      use time_phylmdz_mod, only: diagfi_output_rate, nday
    3838      use phyetat0_mod, only: phyetat0,tab_cntrl_mod
    3939      use wstats_mod, only: callstats, wstats, mkstats
     
    18581858
    18591859         if(meanOLR .and. is_master)then
    1860             if((ngrid.gt.1) .or. (mod(icount-1,ecritphy).eq.0))then
     1860            if((ngrid.gt.1) .or. (mod(icount-1,diagfi_output_rate).eq.0))then
    18611861               ! to record global radiative balance
    18621862               open(92,file="rad_bal.out",form='formatted',position='append')
     
    21102110!           containing any variable for diagnostic
    21112111!
    2112 !             Note 1 : output with  period "ecritphy", set in "run.def"
     2112!             Note 1 : output with  period "diagfi_output_rate", set in "run.def"
    21132113!             Note 2 : writediagfi can also be called from any other subroutine
    21142114!                      for any variable, but its preferable to keep all the
     
    22082208      call write_output('dtaui_01','Layer optical thickness attenuation in IR band','',int_dtaui(:,nlayer:1:-1,1))
    22092209      call write_output('dtaui_17','Layer optical thickness attenuation in IR band','',int_dtaui(:,nlayer:1:-1,17))
    2210      
     2210
    22112211      ! Temporary inclusions for heating diagnostics.
    22122212      if (.not.fast) then
  • trunk/LMDZ.PLUTO/libf/phypluto/time_phylmdz_mod.F90

    r3184 r3749  
    44    REAL,SAVE    :: dtphys     ! physics time step (s)
    55!$OMP THREADPRIVATE(dtphys)
    6     INTEGER,SAVE :: day_step    ! number of dynamical steps per day
    7                                 ! (set via inifis)
    8 !$OMP THREADPRIVATE(day_step)
    96    INTEGER,SAVE :: nday       ! number of days to run
    107!$OMP THREADPRIVATE(nday)
     
    1411!$OMP THREADPRIVATE(day_ini)
    1512
    16     INTEGER,SAVE :: ecritphy  ! for diagfi.nc outputs, write every ecritphy
    17                               ! dynamical steps (set via inifis)
    18 !$OMP THREADPRIVATE(ecritphy)
    19     INTEGER,SAVE :: iphysiq   ! call physics every iphysiq dynamical step
    20                               ! (set via inifis)
    21 !$OMP THREADPRIVATE(iphysiq)
     13    INTEGER,SAVE :: diagfi_output_rate  ! for diagfi.nc outputs, write every diagfi_output_rate physical steps (set via inifis)
     14!$OMP THREADPRIVATE(diagfi_output_rate)
    2215
    2316CONTAINS
     
    2922    INTEGER,INTENT(IN) :: nday_
    3023    REAL,INTENT(IN) :: dtphys_
    31    
     24
    3225    day_ini=day_ini_
    3326    daysec=daysec_
     
    3730  END SUBROUTINE init_time
    3831
    39 END MODULE time_phylmdz_mod     
     32END MODULE time_phylmdz_mod
  • trunk/LMDZ.PLUTO/libf/phypluto/writediagfi.F

    r3623 r3749  
    88!  (ou encore 1d, dans le cas de testphys1d, pour sortir une colonne)
    99!  La periode d'ecriture est donnee par
    10 !  "ecritphy " regle dans le fichier de controle de run :  run.def
     10!  "diagfi_output_rate " regle dans le fichier de controle de run :  run.def
    1111!
    1212!    writediagfi peut etre appele de n'importe quelle subroutine
     
    4141      use surfdat_h, only: phisfi
    4242      use geometry_mod, only: cell_area
    43       use time_phylmdz_mod, only: ecritphy, day_step, iphysiq, day_ini
     43      use time_phylmdz_mod, only: diagfi_output_rate,dtphys,daysec
     44      use time_phylmdz_mod, only: day_ini
    4445      USE mod_phys_lmdz_para, only : is_parallel, is_mpi_root,
    4546     &                               is_master, gather
     
    7374      REAL area((nbp_lon+1),nbp_lat)
    7475
    75       integer irythme
     76      integer isample
    7677      integer ierr,ierr2
    7778      integer i,j,l, ig0
     
    121122
    122123!***************************************************************
    123 !Sortie des variables au rythme voulu
    124 
    125       irythme = int(ecritphy) ! output rate set by ecritphy
     124!Output rate
     125
     126      isample = diagfi_output_rate
    126127
    127128!***************************************************************
     
    272273!------------------------------------------------------------------------
    273274      if (nom.eq.firstnom) then
    274           zitau = zitau + iphysiq
     275          zitau = zitau + 1
    275276      end if
    276277
     
    279280!--------------------------------------------------------
    280281
    281       if ( MOD(zitau+1,irythme) .eq.0.) then
     282      if ( MOD(zitau+1,isample) .eq.0.) then
    282283
    283284! Compute/write/extend 'Time' coordinate (date given in days)
     
    292293           ntime=ntime+1 ! increment # of stored time steps
    293294           ! compute corresponding date (in days and fractions thereof)
    294            date=(zitau +1.)/day_step
     295           date=(zitau +1.)*(dtphys/daysec)
    295296           ! Get NetCDF ID of 'Time' variable
    296297           ierr= NF_INQ_VARID(nid,"Time",varid)
     
    624625        endif ! of if (dim.eq.3) elseif(dim.eq.2)...
    625626
    626       endif ! of if ( MOD(zitau+1,irythme) .eq.0.)
     627      endif ! of if ( MOD(zitau+1,isample) .eq.0.)
    627628
    628629      if (is_master) then
  • trunk/LMDZ.PLUTO/libf/phypluto/writediagsoil.F90

    r3698 r3749  
    2020use comsoil_h, only: nsoilmx, inertiedat
    2121use geometry_mod, only: cell_area
    22 use time_phylmdz_mod, only: ecritphy, day_step, iphysiq
     22use time_phylmdz_mod, only: diagfi_output_rate,dtphys,daysec,day_ini
    2323use mod_phys_lmdz_para, only : is_mpi_root, is_master, gather
    2424use mod_grid_phy_lmdz, only : klon_glo, Grid1Dto2D_glo, &
     
    100100
    101101  ! Set output sample rate
    102   isample=int(ecritphy) ! same as for diagfi outputs
    103   ! Note ecritphy is known from control.h
     102  isample=diagfi_output_rate ! same as for diagfi outputs
    104103
    105104  ! Create output NetCDF file
     
    164163if (name.eq.firstname) then
    165164  ! if we run across 'firstname', then it is a new time step
    166   zitau=zitau+iphysiq
     165  zitau=zitau+1
    167166  ! Note iphysiq is known from control.h
    168167endif
     
    174173  if (name.eq.firstname) then
    175174    ntime=ntime+1
    176     date=float(zitau+1)/float(day_step)
     175    date=(zitau +1.)*(dtphys/daysec)
    177176    ! Note: day_step is known from control.h
    178177
  • trunk/LMDZ.PLUTO/libf/phypluto/writediagspecIR.F

    r3184 r3749  
    11      subroutine writediagspecIR(ngrid,nom,titre,unite,dimpx,px)
    22
    3 !  Ecriture de variables diagnostiques au choix dans la physique 
     3!  Ecriture de variables diagnostiques au choix dans la physique
    44!  dans un fichier NetCDF nomme  'diagfi'. Ces variables peuvent etre
    55!  3d (ex : temperature), 2d (ex : temperature de surface), ou
    66!  0d (pour un scalaire qui ne depend que du temps : ex : la longitude
    77!  solaire)
    8 !  Dans la version 2000, la periode d'ecriture est celle de 
    9 !  "ecritphy " regle dans le fichier de controle de run :  run.def
     8!  Dans la version 2000, la periode d'ecriture est celle de
     9!  "diagfi_output_rate " regle dans le fichier de controle de run :  run.def
    1010!
    1111!    writediagfi peut etre appele de n'importe quelle subroutine
     
    1515! WARNING : les variables dynamique (u,v,t,q,ps)
    1616!  sauvees par writediagfi avec une
    17 ! date donnee sont legerement differentes que dans le fichier histoire car 
     17! date donnee sont legerement differentes que dans le fichier histoire car
    1818! on ne leur a pas encore ajoute de la dissipation et de la physique !!!
    1919! IL est  RECOMMANDE d'ajouter les tendance physique a ces variables
    2020! avant l'ecriture dans diagfi (cf. physiq.F)
    21 ! 
     21!
    2222!
    2323!  parametres (input) :
     
    2626!                (ngrid = 2+(jjm-1)*iim - 1/jjm)
    2727!                 (= nlon ou klon dans la physique terrestre)
    28 !     
     28!
    2929!      unit : unite logique du fichier de sortie (toujours la meme)
    3030!      nom  : nom de la variable a sortir (chaine de caracteres)
     
    4040!
    4141!=================================================================
    42  
     42
    4343! Addition by RW (2010) to allow OLR to be saved in .nc format
    4444      use radinc_h, only : L_NSPECTI
     
    4848     &                              nbp_lon, nbp_lat, grid_type,
    4949     &                              unstructured
    50       use time_phylmdz_mod, only: ecritphy, iphysiq, day_step, day_ini
     50      use time_phylmdz_mod, only: diagfi_output_rate,dtphys,daysec
     51      use time_phylmdz_mod, only: day_ini
    5152      use callkeys_mod, only: iradia
    5253
     
    6768!      real dx0
    6869
    69       integer irythme
     70      integer isample
    7071      integer ierr
    7172      integer iq
     
    99100      real areafi_glo(ngrid) ! mesh area on global physics grid
    100101#endif
    101       if (grid_type == unstructured) then 
    102         return 
     102      if (grid_type == unstructured) then
     103        return
    103104      endif
    104105
     
    106107!Sortie des variables au rythme voulu
    107108
    108       irythme = ecritphy*iradia ! sortie au rythme de ecritphy*iradia
     109      isample = diagfi_output_rate*iradia ! sortie au rythme de diagfi_output_rate*iradia
    109110!EM+JL if the spetra need to be output more frequently, need to define a ecritSpec...
    110 !     irythme = iphysiq  ! sortie a tous les pas physique
     111!     isample = iphysiq  ! sortie a tous les pas physique
    111112
    112113
     
    193194!------------------------------------------------------------------------
    194195      if (nom.eq.firstnom) then
    195           zitau = zitau + iphysiq
     196          zitau = zitau + 1
    196197      end if
    197198
     
    200201!--------------------------------------------------------
    201202
    202       if ( MOD(zitau+1,irythme) .eq.0.) then
     203      if ( MOD(zitau+1,isample) .eq.0.) then
    203204
    204205! Compute/write/extend 'Time' coordinate (date given in days)
     
    213214           ntime=ntime+1 ! increment # of stored time steps
    214215           ! compute corresponding date (in days and fractions thereof)
    215            date= float (zitau +1)/float (day_step)
     216           date= float (zitau +1)*(dtphys/daysec)
    216217
    217218           if (is_master) then
     
    228229              write(*,*) "***** PUT_VAR matter in writediagspec_nc"
    229230              write(*,*) "***** with time"
    230               write(*,*) 'ierr=', ierr   
     231              write(*,*) 'ierr=', ierr
    231232c             call abort
    232233             endif
     
    237238
    238239
    239  
     240
    240241!Case of a 3D variable
    241242!---------------------
     
    327328              write(*,*) 'ierr=', ierr
    328329             call abort
    329            endif 
     330           endif
    330331
    331332          endif ! of if (is_master)
     
    333334        endif ! of if (dimpx.eq.3)
    334335
    335       endif ! of if ( MOD(zitau+1,irythme) .eq.0.)
     336      endif ! of if ( MOD(zitau+1,isample) .eq.0.)
    336337
    337338      ! Close the NetCDF file
  • trunk/LMDZ.PLUTO/libf/phypluto/writediagspecVI.F

    r3184 r3749  
    11      subroutine writediagspecVI(ngrid,nom,titre,unite,dimpx,px)
    22
    3 !  Ecriture de variables diagnostiques au choix dans la physique 
     3!  Ecriture de variables diagnostiques au choix dans la physique
    44!  dans un fichier NetCDF nomme  'diagfi'. Ces variables peuvent etre
    55!  3d (ex : temperature), 2d (ex : temperature de surface), ou
    66!  0d (pour un scalaire qui ne depend que du temps : ex : la longitude
    77!  solaire)
    8 !  Dans la version 2000, la periode d'ecriture est celle de 
    9 !  "ecritphy " regle dans le fichier de controle de run :  run.def
     8!  Dans la version 2000, la periode d'ecriture est celle de
     9!  "diagfi_output_rate " regle dans le fichier de controle de run :  run.def
    1010!
    1111!    writediagfi peut etre appele de n'importe quelle subroutine
     
    1515! WARNING : les variables dynamique (u,v,t,q,ps)
    1616!  sauvees par writediagfi avec une
    17 ! date donnee sont legerement differentes que dans le fichier histoire car 
     17! date donnee sont legerement differentes que dans le fichier histoire car
    1818! on ne leur a pas encore ajoute de la dissipation et de la physique !!!
    1919! IL est  RECOMMANDE d'ajouter les tendance physique a ces variables
    2020! avant l'ecriture dans diagfi (cf. physiq.F)
    21 ! 
     21!
    2222!
    2323!  parametres (input) :
     
    2626!                (ngrid = 2+(jjm-1)*iim - 1/jjm)
    2727!                 (= nlon ou klon dans la physique terrestre)
    28 !     
     28!
    2929!      unit : unite logique du fichier de sortie (toujours la meme)
    3030!      nom  : nom de la variable a sortir (chaine de caracteres)
     
    4040!
    4141!=================================================================
    42  
     42
    4343! Addition by RW (2010) to allow OSR to be saved in .nc format
    4444      use radinc_h, only : L_NSPECTV
     
    4848     &                              nbp_lon, nbp_lat, grid_type,
    4949     &                              unstructured
    50       use time_phylmdz_mod, only: ecritphy, iphysiq, day_step, day_ini
     50      use time_phylmdz_mod, only: diagfi_output_rate,dtphys,daysec
     51      use time_phylmdz_mod, only: day_ini
    5152      use callkeys_mod, only: iradia
    5253
     
    6768!      real dx0
    6869
    69       integer irythme
     70      integer isample
    7071      integer ierr
    7172      integer iq
     
    99100      real areafi_glo(ngrid) ! mesh area on global physics grid
    100101#endif
    101       if (grid_type == unstructured) then 
     102      if (grid_type == unstructured) then
    102103        return
    103104      endif
     
    106107!Sortie des variables au rythme voulu
    107108
    108       irythme = ecritphy*iradia ! sortie au rythme de ecritphy
     109      isample = diagfi_output_rate*iradia ! sortie au rythme de diagfi_output_rate
    109110!EM+JL if the spetra need to be output more frequently, need to define a ecritSpec...
    110 !     irythme = iphysiq  ! sortie a tous les pas physique
     111!     isample = diagfi_output_rate  ! sortie a tous les pas physique
    111112
    112113!***************************************************************
     
    192193!------------------------------------------------------------------------
    193194      if (nom.eq.firstnom) then
    194           zitau = zitau + iphysiq
     195          zitau = zitau + 1
    195196      end if
    196197
     
    199200!--------------------------------------------------------
    200201
    201       if ( MOD(zitau+1,irythme) .eq.0.) then
     202      if ( MOD(zitau+1,isample) .eq.0.) then
    202203
    203204! Compute/write/extend 'Time' coordinate (date given in days)
     
    212213           ntime=ntime+1 ! increment # of stored time steps
    213214           ! compute corresponding date (in days and fractions thereof)
    214            date= float (zitau +1)/float (day_step)
     215           date= float (zitau +1)*(dtphys/daysec)
    215216
    216217           if (is_master) then
     
    227228              write(*,*) "***** PUT_VAR matter in writediagspec_nc"
    228229              write(*,*) "***** with time"
    229               write(*,*) 'ierr=', ierr   
     230              write(*,*) 'ierr=', ierr
    230231c             call abort
    231232             endif
     
    236237
    237238
    238  
     239
    239240!Case of a 3D variable
    240241!---------------------
     
    326327              write(*,*) 'ierr=', ierr
    327328             call abort
    328            endif 
     329           endif
    329330
    330331          endif ! of if (is_master)
Note: See TracChangeset for help on using the changeset viewer.