source: LMDZ6/branches/LMDZ-tracers/libf/dyn3d/qminimum.F @ 4350

Last change on this file since 4350 was 3852, checked in by dcugnet, 3 years ago

Extension of the tracers management.

The tracers files can be:

1) "traceur.def": old format, with:

  • the number of tracers on the first line
  • one line for each tracer: <tracer name> <hadv> <vadv> [<parent name>]

2) "tracer.def": new format with one section each model component.
3) "tracer_<name>.def": new format with a single section.

The formats 2 and 3 reading is driven by the "type_trac" key, which can be a

coma-separated list of components.

  • Format 2: read the sections from the "tracer.def" file.
  • format 3: read one section each "tracer_<section name>.def" file.
  • the first line of a section is "&<section name>
  • the other lines start with a tracer name followed by <key>=<val> pairs.
  • the "default" tracer name is reserved ; the other tracers of the section inherit its <key>=<val>, except for the keys that are redefined locally.

This format helps keeping the tracers files compact, thanks to the "default"
special tracer and the three levels of factorization:

  • on the tracers names: a tracer name can be a coma-separated list of tracers => all the tracers of the list have the same <key>=<val> properties
  • on the parents names: the value of the "parent" property can be a coma-separated list of tracers => only possible for geographic tagging tracers
  • on the phases: the property "phases" is [g](l][s] (gas/liquid/solid)

Read information is stored in the vector "tracers(:)", of derived type "tra".

"isotopes_params.def" is a similar file, with one section each isotopes family.
It contains a database of isotopes properties ; if there are second generation
tracers (isotopes), the corresponding sections are read.

Read information is stored in the vector "isotopes(:)", of derived type "iso".

The "getKey" function helps to get the values of the parameters stored in
"tracers" or "isotopes".

  • 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: 6.1 KB
