source: LMDZ5/trunk/libf/phylmd/undefSTD.F @ 1907

Last change on this file since 1907 was 1907, checked in by lguez, 10 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
Name of program: LMDZ
Creation date: 1984
Version: LMDZ5
License: CeCILL version 2
Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
See the license file in the root directory

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 3.0 KB
Line 
1!
2! $Id: undefSTD.F 1907 2013-11-26 13:10:46Z lguez $
3!
4      SUBROUTINE undefSTD(itap,freq_calNMC, read_climoz)
5      USE netcdf
6      USE dimphy
7      USE phys_state_var_mod ! Variables sauvegardees de la physique
8      IMPLICIT none
9c
10c====================================================================
11c
12c I. Musat : 09.2004
13c
14c Calcul * du nombre de pas de temps (FLOAT(ecrit_XXX)-tnondef))
15c          ou la variable tlevSTD est bien definie (.NE.missing_val),
16c et
17c        * de la somme de tlevSTD => tsumSTD
18c
19c nout=1 !var. journaliere "day" moyenne sur tous les pas de temps
20c        ! de la physique
21c nout=2 !var. mensuelle "mth" moyennee sur tous les pas de temps
22c        ! de la physique
23c nout=3 !var. mensuelle "NMC" moyennee toutes les ecrit_hf
24c
25c
26c NB: mettre "inst(X)" dans le write_hist*NMC.h !
27c====================================================================
28c
29cym#include "dimensions.h"
30cym      integer jjmp1
31cym      parameter (jjmp1=jjm+1-1/jjm)
32cym#include "dimphy.h"
33c variables Input
34c
35c     INTEGER nlevSTD, klevSTD, itap
36c     PARAMETER(klevSTD=17)
37      INTEGER itap
38c     REAL dtime
39c
40c variables locales
41c     INTEGER i, k, nout, n
42c     PARAMETER(nout=3) !nout=1 : day; =2 : mth; =3 : NMC
43      INTEGER i, k, n
44      REAL freq_calNMC(nout)
45      INTEGER read_climoz
46c
47c variables Output
48c     REAL tlevSTD(klon,klevSTD), tsumSTD(klon,klevSTD,nout)
49c     LOGICAL oknondef(klon,klevSTD,nout)
50c     REAL tnondef(klon,klevSTD,nout)
51c
52      REAL missing_val
53c
54      missing_val=nf90_fill_real
55c
56      DO n=1, nout
57c
58c
59c calcul variables tous les freq_calNMC(n)/dtime pas de temps
60c de la physique
61c
62       IF(MOD(itap,NINT(freq_calNMC(n)/dtime)).EQ.0) THEN
63        DO k=1, nlevSTD
64         DO i=1, klon
65          IF(tlevSTD(i,k).EQ.missing_val) THEN
66c          IF(oknondef(i,k,n)) THEN         
67            tnondef(i,k,n)=tnondef(i,k,n)+1.
68c          ENDIF !oknondef(i,k)
69c
70          ELSE IF(tlevSTD(i,k).NE.missing_val) THEN
71           tsumSTD(i,k,n)=tsumSTD(i,k,n)+tlevSTD(i,k)
72           usumSTD(i,k,n)=usumSTD(i,k,n)+ulevSTD(i,k)
73           vsumSTD(i,k,n)=vsumSTD(i,k,n)+vlevSTD(i,k)
74           wsumSTD(i,k,n)=wsumSTD(i,k,n)+wlevSTD(i,k)
75           phisumSTD(i,k,n)=phisumSTD(i,k,n)+philevSTD(i,k)
76           qsumSTD(i,k,n)=qsumSTD(i,k,n)+qlevSTD(i,k)
77           rhsumSTD(i,k,n)=rhsumSTD(i,k,n)+rhlevSTD(i,k)
78           uvsumSTD(i,k,n)=uvsumSTD(i,k,n)+uvSTD(i,k)
79           vqsumSTD(i,k,n)=vqsumSTD(i,k,n)+vqSTD(i,k)
80           vTsumSTD(i,k,n)=vTsumSTD(i,k,n)+vTSTD(i,k)
81           wqsumSTD(i,k,n)=wqsumSTD(i,k,n)+wqSTD(i,k)
82           vphisumSTD(i,k,n)=vphisumSTD(i,k,n)+vphiSTD(i,k)
83           wTsumSTD(i,k,n)=wTsumSTD(i,k,n)+wTSTD(i,k)
84           u2sumSTD(i,k,n)=u2sumSTD(i,k,n)+u2STD(i,k)
85           v2sumSTD(i,k,n)=v2sumSTD(i,k,n)+v2STD(i,k)
86           T2sumSTD(i,k,n)=T2sumSTD(i,k,n)+T2STD(i,k)
87           O3sumSTD(i,k,n)=O3sumSTD(i,k,n)+O3STD(i,k)
88           IF (read_climoz==2)
89     &          O3daysumSTD(i,k,n)=O3daysumSTD(i,k,n)+O3daySTD(i,k)
90
91          ENDIF
92         ENDDO !i
93        ENDDO !k
94c
95       ENDIF !MOD(itap,NINT(freq_calNMC(n)/dtime)).EQ.0
96c
97      ENDDO !n
98c
99      RETURN
100      END 
Note: See TracBrowser for help on using the repository browser.