Ignore:
Timestamp:
Jul 28, 2025, 7:23:15 PM (7 days ago)
Author:
aborella
Message:

Merge with trunk r5789

Location:
LMDZ6/branches/contrails
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails

  • LMDZ6/branches/contrails/libf/phylmd/undefSTD.f90

    r5310 r5791  
    33
    44SUBROUTINE undefstd(itap, read_climoz)
    5   USE clesphys_mod_h
     5  USE clesphys_mod_h, ONLY : freq_calnmc
    66  USE netcdf
    7   USE dimphy
    8   USE phys_state_var_mod
     7  USE dimphy, ONLY : klon
     8  USE phys_state_var_mod, ONLY : nlevstd,nout,o3std,o3sumstd,philevstd,phisumstd,phys_tstep,qlevstd,qsumstd
     9  USE phys_state_var_mod, ONLY : rhlevstd,rhsumstd,t2std,t2sumstd,tlevstd,tnondef,tsumstd,u2std,u2sumstd
     10  USE phys_state_var_mod, ONLY : ulevstd,usumstd,uvstd,uvsumstd,v2std,v2sumstd,vlevstd,vphistd,vphisumstd
     11  USE phys_state_var_mod, ONLY : vqstd,vqsumstd,vsumstd,vtstd,vtsumstd,wlevstd,wqstd,wqsumstd,wsumstd
     12  USE phys_state_var_mod, ONLY : wtstd,wtsumstd,o3daysumstd,o3daystd,missing_val_nf90
     13  USE phys_output_var_mod, ONLY : clef_files
     14
     15
    916  use wxios_mod, ONLY: missing_val_xios => missing_val, using_xios
    1017
     
    6471    ! de la physique
    6572
    66     IF (mod(itap,nint(freq_calnmc(n)/phys_tstep))==0) THEN
     73!   print*,'STDSTD n,freq_calnmc(n),phys_tstep',n,freq_calnmc(n),phys_tstep
     74    IF (clef_files(n) .and. mod(itap,nint(freq_calnmc(n)/phys_tstep))==0) THEN
    6775      DO k = 1, nlevstd
    6876        DO i = 1, klon
Note: See TracChangeset for help on using the changeset viewer.