Ignore:
Timestamp:
Dec 20, 2013, 10:04:40 AM (10 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r1909:1920 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phylmd/moy_undefSTD.F

    r1910 r1921  
    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       ELSE
     63         freq_moyNMC(n)=freq_outNMC(n)/freq_calNMC(n)
     64       ENDIF         
    5365c
    54 c calcul 1 fois par jour
     66c calcul 1 fois pas mois, 1 fois par jour ou toutes les 6h
    5567c
    56        IF(MOD(itap,NINT(freq_outNMC(n)/dtime)).EQ.0) THEN
     68       IF(n.EQ.1.AND.itap.EQ.itapm1.OR.
     69     $n.GT.1.AND.MOD(itap,NINT(freq_outNMC(n)/dtime)).EQ.0) THEN
     70c
     71c       print*,'moy_undefSTD n itap itapm1',n,itap,itapm1
    5772c
    5873        DO k=1, nlevSTD
     
    6176           tsumSTD(i,k,n)=tsumSTD(i,k,n)/
    6277     $     (freq_moyNMC(n)-tnondef(i,k,n))
    63 cIM BEG
    6478          usumSTD(i,k,n)=usumSTD(i,k,n)/
    6579     $     (freq_moyNMC(n)-tnondef(i,k,n))
     
    96110          O3daysumSTD(i,k,n)=O3daysumSTD(i,k,n)/
    97111     $     (freq_moyNMC(n)-tnondef(i,k,n))
    98 cIM END
    99112          ELSE
    100113           tsumSTD(i,k,n)=missing_val
Note: See TracChangeset for help on using the changeset viewer.