/[lmdze]/trunk/Sources/dyn3d/advtrac.f
ViewVC logotype

Annotation of /trunk/Sources/dyn3d/advtrac.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 178 - (hide annotations)
Fri Mar 11 18:47:26 2016 UTC (8 years, 2 months ago) by guez
File size: 4444 byte(s)
Moved variables date0, deltat, datasz_max, ncvar_ids, point, buff_pos,
buffer, regular from module histcom_var to modules where they are
defined.

Removed procedure ioipslmpp, useless for a sequential program.

Added argument datasz_max to histwrite_real (to avoid circular
dependency with histwrite).

Removed useless variables and computations everywhere.

Changed real litteral constants from default kind to double precision
in lwb, lwu, lwvn, sw1s, swtt, swtt1, swu.

Removed unused arguments: paer of sw, sw1s, sw2s, swclr; pcldsw of
sw1s, sw2s; pdsig, prayl of swr; co2_ppm of clmain, clqh; tsol of
transp_lay; nsrf of screenp; kcrit and kknu of gwstress; pstd of
orosetup.

Added output of relative humidity.

1 guez 40 module advtrac_m
2 guez 3
3 guez 40 IMPLICIT NONE
4 guez 3
5 guez 40 contains
6 guez 23
7 guez 40 SUBROUTINE advtrac(pbaru, pbarv, p, masse, q, iapptrac, teta, pk)
8 guez 3
9 guez 40 ! From dyn3d/advtrac.F, version 1.4 2005/04/13 08:58:34
10     ! Author: F. Hourdin
11 guez 3
12 guez 71 USE comconst, ONLY : dtvr
13     USE conf_gcm_m, ONLY : iapp_tracvl
14 guez 178 USE dimens_m, ONLY : jjm, llm, nqmx
15 guez 71 USE iniadvtrac_m, ONLY : iadv
16 guez 91 use massbar_m, only: massbar
17 guez 178 USE paramet_m, ONLY : iip1, iip2, ijmllm, ijp1llm, ip1jm, ip1jmp1, llmp1
18 guez 157 use vlsplt_m, only: vlsplt
19 guez 108 use vlspltqs_m, only: vlspltqs
20 guez 31
21 guez 71 REAL, intent(in):: pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
22     REAL, intent(in):: p(ip1jmp1, llmp1)
23     real, intent(in):: masse(ip1jmp1, llm)
24 guez 40 REAL, intent(inout):: q(ip1jmp1, llm, nqmx)
25 guez 71 INTEGER, intent(out):: iapptrac
26 guez 44 real, intent(in):: teta(ip1jmp1, llm)
27 guez 71 REAL, intent(in):: pk(ip1jmp1, llm)
28 guez 3
29 guez 40 ! Variables locales
30 guez 3
31 guez 40 REAL massebx(ip1jmp1, llm), masseby(ip1jm, llm)
32     REAL, save:: pbaruc(ip1jmp1, llm), pbarvc(ip1jm, llm)
33     REAL, save:: massem(ip1jmp1, llm)
34     real zdp(ip1jmp1)
35     REAL pbarug(ip1jmp1, llm), pbarvg(ip1jm, llm), wg(ip1jmp1, llm)
36 guez 31
37 guez 40 INTEGER:: iadvtr = 0
38     INTEGER ij, l, iq
39     REAL zdpmin, zdpmax
40     EXTERNAL minmax
41 guez 31
42 guez 40 INTEGER indice, n
43     ! Pas de temps adaptatif pour que CFL < 1
44     REAL dtbon
45 guez 3
46 guez 40 !-----------------------------------------------------------
47 guez 3
48 guez 40 IF (iadvtr==0) THEN
49     CALL initial0(ijp1llm, pbaruc)
50     CALL initial0(ijmllm, pbarvc)
51     END IF
52 guez 3
53 guez 40 ! accumulation des flux de masse horizontaux
54     DO l = 1, llm
55     DO ij = 1, ip1jmp1
56     pbaruc(ij, l) = pbaruc(ij, l) + pbaru(ij, l)
57     END DO
58     DO ij = 1, ip1jm
59     pbarvc(ij, l) = pbarvc(ij, l) + pbarv(ij, l)
60     END DO
61     END DO
62 guez 3
63 guez 40 ! selection de la masse instantannee des mailles avant le transport.
64 guez 71 IF (iadvtr==0) massem = masse
65 guez 3
66 guez 40 iadvtr = iadvtr + 1
67     iapptrac = iadvtr
68 guez 3
69 guez 40 ! Test pour savoir si on advecte a ce pas de temps
70 guez 71 IF (iadvtr == iapp_tracvl) THEN
71 guez 40 ! traitement des flux de masse avant advection.
72     ! 1. calcul de w
73     ! 2. groupement des mailles pres du pole.
74 guez 3
75 guez 150 CALL groupe(pbaruc, pbarvc, pbarug, pbarvg, wg)
76 guez 3
77 guez 40 ! test sur l'eventuelle creation de valeurs negatives de la masse
78     DO l = 1, llm - 1
79     DO ij = iip2 + 1, ip1jm
80     zdp(ij) = pbarug(ij-1, l) - pbarug(ij, l) - pbarvg(ij-iip1, l) + &
81     pbarvg(ij, l) + wg(ij, l+1) - wg(ij, l)
82     END DO
83     CALL scopy(jjm-1, zdp(iip1+iip1), iip1, zdp(iip2), iip1)
84     DO ij = iip2, ip1jm
85     zdp(ij) = zdp(ij)*dtvr/massem(ij, l)
86     END DO
87 guez 3
88 guez 40 CALL minmax(ip1jm-iip1, zdp(iip2), zdpmin, zdpmax)
89 guez 3
90 guez 40 IF (max(abs(zdpmin), abs(zdpmax))>0.5) THEN
91     PRINT *, 'WARNING DP/P l=', l, ' MIN:', zdpmin, ' MAX:', zdpmax
92     END IF
93     END DO
94 guez 3
95 guez 40 ! Advection proprement dite
96 guez 3
97 guez 150 ! Calcul des moyennes bas\'ees sur la masse
98 guez 40 CALL massbar(massem, massebx, masseby)
99 guez 31
100 guez 40 ! Appel des sous programmes d'advection
101 guez 31
102 guez 40 DO iq = 1, nqmx
103 guez 157 select case (iadv(iq))
104     case (10)
105     ! Schema de Van Leer I MUSCL
106 guez 40 CALL vlsplt(q(:, :, iq), 2., massem, wg, pbarug, pbarvg, dtvr)
107 guez 177 case (12)
108 guez 40 ! Schema de Frederic Hourdin
109     ! Pas de temps adaptatif
110 guez 104 CALL adaptdt(dtbon, n, pbarug, massem)
111 guez 40 IF (n>1) THEN
112     WRITE (*, *) 'WARNING horizontal dt=', dtbon, 'dtvr=', dtvr, &
113     'n=', n
114     END IF
115     DO indice = 1, n
116     CALL advn(q(1, 1, iq), massem, wg, pbarug, pbarvg, dtbon, 1)
117     END DO
118 guez 157 case (13)
119 guez 40 ! Pas de temps adaptatif
120 guez 104 CALL adaptdt(dtbon, n, pbarug, massem)
121 guez 40 IF (n>1) THEN
122     WRITE (*, *) 'WARNING horizontal dt=', dtbon, 'dtvr=', dtvr, &
123     'n=', n
124     END IF
125     DO indice = 1, n
126     CALL advn(q(1, 1, iq), massem, wg, pbarug, pbarvg, dtbon, 2)
127     END DO
128 guez 177 case (14)
129     ! Schema "pseudo amont" + test sur humidite specifique
130     ! pour la vapeur d'eau. F. Codron
131     CALL vlspltqs(q(1, 1, 1), 2., massem, wg, pbarug, pbarvg, dtvr, &
132     p, pk, teta)
133 guez 157 END select
134 guez 40 END DO
135 guez 3
136 guez 40 ! on reinitialise a zero les flux de masse cumules
137     iadvtr = 0
138     END IF
139    
140     END SUBROUTINE advtrac
141    
142     end module advtrac_m

  ViewVC Help
Powered by ViewVC 1.1.21