Line 
1!
2! $Header$
3!
4      SUBROUTINE qminimum( q,nqtot,deltap )
5
6      USE infotrac, ONLY: niso, nitr, iTraPha
7      IMPLICIT none
8c
9c  -- Objet : Traiter les valeurs trop petites (meme negatives)
10c             pour l'eau vapeur et l'eau liquide
11c
12      include "dimensions.h"
13      include "paramet.h"
14c
15      INTEGER nqtot
16      REAL q(ip1jmp1,llm,nqtot), deltap(ip1jmp1,llm)
17c
18      INTEGER iq_vap, iq_liq
19      PARAMETER ( iq_vap = 1 ) ! indice pour l'eau vapeur
20      PARAMETER ( iq_liq = 2 ) ! indice pour l'eau liquide
21      REAL seuil_vap, seuil_liq
22      PARAMETER ( seuil_vap = 1.0e-10 ) ! seuil pour l'eau vapeur
23      PARAMETER ( seuil_liq = 1.0e-11 ) ! seuil pour l'eau liquide
24c
25c  NB. ....( Il est souhaitable mais non obligatoire que les valeurs des
26c            parametres seuil_vap, seuil_liq soient pareilles a celles
27c            qui  sont utilisees dans la routine    ADDFI       )
28c     .................................................................
29c
30      INTEGER i, k, iq
31      REAL zx_defau, zx_abc, zx_pump(ip1jmp1), pompe
32
33      real zx_defau_diag(ip1jmp1,llm,2)
34      real q_follow(ip1jmp1,llm,2)
35c
36      REAL SSUM
37c
38      INTEGER imprim
39      SAVE imprim
40      DATA imprim /0/
41      !INTEGER ijb,ije
42      !INTEGER Index_pump(ij_end-ij_begin+1)
43      !INTEGER nb_pump
44      INTEGER ixt
45c
46c Quand l'eau liquide est trop petite (ou negative), on prend
47c l'eau vapeur de la meme couche et la convertit en eau liquide
48c (sans changer la temperature !)
49c
50
51      call check_isotopes_seq(q,ip1jmp1,'qminimum 52')   
52
53      zx_defau_diag(:,:,:)=0.0
54      q_follow(:,:,1:2)=q(:,:,1:2) 
55      DO 1000 k = 1, llm
56        DO 1040 i = 1, ip1jmp1
57          if (seuil_liq - q(i,k,iq_liq) .gt. 0.d0 ) then
58
59              if (niso > 0) zx_defau_diag(i,k,iq_liq)=AMAX1
60     :               ( seuil_liq - q(i,k,iq_liq), 0.0 )
61
62             q(i,k,iq_vap) = q(i,k,iq_vap) + q(i,k,iq_liq) - seuil_liq
63             q(i,k,iq_liq) = seuil_liq
64           endif
65 1040   CONTINUE
66 1000 CONTINUE
67c
68c Quand l'eau vapeur est trop faible (ou negative), on complete
69c le defaut en prennant de l'eau vapeur de la couche au-dessous.
70c
71      iq = iq_vap
72c
73      DO k = llm, 2, -1
74ccc      zx_abc = dpres(k) / dpres(k-1)
75        DO i = 1, ip1jmp1
76          if ( seuil_vap - q(i,k,iq) .gt. 0.d0 ) then
77
78            zx_defau_diag(i,k,iq)=AMAX1( seuil_vap - q(i,k,iq), 0.0 )
79
80            q(i,k-1,iq) =  q(i,k-1,iq) - ( seuil_vap - q(i,k,iq) ) *
81     &                     deltap(i,k) / deltap(i,k-1)
82            q(i,k,iq)   =  seuil_vap 
83          endif
84        ENDDO
85      ENDDO
86c
87c Quand il s'agit de la premiere couche au-dessus du sol, on
88c doit imprimer un message d'avertissement (saturation possible).
89c
90      DO i = 1, ip1jmp1
91         zx_pump(i) = AMAX1( 0.0, seuil_vap - q(i,1,iq) )
92         q(i,1,iq)  = AMAX1( q(i,1,iq), seuil_vap )
93      ENDDO
94      pompe = SSUM(ip1jmp1,zx_pump,1)
95      IF (imprim.LE.500 .AND. pompe.GT.0.0) THEN
96         WRITE(6,'(1x,"ATT!:on pompe de l eau au sol",e15.7)') pompe
97         DO i = 1, ip1jmp1
98            IF (zx_pump(i).GT.0.0) THEN
99               imprim = imprim + 1
100               PRINT*,'QMINIMUM:  en ',i,zx_pump(i)
101            ENDIF
102         ENDDO
103      ENDIF
104
105      !write(*,*) 'qminimum 128'
106      if (niso > 0) then
107      ! CRisi: traiter de même les traceurs d'eau
108      ! Mais il faut les prendre à l'envers pour essayer de conserver la
109      ! masse.
110      ! 1) pompage dans le sol 
111      ! On suppose que ce pompage se fait sans isotopes -> on ne modifie
112      ! rien ici et on croise les doigts pour que ça ne soit pas trop
113      ! génant
114      DO i = 1,ip1jmp1
115        if (zx_pump(i).gt.0.0) then
116          q_follow(i,1,iq_vap)=q_follow(i,1,iq_vap)+zx_pump(i)
117        endif !if (zx_pump(i).gt.0.0) then
118      enddo !DO i = 1,ip1jmp1
119
120      ! 2) transfert de vap vers les couches plus hautes
121      !write(*,*) 'qminimum 139'
122      do k=2,llm
123        DO i = 1,ip1jmp1
124          if (zx_defau_diag(i,k,iq_vap).gt.0.0) then             
125              ! on ajoute la vapeur en k             
126              do ixt=1,nitr
127               q(i,k,iTraPha(ixt,iq_vap))=q(i,k,iTraPha(ixt,iq_vap))
128     :              +zx_defau_diag(i,k,iq_vap)
129     :              *q(i,k-1,iTraPha(ixt,iq_vap))/q_follow(i,k-1,iq_vap)
130               
131              ! et on la retranche en k-1
132               q(i,k-1,iTraPha(ixt,iq_vap))=q(i,k-1,iTraPha(ixt,iq_vap))
133     :              -zx_defau_diag(i,k,iq_vap)
134     :              *deltap(i,k)/deltap(i,k-1)
135     :              *q(i,k-1,iTraPha(ixt,iq_vap))/q_follow(i,k-1,iq_vap)
136
137              enddo !do ixt=1,nitr
138              q_follow(i,k,iq_vap)=   q_follow(i,k,iq_vap)
139     :               +zx_defau_diag(i,k,iq_vap)
140              q_follow(i,k-1,iq_vap)=   q_follow(i,k-1,iq_vap)
141     :               -zx_defau_diag(i,k,iq_vap)
142     :              *deltap(i,k)/deltap(i,k-1)
143          endif !if (zx_defau_diag(i,k,iq_vap).gt.0.0) then
144        enddo !DO i = 1, ip1jmp1       
145       enddo !do k=2,llm
146
147       call check_isotopes_seq(q,ip1jmp1,'qminimum 168')
148       
149     
150        ! 3) transfert d'eau de la vapeur au liquide
151        !write(*,*) 'qminimum 164'
152        do k=1,llm
153        DO i = 1,ip1jmp1
154          if (zx_defau_diag(i,k,iq_liq).gt.0.0) then
155
156              ! on ajoute eau liquide en k en k             
157              do ixt=1,nitr
158               q(i,k,iTraPha(ixt,iq_liq))=q(i,k,iTraPha(ixt,iq_liq))
159     :              +zx_defau_diag(i,k,iq_liq)
160     :              *q(i,k,iTraPha(ixt,iq_vap))/q_follow(i,k,iq_vap)
161              ! et on la retranche à la vapeur en k
162               q(i,k,iTraPha(ixt,iq_vap))=q(i,k,iTraPha(ixt,iq_vap))
163     :              -zx_defau_diag(i,k,iq_liq)
164     :              *q(i,k,iTraPha(ixt,iq_vap))/q_follow(i,k,iq_vap)   
165              enddo !do ixt=1,niso
166              q_follow(i,k,iq_liq)=   q_follow(i,k,iq_liq)
167     :               +zx_defau_diag(i,k,iq_liq)
168              q_follow(i,k,iq_vap)=   q_follow(i,k,iq_vap)
169     :               -zx_defau_diag(i,k,iq_liq)
170          endif !if (zx_defau_diag(i,k,iq_vap).gt.0.0) then
171        enddo !DO i = 1, ip1jmp1
172       enddo !do k=2,llm 
173
174       call check_isotopes_seq(q,ip1jmp1,'qminimum 197')
175
176      endif !if (niso > 0) then
177      !write(*,*) 'qminimum 188'
178     
179c
180      RETURN
181      END
Note: See TracBrowser for help on using the repository browser.