Ignore:
Timestamp:
Dec 5, 2013, 6:32:35 PM (10 years ago)
Author:
musat
Message:

1) Modifications pour faire des simulations par an avec un calendrier realiste (365 jours ou autre).

Il faut mettre une frequence de sortie de -1 (variable phys_out_filetimesteps dans config.def) pour
que IOIPSL calcule les moyennes mensuels en prenant en compte des longuers variables de chaque
mois. Par exemple, pour le fichier histmth (1er fichier) et histmthNMC (7eme).
phys_out_filetimesteps= -1 1day 6hr 6hr 6hr 1d -1 1day 6hr

2) Corrections titres variables niveaux de pression des fichiers histmth, histday, etc

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/moy_undefSTD.F

    r1907 r1912  
    22! $Id$
    33!
    4       SUBROUTINE moy_undefSTD(itap,freq_outNMC,freq_moyNMC)
     4      SUBROUTINE moy_undefSTD(itap,itapm1)
    55      USE netcdf
    66      USE dimphy
    7       USE phys_state_var_mod ! Variables sauvegardees de la physique
     7      USE phys_state_var_mod
     8      USE phys_cal_mod, only : mth_len
    89      IMPLICIT none
     10      include "clesphys.h"
    911c
    1012c====================================================================
     
    3335c     INTEGER nlevSTD, klevSTD, itap
    3436c     PARAMETER(klevSTD=17)
    35       INTEGER itap
     37      INTEGER itap, itapm1
    3638c
    3739c variables locales
     
    4042      INTEGER i, k, n
    4143c     REAL dtime, freq_outNMC(nout), freq_moyNMC(nout)
    42       REAL freq_outNMC(nout), freq_moyNMC(nout)
     44c     REAL freq_outNMC(nout), freq_calNMC(nout)
     45      REAL freq_moyNMC(nout)
    4346c
    4447c variables Output
     
    4649c     REAL tsumSTD(klon,klevSTD,nout)
    4750c
     51      REAL un_jour
     52      PARAMETER(un_jour=86400.)
    4853      REAL missing_val
    4954c
     
    5156c
    5257      DO n=1, nout
     58       IF(freq_outNMC(n).LT.0) THEN
     59         freq_moyNMC(n)=(mth_len*un_jour)/freq_calNMC(n)
     60c        print*,'moy_undefSTD n freq_out freq_moy =',
     61c    $n,freq_moyNMC(n)
     62       ENDIF         
    5363c
    54 c calcul 1 fois par jour
     64c calcul 1 fois pas mois, 1 fois par jour ou toutes les 6h
    5565c
    56        IF(MOD(itap,NINT(freq_outNMC(n)/dtime)).EQ.0) THEN
     66       IF(n.EQ.1.AND.itap.EQ.itapm1.OR.
     67     $n.GT.1.AND.MOD(itap,NINT(freq_outNMC(n)/dtime)).EQ.0) THEN
     68c
     69c       print*,'moy_undefSTD n itap itapm1',n,itap,itapm1
    5770c
    5871        DO k=1, nlevSTD
     
    6174           tsumSTD(i,k,n)=tsumSTD(i,k,n)/
    6275     $     (freq_moyNMC(n)-tnondef(i,k,n))
    63 cIM BEG
    6476          usumSTD(i,k,n)=usumSTD(i,k,n)/
    6577     $     (freq_moyNMC(n)-tnondef(i,k,n))
     
    96108          O3daysumSTD(i,k,n)=O3daysumSTD(i,k,n)/
    97109     $     (freq_moyNMC(n)-tnondef(i,k,n))
    98 cIM END
    99110          ELSE
    100111           tsumSTD(i,k,n)=missing_val
Note: See TracChangeset for help on using the changeset viewer.