/[lmdze]/trunk/libf/phylmd/undefSTD.f
ViewVC logotype

Annotation of /trunk/libf/phylmd/undefSTD.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 7 - (hide annotations)
Mon Mar 31 12:24:17 2008 UTC (16 years, 2 months ago) by guez
File size: 2364 byte(s)
This revision is not in working order. Pending some moving of files.

Important changes. In the program "etat0_lim": ozone coefficients from
Mobidic are regridded in time instead of pressure ; consequences in
"etat0". In the program "gcm", ozone coefficients from Mobidic are
read once per day only for the current day and regridded in pressure ;
consequences in "o3_chem_m", "regr_pr_coefoz", "phytrac" and
"regr_pr_comb_coefoz_m".

NetCDF95 is a library and does not export NetCDF.

New variables "nag_gl_options", "nag_fcalls_options" and
"nag_cross_options" in "nag_tools.mk".

"check_coefoz.jnl" rewritten entirely for new version of
"coefoz_LMDZ.nc".

Target "obj_etat0_lim" moved from "GNUmakefile" to "nag_rules.mk".

Added some "intent" attributes in "calfis", "clmain", "clqh",
"cltrac", "cltracrn", "cvltr", "ini_undefSTD", "moy_undefSTD",
"nflxtr", "phystokenc", "phytrac", "readsulfate", "readsulfate_preind"
and "undefSTD".

In "dynetat0", "dynredem0" and "gcm", "phis" has rank 2 instead of
1. "phis" has assumed shape in "dynredem0".

Added module containing "dynredem0". Changed some calls with NetCDF
Fortran 77 interface to calls with NetCDF95 interface.

Replaced calls to "ssum" by calls to "sum" in "inigeom".

In "make.sh", new option "-c" to change compiler.

In "aaam_bud", argument "rjour" deleted.

In "physiq": renamed some variables; deleted variable "xjour".

In "phytrac": renamed some variables; new argument "lmt_pas".

1 guez 3 SUBROUTINE undefSTD(nlevSTD,itap,tlevSTD,
2     $ ecrit_hf,
3     $ oknondef,tnondef,tsumSTD)
4     use dimens_m
5     use dimphy
6     IMPLICIT none
7     c
8     c====================================================================
9     c
10     c I. Musat : 09.2004
11     c
12     c Calcul * du nombre de pas de temps (FLOAT(ecrit_XXX)-tnondef))
13     c ou la variable tlevSTD est bien definie (.NE.1.E+20),
14     c et
15     c * de la somme de tlevSTD => tsumSTD
16     c
17     c nout=1 !var. journaliere "day" moyenne sur tous les pas de temps
18     c ! de la physique
19     c nout=2 !var. mensuelle "mth" moyennee sur tous les pas de temps
20     c ! de la physique
21     c nout=3 !var. mensuelle "NMC" moyennee toutes les 6heures
22     c
23     c
24     c NB: mettre "inst(X)" dans le write_histXXX.h !
25     c====================================================================
26     c
27     integer jjmp1
28     parameter (jjmp1=jjm+1-1/jjm)
29     c variables Input
30 guez 7 INTEGER nlevSTD, klevSTD
31     integer, intent(in):: itap
32 guez 3 PARAMETER(klevSTD=17)
33     INTEGER, intent(in):: ecrit_hf
34     c
35     c variables locales
36     INTEGER i, k, nout
37     PARAMETER(nout=3) !nout=1 : day; =2 : mth; =3 : NMC
38     c
39     c variables Output
40     REAL tlevSTD(klon,klevSTD), tsumSTD(klon,klevSTD,nout)
41     LOGICAL oknondef(klon,klevSTD,nout)
42     REAL tnondef(klon,klevSTD,nout)
43     c
44     c calcul variables tous les pas de temps de la physique
45     c
46     DO k=1, nlevSTD
47     DO i=1, klon
48     IF(tlevSTD(i,k).EQ.1E+20) THEN
49     IF(oknondef(i,k,1)) THEN
50     tnondef(i,k,1)=tnondef(i,k,1)+1.
51     ENDIF !oknondef(i,k)
52     c
53     IF(oknondef(i,k,2)) THEN
54     tnondef(i,k,2)=tnondef(i,k,2)+1.
55     ENDIF !oknondef(i,k)
56     c
57     ELSE IF(tlevSTD(i,k).NE.1E+20) THEN
58     tsumSTD(i,k,1)=tsumSTD(i,k,1)+tlevSTD(i,k)
59     tsumSTD(i,k,2)=tsumSTD(i,k,2)+tlevSTD(i,k)
60     ENDIF
61     ENDDO !i
62     ENDDO !k
63     c
64     c calcul variables toutes les 6h
65     c
66     IF(MOD(itap,ecrit_hf).EQ.0) THEN
67     c
68     DO k=1, nlevSTD
69     DO i=1, klon
70     IF(tlevSTD(i,k).EQ.1E+20) THEN
71     IF(oknondef(i,k,3)) THEN
72     tnondef(i,k,3)=tnondef(i,k,3)+1.
73     ENDIF !oknondef(i,k)
74     c
75     ELSE IF(tlevSTD(i,k).NE.1E+20) THEN
76     tsumSTD(i,k,3)=tsumSTD(i,k,3)+tlevSTD(i,k)
77     ENDIF
78     ENDDO !i
79     ENDDO !k
80    
81     ENDIF !MOD(itap,ecrit_hf).EQ.0
82     c
83     RETURN
84     END

  ViewVC Help
Powered by ViewVC 1.1.21