source: LMDZ6/branches/Amaury_dev/libf/phylmd/dyn1d/lmdz_old_1dconv.f90 @ 5117

Last change on this file since 5117 was 5117, checked in by abarral, 3 months ago

rename modules properly lmdz_*
move some unused files to obsolete/
(lint) uppercase fortran keywords

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 31.0 KB
Line 
1MODULE lmdz_old_1dconv
2  IMPLICIT NONE; PRIVATE
3  PUBLIC get_uvd, copie
4CONTAINS
5
6  subroutine get_uvd(itap, dtime, file_forctl, file_fordat, &
7          &       ht, hq, hw, hu, hv, hthturb, hqturb, &
8          &       Ts, imp_fcg, ts_fcg, Tp_fcg, Turb_fcg)
9
10    IMPLICIT NONE
11
12    !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
13    ! cette routine permet d obtenir u_convg,v_convg,ht,hq et ainsi de
14    ! pouvoir calculer la convergence et le cisaillement dans la physiq
15    !cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
16
17    INCLUDE "YOMCST.h"
18
19    INTEGER klev
20    REAL play(100)  !pression en Pa au milieu de chaque couche GCM
21    INTEGER JM(100) !pression en Pa au milieu de chaque couche GCM
22    REAL coef1(100) !coefficient d interpolation
23    REAL coef2(100) !coefficient d interpolation
24
25    INTEGER nblvlm !nombre de niveau de pression du mesoNH
26    REAL playm(100)  !pression en Pa au milieu de chaque couche Meso-NH
27    REAL hplaym(100) !pression en hPa milieux des couches Meso-NH
28
29    INTEGER i, j, k, ll, in
30
31    CHARACTER*80 file_forctl, file_fordat
32
33    COMMON/com1_phys_gcss/play, coef1, coef2, JM, klev
34    COMMON/com2_phys_gcss/playm, hplaym, nblvlm
35
36    !======================================================================
37    ! methode: on va chercher les donnees du mesoNH de meteo france, on y
38    !          a acces a tout pas detemps grace a la routine rdgrads qui
39    !          est une boucle lisant dans ces fichiers.
40    !          Puis on interpole ces donnes sur les 11 niveaux du gcm et
41    !          et sur les pas de temps de ce meme gcm
42    !----------------------------------------------------------------------
43    ! input:
44    !       pasmax     :nombre de pas de temps maximum du mesoNH
45    !       dt         :pas de temps du meso_NH (en secondes)
46    !----------------------------------------------------------------------
47    INTEGER pasmax, dt
48    save pasmax, dt
49    !----------------------------------------------------------------------
50    ! arguments:
51    !           itap   :compteur de la physique(le nombre de ces pas est
52    !                   fixe dans la subroutine calcul_ini_gcm de interpo
53    !                   -lation
54    !           dtime  :pas detemps du gcm (en secondes)
55    !           ht     :convergence horizontale de temperature(K/s)
56    !           hq     :    "         "       d humidite (kg/kg/s)
57    !           hw     :vitesse verticale moyenne (m/s**2)
58    !           hu     :convergence horizontale d impulsion le long de x
59    !                  (kg/(m^2 s^2)
60    !           hv     : idem le long de y.
61    !           Ts     : Temperature de surface (K)
62    !           imp_fcg: var. LOGICAL .EQ. T si forcage en impulsion
63    !           ts_fcg: var. LOGICAL .EQ. T si forcage en Ts present dans fichier
64    !           Tp_fcg: var. LOGICAL .EQ. T si forcage donne en Temp potentielle
65    !           Turb_fcg: var. LOGICAL .EQ. T si forcage turbulent present dans fichier
66    !----------------------------------------------------------------------
67    INTEGER itap
68    REAL dtime
69    REAL ht(100)
70    REAL hq(100)
71    REAL hu(100)
72    REAL hv(100)
73    REAL hw(100)
74    REAL hthturb(100)
75    REAL hqturb(100)
76    REAL Ts, Ts_subr
77    LOGICAL imp_fcg
78    LOGICAL ts_fcg
79    LOGICAL Tp_fcg
80    LOGICAL Turb_fcg
81    !----------------------------------------------------------------------
82    ! Variables internes de get_uvd (note : l interpolation temporelle
83    ! est faite entre les pas de temps before et after, sur les variables
84    ! definies sur la grille du SCM; on atteint exactement les valeurs Meso
85    ! aux milieux des pas de temps Meso)
86    !     time0     :date initiale en secondes
87    !     time      :temps associe a chaque pas du SCM
88    !     pas       :numero du pas du meso_NH (on lit en pas : le premier pas
89    !                 des donnees est duplique)
90    !     pasprev   :numero du pas de lecture precedent
91    !     htaft     :advection horizontale de temp. au pas de temps after
92    !     hqaft     :    "         "      d humidite        "
93    !     hwaft     :vitesse verticalle moyenne  au pas de temps after
94    !     huaft,hvaft :advection horizontale d impulsion au pas de temps after
95    !     tsaft     : surface temperature 'after time step'
96    !     htbef     :idem htaft, mais pour le pas de temps before
97    !     hqbef     :voir hqaft
98    !     hwbef     :voir hwaft
99    !     hubef,hvbef : idem huaft,hvaft, mais pour before
100    !     tsbef     : surface temperature 'before time step'
101    !----------------------------------------------------------------------
102    INTEGER time0, pas, pasprev
103    save time0, pas, pasprev
104    REAL time
105    REAL htaft(100), hqaft(100), hwaft(100), huaft(100), hvaft(100)
106    REAL hthturbaft(100), hqturbaft(100)
107    REAL Tsaft
108    save htaft, hqaft, hwaft, huaft, hvaft, hthturbaft, hqturbaft
109    REAL htbef(100), hqbef(100), hwbef(100), hubef(100), hvbef(100)
110    REAL hthturbbef(100), hqturbbef(100)
111    REAL Tsbef
112    save htbef, hqbef, hwbef, hubef, hvbef, hthturbbef, hqturbbef
113
114    REAL timeaft, timebef
115    save timeaft, timebef
116    INTEGER temps
117    character*4 string
118    !----------------------------------------------------------------------
119    ! variables arguments de la subroutine rdgrads
120    !---------------------------------------------------------------------
121    INTEGER icompt, icomp1 !compteurs de rdgrads
122    REAL z(100)         ! altitude (grille Meso)
123    REAL ht_mes(100)    !convergence horizontale de temperature
124    !-(grille Meso)
125    REAL hq_mes(100)    !convergence horizontale d humidite
126    !(grille Meso)
127    REAL hw_mes(100)    !vitesse verticale moyenne
128    !(grille Meso)
129    REAL hu_mes(100), hv_mes(100)    !convergence horizontale d impulsion
130    !(grille Meso)
131    REAL hthturb_mes(100) !tendance horizontale de T_pot, due aux
132    !flux turbulents
133    REAL hqturb_mes(100) !tendance horizontale d humidite, due aux
134    !flux turbulents
135
136    !---------------------------------------------------------------------
137    ! variable argument de la subroutine copie
138    !---------------------------------------------------------------------
139    ! SB        real pplay(100)    !pression en milieu de couche du gcm
140    ! SB                            !argument de la physique
141    !---------------------------------------------------------------------
142    ! variables destinees a la lecture du pas de temps du fichier de donnees
143    !---------------------------------------------------------------------
144    character*80 aaa, atemps, spaces, apasmax
145    INTEGER nch, imn, ipa
146    !---------------------------------------------------------------------
147    !  procedures appelees
148    external rdgrads    !lire en iterant dans forcing.dat
149    !---------------------------------------------------------------------
150    PRINT*, 'le pas itap est:', itap
151    !*** on determine le pas du meso_NH correspondant au nouvel itap ***
152    !*** pour aller chercher les champs dans rdgrads                 ***
153
154    time = time0 + itap * dtime
155    !c        temps=int(time/dt+1)
156    !c        pas=min(temps,pasmax)
157    temps = 1 + int((dt + 2 * time) / (2 * dt))
158    pas = min(temps, pasmax - 1)
159    PRINT*, 'le pas Meso est:', pas
160
161
162    !===================================================================
163
164    !*** on remplit les champs before avec les champs after du pas   ***
165    !*** precedent en format gcm                                     ***
166    IF(pas>pasprev)THEN
167      do i = 1, klev
168        htbef(i) = htaft(i)
169        hqbef(i) = hqaft(i)
170        hwbef(i) = hwaft(i)
171        hubef(i) = huaft(i)
172        hvbef(i) = hvaft(i)
173        hThTurbbef(i) = hThTurbaft(i)
174        hqTurbbef(i) = hqTurbaft(i)
175      enddo
176      tsbef = tsaft
177      timebef = pasprev * dt
178      timeaft = timebef + dt
179      icomp1 = nblvlm * 4
180      IF (ts_fcg) icomp1 = icomp1 + 1
181      IF (imp_fcg) icomp1 = icomp1 + nblvlm * 2
182      IF (Turb_fcg) icomp1 = icomp1 + nblvlm * 2
183      icompt = icomp1 * pas
184      print *, 'imp_fcg,ts_fcg,Turb_fcg,pas,nblvlm,icompt'
185      print *, imp_fcg, ts_fcg, Turb_fcg, pas, nblvlm, icompt
186      PRINT*, 'le pas pas est:', pas
187      !*** on va chercher les nouveaux champs after dans toga.dat     ***
188      !*** champs en format meso_NH                                   ***
189      open(99, FILE = file_fordat, FORM = 'UNFORMATTED', &
190              &             ACCESS = 'DIRECT', RECL = 8)
191      CALL rdgrads(99, icompt, nblvlm, z, ht_mes, hq_mes, hw_mes                &
192              &, hu_mes, hv_mes, hthturb_mes, hqturb_mes                 &
193              &, ts_fcg, ts_subr, imp_fcg, Turb_fcg)
194
195      IF(Tp_fcg) THEN
196        !     (le forcage est donne en temperature potentielle)
197        do i = 1, nblvlm
198          ht_mes(i) = ht_mes(i) * (hplaym(i) / 1000.)**rkappa
199        enddo
200      endif ! Tp_fcg
201      IF(Turb_fcg) THEN
202        do i = 1, nblvlm
203          hThTurb_mes(i) = hThTurb_mes(i) * (hplaym(i) / 1000.)**rkappa
204        enddo
205      endif  ! Turb_fcg
206
207      PRINT*, 'ht_mes ', (ht_mes(i), i = 1, nblvlm)
208      PRINT*, 'hq_mes ', (hq_mes(i), i = 1, nblvlm)
209      PRINT*, 'hw_mes ', (hw_mes(i), i = 1, nblvlm)
210      IF(imp_fcg) THEN
211        PRINT*, 'hu_mes ', (hu_mes(i), i = 1, nblvlm)
212        PRINT*, 'hv_mes ', (hv_mes(i), i = 1, nblvlm)
213      endif
214      IF(Turb_fcg) THEN
215        PRINT*, 'hThTurb_mes ', (hThTurb_mes(i), i = 1, nblvlm)
216        PRINT*, 'hqTurb_mes ', (hqTurb_mes(i), i = 1, nblvlm)
217      endif
218      IF (ts_fcg) PRINT*, 'ts_subr', ts_subr
219      !*** on interpole les champs meso_NH sur les niveaux de pression***
220      !*** gcm . on obtient le nouveau champ after                    ***
221      do k = 1, klev
222        IF (JM(k) == 0) THEN
223          htaft(k) = ht_mes(jm(k) + 1)
224          hqaft(k) = hq_mes(jm(k) + 1)
225          hwaft(k) = hw_mes(jm(k) + 1)
226          IF(imp_fcg) THEN
227            huaft(k) = hu_mes(jm(k) + 1)
228            hvaft(k) = hv_mes(jm(k) + 1)
229          endif ! imp_fcg
230          IF(Turb_fcg) THEN
231            hThTurbaft(k) = hThTurb_mes(jm(k) + 1)
232            hqTurbaft(k) = hqTurb_mes(jm(k) + 1)
233          endif ! Turb_fcg
234        else ! JM(k) .EQ. 0
235          htaft(k) = coef1(k) * ht_mes(jm(k)) + coef2(k) * ht_mes(jm(k) + 1)
236          hqaft(k) = coef1(k) * hq_mes(jm(k)) + coef2(k) * hq_mes(jm(k) + 1)
237          hwaft(k) = coef1(k) * hw_mes(jm(k)) + coef2(k) * hw_mes(jm(k) + 1)
238          IF(imp_fcg) THEN
239            huaft(k) = coef1(k) * hu_mes(jm(k)) + coef2(k) * hu_mes(jm(k) + 1)
240            hvaft(k) = coef1(k) * hv_mes(jm(k)) + coef2(k) * hv_mes(jm(k) + 1)
241          endif ! imp_fcg
242          IF(Turb_fcg) THEN
243            hThTurbaft(k) = coef1(k) * hThTurb_mes(jm(k))                            &
244                    & + coef2(k) * hThTurb_mes(jm(k) + 1)
245            hqTurbaft(k) = coef1(k) * hqTurb_mes(jm(k))                             &
246                    & + coef2(k) * hqTurb_mes(jm(k) + 1)
247          endif ! Turb_fcg
248        endif ! JM(k) .EQ. 0
249      enddo
250      tsaft = ts_subr
251      pasprev = pas
252    else ! pas.gt.pasprev
253      PRINT*, 'timebef est:', timebef
254    endif ! pas.gt.pasprev    fin du bloc relatif au passage au pas
255    !de temps (meso) suivant
256    !*** si on atteint le pas max des donnees experimentales ,on     ***
257    !*** on conserve les derniers champs calcules                    ***
258    IF(temps>=pasmax)THEN
259      do ll = 1, klev
260        ht(ll) = htaft(ll)
261        hq(ll) = hqaft(ll)
262        hw(ll) = hwaft(ll)
263        hu(ll) = huaft(ll)
264        hv(ll) = hvaft(ll)
265        hThTurb(ll) = hThTurbaft(ll)
266        hqTurb(ll) = hqTurbaft(ll)
267      enddo
268      ts_subr = tsaft
269    else ! temps.ge.pasmax
270      !*** on interpole sur les pas de temps de 10mn du gcm a partir   ***
271      !** des pas de temps de 1h du meso_NH                            ***
272      do j = 1, klev
273        ht(j) = ((timeaft - time) * htbef(j) + (time - timebef) * htaft(j)) / dt
274        hq(j) = ((timeaft - time) * hqbef(j) + (time - timebef) * hqaft(j)) / dt
275        hw(j) = ((timeaft - time) * hwbef(j) + (time - timebef) * hwaft(j)) / dt
276        IF(imp_fcg) THEN
277          hu(j) = ((timeaft - time) * hubef(j) + (time - timebef) * huaft(j)) / dt
278          hv(j) = ((timeaft - time) * hvbef(j) + (time - timebef) * hvaft(j)) / dt
279        endif ! imp_fcg
280        IF(Turb_fcg) THEN
281          hThTurb(j) = ((timeaft - time) * hThTurbbef(j)                           &
282                  & + (time - timebef) * hThTurbaft(j)) / dt
283          hqTurb(j) = ((timeaft - time) * hqTurbbef(j)                            &
284                  & + (time - timebef) * hqTurbaft(j)) / dt
285        endif ! Turb_fcg
286      enddo
287      ts_subr = ((timeaft - time) * tsbef + (time - timebef) * tsaft) / dt
288    endif ! temps.ge.pasmax
289
290    print *, ' time,timebef,timeaft', time, timebef, timeaft
291    print *, ' ht,htbef,htaft,hthturb,hthturbbef,hthturbaft'
292    do j = 1, klev
293      print *, j, ht(j), htbef(j), htaft(j), &
294              &             hthturb(j), hthturbbef(j), hthturbaft(j)
295    enddo
296    print *, ' hq,hqbef,hqaft,hqturb,hqturbbef,hqturbaft'
297    do j = 1, klev
298      print *, j, hq(j), hqbef(j), hqaft(j), &
299              &             hqturb(j), hqturbbef(j), hqturbaft(j)
300    enddo
301
302    !-------------------------------------------------------------------
303
304    IF (Ts_fcg) Ts = Ts_subr
305    return
306
307    !-----------------------------------------------------------------------
308    ! on sort les champs de "convergence" pour l instant initial 'in'
309    ! ceci se passe au pas temps itap=0 de la physique
310    !-----------------------------------------------------------------------
311    entry get_uvd2(itap, dtime, file_forctl, file_fordat, &
312            &           ht, hq, hw, hu, hv, hThTurb, hqTurb, ts, &
313            &           imp_fcg, ts_fcg, Tp_fcg, Turb_fcg)
314    PRINT*, 'le pas itap est:', itap
315
316    !===================================================================
317
318    WRITE(*, '(a)') 'OPEN ' // file_forctl
319    open(97, FILE = file_forctl, FORM = 'FORMATTED')
320
321    !------------------
322    do i = 1, 1000
323      read(97, 1000, end = 999) string
324      1000 format (a4)
325      IF (string == 'TDEF') go to 50
326    enddo
327    50   backspace(97)
328    !-------------------------------------------------------------------
329    !   *** on lit le pas de temps dans le fichier de donnees ***
330    !   *** "forcing.ctl" et pasmax                           ***
331    !-------------------------------------------------------------------
332    read(97, 2000) aaa
333    2000  format (a80)
334    PRINT*, 'aaa est', aaa
335    aaa = spaces(aaa, 1)
336    PRINT*, 'aaa', aaa
337    CALL getsch(aaa, ' ', ' ', 5, atemps, nch)
338    PRINT*, 'atemps est', atemps
339    atemps = atemps(1:nch - 2)
340    PRINT*, 'atemps', atemps
341    read(atemps, *) imn
342    dt = imn * 60
343    PRINT*, 'le pas de temps dt', dt
344    CALL getsch(aaa, ' ', ' ', 2, apasmax, nch)
345    apasmax = apasmax(1:nch)
346    read(apasmax, *) ipa
347    pasmax = ipa
348    PRINT*, 'pasmax est', pasmax
349    CLOSE(97)
350    !------------------------------------------------------------------
351    ! *** on lit le pas de temps initial de la simulation ***
352    !------------------------------------------------------------------
353    in = itap
354    !c                  pasprev=in
355    !c                  time0=dt*(pasprev-1)
356    pasprev = in - 1
357    time0 = dt * pasprev
358
359    close(98)
360
361    WRITE(*, '(a)') 'OPEN ' // file_fordat
362    open(99, FILE = file_fordat, FORM = 'UNFORMATTED', ACCESS = 'DIRECT', RECL = 8)
363    icomp1 = nblvlm * 4
364    IF (ts_fcg) icomp1 = icomp1 + 1
365    IF (imp_fcg) icomp1 = icomp1 + nblvlm * 2
366    IF (Turb_fcg) icomp1 = icomp1 + nblvlm * 2
367    icompt = icomp1 * (in - 1)
368    CALL rdgrads(99, icompt, nblvlm, z, ht_mes, hq_mes, hw_mes              &
369            &, hu_mes, hv_mes, hthturb_mes, hqturb_mes              &
370            &, ts_fcg, ts_subr, imp_fcg, Turb_fcg)
371    print *, 'get_uvd : rdgrads ->'
372    print *, tp_fcg
373
374    ! following commented out because we have temperature already in ARM case
375    !   (otherwise this is the potential temperature )
376    !------------------------------------------------------------------------
377    IF(Tp_fcg) THEN
378      do i = 1, nblvlm
379        ht_mes(i) = ht_mes(i) * (hplaym(i) / 1000.)**rkappa
380      enddo
381    endif ! Tp_fcg
382    PRINT*, 'ht_mes ', (ht_mes(i), i = 1, nblvlm)
383    PRINT*, 'hq_mes ', (hq_mes(i), i = 1, nblvlm)
384    PRINT*, 'hw_mes ', (hw_mes(i), i = 1, nblvlm)
385    IF(imp_fcg) THEN
386      PRINT*, 'hu_mes ', (hu_mes(i), i = 1, nblvlm)
387      PRINT*, 'hv_mes ', (hv_mes(i), i = 1, nblvlm)
388      PRINT*, 't', ts_subr
389    endif ! imp_fcg
390    IF(Turb_fcg) THEN
391      PRINT*, 'hThTurb_mes ', (hThTurb_mes(i), i = 1, nblvlm)
392      PRINT*, 'hqTurb ', (hqTurb_mes(i), i = 1, nblvlm)
393    endif ! Turb_fcg
394    !----------------------------------------------------------------------
395    ! on a obtenu des champs initiaux sur les niveaux du meso_NH
396    ! on interpole sur les niveaux du gcm(niveau pression bien sur!)
397    !-----------------------------------------------------------------------
398    do k = 1, klev
399      IF (JM(k) == 0) THEN
400        !FKC bug? ne faut il pas convertir tsol en tendance ????
401        !RT bug taken care of by removing the stuff
402        htaft(k) = ht_mes(jm(k) + 1)
403        hqaft(k) = hq_mes(jm(k) + 1)
404        hwaft(k) = hw_mes(jm(k) + 1)
405        IF(imp_fcg) THEN
406          huaft(k) = hu_mes(jm(k) + 1)
407          hvaft(k) = hv_mes(jm(k) + 1)
408        endif ! imp_fcg
409        IF(Turb_fcg) THEN
410          hThTurbaft(k) = hThTurb_mes(jm(k) + 1)
411          hqTurbaft(k) = hqTurb_mes(jm(k) + 1)
412        endif ! Turb_fcg
413      else ! JM(k) .EQ. 0
414        htaft(k) = coef1(k) * ht_mes(jm(k)) + coef2(k) * ht_mes(jm(k) + 1)
415        hqaft(k) = coef1(k) * hq_mes(jm(k)) + coef2(k) * hq_mes(jm(k) + 1)
416        hwaft(k) = coef1(k) * hw_mes(jm(k)) + coef2(k) * hw_mes(jm(k) + 1)
417        IF(imp_fcg) THEN
418          huaft(k) = coef1(k) * hu_mes(jm(k)) + coef2(k) * hu_mes(jm(k) + 1)
419          hvaft(k) = coef1(k) * hv_mes(jm(k)) + coef2(k) * hv_mes(jm(k) + 1)
420        endif ! imp_fcg
421        IF(Turb_fcg) THEN
422          hThTurbaft(k) = coef1(k) * hThTurb_mes(jm(k))                        &
423                  & + coef2(k) * hThTurb_mes(jm(k) + 1)
424          hqTurbaft(k) = coef1(k) * hqTurb_mes(jm(k))                         &
425                  & + coef2(k) * hqTurb_mes(jm(k) + 1)
426        endif ! Turb_fcg
427      endif ! JM(k) .EQ. 0
428    enddo
429    tsaft = ts_subr
430    ! valeurs initiales des champs de convergence
431    do k = 1, klev
432      ht(k) = htaft(k)
433      hq(k) = hqaft(k)
434      hw(k) = hwaft(k)
435      IF(imp_fcg) THEN
436        hu(k) = huaft(k)
437        hv(k) = hvaft(k)
438      endif ! imp_fcg
439      IF(Turb_fcg) THEN
440        hThTurb(k) = hThTurbaft(k)
441        hqTurb(k) = hqTurbaft(k)
442      endif ! Turb_fcg
443    enddo
444    ts_subr = tsaft
445    close(99)
446    close(98)
447
448    !-------------------------------------------------------------------
449
450    IF (Ts_fcg) Ts = Ts_subr
451    return
452
453    999     continue
454    stop 'erreur lecture, file forcing.ctl'
455  end
456
457  SUBROUTINE advect_tvl(dtime, zt, zq, vu_f, vv_f, t_f, q_f                   &
458          &, d_t_adv, d_q_adv)
459    USE dimphy
460    IMPLICIT NONE
461
462    INCLUDE "dimensions.h"
463    !cccc      INCLUDE "dimphy.h"
464
465    INTEGER k
466    REAL dtime, fact, du, dv, cx, cy, alx, aly
467    REAL zt(klev), zq(klev, 3)
468    REAL vu_f(klev), vv_f(klev), t_f(klev), q_f(klev, 3)
469
470    REAL d_t_adv(klev), d_q_adv(klev, 3)
471
472    ! Velocity of moving cell
473    data cx, cy /12., -2./
474
475    ! Dimensions of moving cell
476    data alx, aly /100000., 150000./
477
478    do k = 1, klev
479      du = abs(vu_f(k) - cx) / alx
480      dv = abs(vv_f(k) - cy) / aly
481      fact = dtime * (du + dv - du * dv * dtime)
482      d_t_adv(k) = fact * (t_f(k) - zt(k))
483      d_q_adv(k, 1) = fact * (q_f(k, 1) - zq(k, 1))
484      d_q_adv(k, 2) = fact * (q_f(k, 2) - zq(k, 2))
485      d_q_adv(k, 3) = fact * (q_f(k, 3) - zq(k, 3))
486    enddo
487
488    RETURN
489  end
490
491  SUBROUTINE copie(klevgcm, playgcm, psolgcm, file_forctl)
492    IMPLICIT NONE
493
494    !cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
495    ! cette routine remplit les COMMON com1_phys_gcss et com2_phys_gcss.h
496    !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
497
498    INTEGER klev !nombre de niveau de pression du GCM
499    REAL play(100)  !pression en Pa au milieu de chaque couche GCM
500    INTEGER JM(100)
501    REAL coef1(100)   !coefficient d interpolation
502    REAL coef2(100)   !coefficient d interpolation
503
504    INTEGER nblvlm !nombre de niveau de pression du mesoNH
505    REAL playm(100) !pression en Pa au milieu de chaque couche Meso-NH
506    REAL hplaym(100)!pression en hecto-Pa des milieux de couche Meso-NH
507
508    COMMON/com1_phys_gcss/play, coef1, coef2, JM, klev
509    COMMON/com2_phys_gcss/playm, hplaym, nblvlm
510
511    INTEGER k, klevgcm
512    REAL playgcm(klevgcm) ! pression en milieu de couche du gcm
513    REAL psolgcm
514    character*80 file_forctl
515
516    klev = klevgcm
517
518    !---------------------------------------------------------------------
519    ! pression au milieu des couches du gcm dans la physiq
520    ! (SB: remplace le CALL conv_lipress_gcm(playgcm) )
521    !---------------------------------------------------------------------
522
523    do k = 1, klev
524      play(k) = playgcm(k)
525      PRINT*, 'la pression gcm est:', play(k)
526    enddo
527
528    !----------------------------------------------------------------------
529    ! lecture du descripteur des donnees Meso-NH (forcing.ctl):
530    !  -> nb niveaux du meso.NH (nblvlm) + pressions meso.NH
531    ! (on remplit le COMMON com2_phys_gcss)
532    !----------------------------------------------------------------------
533
534    CALL mesolupbis(file_forctl)
535
536    PRINT*, 'la valeur de nblvlm est:', nblvlm
537
538    !----------------------------------------------------------------------
539    ! etude de la correspondance entre les niveaux meso.NH et GCM;
540    ! calcul des coefficients d interpolation coef1 et coef2
541    ! (on remplit le COMMON com1_phys_gcss)
542    !----------------------------------------------------------------------
543
544    CALL corresbis(psolgcm)
545
546    !---------------------------------------------------------
547    ! TEST sur le remplissage de com1_phys_gcss et com2_phys_gcss:
548    !---------------------------------------------------------
549
550    WRITE(*, *) ' '
551    WRITE(*, *) 'TESTS com1_phys_gcss et com2_phys_gcss dans copie.F'
552    WRITE(*, *) '--------------------------------------'
553    WRITE(*, *) 'GCM: nb niveaux:', klev, ' et pression, coeffs:'
554    do k = 1, klev
555      WRITE(*, *) play(k), coef1(k), coef2(k)
556    enddo
557    WRITE(*, *) 'MESO-NH: nb niveaux:', nblvlm, ' et pression:'
558    do k = 1, nblvlm
559      WRITE(*, *) playm(k), hplaym(k)
560    enddo
561    WRITE(*, *) ' '
562
563  end
564  SUBROUTINE mesolupbis(file_forctl)
565    !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
566
567    ! Lecture descripteur des donnees MESO-NH (forcing.ctl):
568    ! -------------------------------------------------------
569
570    !     Cette subroutine lit dans le fichier de controle "essai.ctl"
571    !     et affiche le nombre de niveaux du Meso-NH ainsi que les valeurs
572    !     des pressions en milieu de couche du Meso-NH (en Pa puis en hPa).
573    !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
574
575    INTEGER nblvlm !nombre de niveau de pression du mesoNH
576    REAL playm(100)  !pression en Pa milieu de chaque couche Meso-NH
577    REAL hplaym(100) !pression en hPa des milieux de couche Meso-NH
578    COMMON/com2_phys_gcss/playm, hplaym, nblvlm
579
580    INTEGER i, lu, mlz, mlzh
581
582    character*80 file_forctl
583
584    character*4 a
585    character*80 aaa, anblvl, spaces
586    INTEGER nch
587
588    lu = 9
589    open(lu, file = file_forctl, form = 'formatted')
590
591    do i = 1, 1000
592      read(lu, 1000, end = 999) a
593      IF (a == 'ZDEF') go to 100
594    enddo
595
596    100  backspace(lu)
597    PRINT*, '  DESCRIPTION DES 2 MODELES : '
598    PRINT*, ' '
599
600    read(lu, 2000) aaa
601    2000  format (a80)
602    aaa = spaces(aaa, 1)
603    CALL getsch(aaa, ' ', ' ', 2, anblvl, nch)
604    read(anblvl, *) nblvlm
605
606    PRINT*, 'nbre de niveaux de pression Meso-NH :', nblvlm
607    PRINT*, ' '
608    PRINT*, 'pression en Pa de chaque couche du meso-NH :'
609
610    read(lu, *) (playm(mlz), mlz = 1, nblvlm)
611    !      Si la pression est en HPa, la multiplier par 100
612    IF (playm(1) < 10000.) THEN
613      do mlz = 1, nblvlm
614        playm(mlz) = playm(mlz) * 100.
615      enddo
616    endif
617    PRINT*, (playm(mlz), mlz = 1, nblvlm)
618
619    1000 format (a4)
620
621    PRINT*, ' '
622    do mlzh = 1, nblvlm
623      hplaym(mlzh) = playm(mlzh) / 100.
624    enddo
625
626    PRINT*, 'pression en hPa de chaque couche du meso-NH: '
627    PRINT*, (hplaym(mlzh), mlzh = 1, nblvlm)
628
629    close (lu)
630    return
631
632    999  stop 'erreur lecture des niveaux pression des donnees'
633  end
634
635  SUBROUTINE rdgrads(itape, icount, nl, z, ht, hq, hw, hu, hv, hthtur, hqtur, &
636          &  ts_fcg, ts, imp_fcg, Turb_fcg)
637    IMPLICIT none
638    INTEGER itape, icount, icomp, nl
639    REAL z(nl), ht(nl), hq(nl), hw(nl), hu(nl), hv(nl)
640    REAL hthtur(nl), hqtur(nl)
641    REAL ts
642
643    INTEGER k
644
645    LOGICAL imp_fcg, ts_fcg, Turb_fcg
646
647    icomp = icount
648
649    do k = 1, nl
650      icomp = icomp + 1
651      read(itape, rec = icomp)z(k)
652      print *, 'icomp,k,z(k) ', icomp, k, z(k)
653    enddo
654    do k = 1, nl
655      icomp = icomp + 1
656      read(itape, rec = icomp)hT(k)
657      PRINT*, hT(k), k
658    enddo
659    do k = 1, nl
660      icomp = icomp + 1
661      read(itape, rec = icomp)hQ(k)
662    enddo
663
664    IF(turb_fcg) THEN
665      do k = 1, nl
666        icomp = icomp + 1
667        read(itape, rec = icomp)hThTur(k)
668      enddo
669      do k = 1, nl
670        icomp = icomp + 1
671        read(itape, rec = icomp)hqTur(k)
672      enddo
673    endif
674    print *, ' apres lecture hthtur, hqtur'
675
676    IF(imp_fcg) THEN
677      do k = 1, nl
678        icomp = icomp + 1
679        read(itape, rec = icomp)hu(k)
680      enddo
681      do k = 1, nl
682        icomp = icomp + 1
683        read(itape, rec = icomp)hv(k)
684      enddo
685
686    endif
687
688    do k = 1, nl
689      icomp = icomp + 1
690      read(itape, rec = icomp)hw(k)
691    enddo
692
693    IF(ts_fcg) THEN
694      icomp = icomp + 1
695      read(itape, rec = icomp)ts
696    endif
697
698    print *, ' rdgrads ->'
699
700    RETURN
701  END
702
703  SUBROUTINE corresbis(psol)
704    IMPLICIT NONE
705
706    !cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
707    ! Cette subroutine calcule et affiche les valeurs des coefficients
708    ! d interpolation qui serviront dans la formule d interpolation elle-
709    ! meme.
710    !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
711
712    INTEGER klev    !nombre de niveau de pression du GCM
713    REAL play(100)  !pression en Pa au milieu de chaque couche GCM
714    INTEGER JM(100)
715    REAL coef1(100) !coefficient d interpolation
716    REAL coef2(100) !coefficient d interpolation
717
718    INTEGER nblvlm !nombre de niveau de pression du mesoNH
719    REAL playm(100) !pression en Pa milieu de chaque couche Meso-NH
720    REAL hplaym(100)!pression en hPa des milieux de couche Meso-NH
721
722    COMMON/com1_phys_gcss/play, coef1, coef2, JM, klev
723    COMMON/com2_phys_gcss/playm, hplaym, nblvlm
724
725    REAL psol
726    REAL val
727    INTEGER k, mlz
728
729    do k = 1, klev
730      val = play(k)
731      IF (val > playm(1)) THEN
732        mlz = 0
733        JM(1) = mlz
734        coef1(1) = (playm(mlz + 1) - val) / (playm(mlz + 1) - psol)
735        coef2(1) = (val - psol) / (playm(mlz + 1) - psol)
736      ELSE IF (val > playm(nblvlm)) THEN
737        do mlz = 1, nblvlm
738          IF (val <= playm(mlz).AND. val > playm(mlz + 1))THEN
739            JM(k) = mlz
740            coef1(k) = (playm(mlz + 1) - val) / (playm(mlz + 1) - playm(mlz))
741            coef2(k) = (val - playm(mlz)) / (playm(mlz + 1) - playm(mlz))
742          endif
743        enddo
744      else
745        JM(k) = nblvlm - 1
746        coef1(k) = 0.
747        coef2(k) = 0.
748      endif
749    enddo
750
751    !c      if (play(klev) .le. playm(nblvlm)) THEN
752    !c         mlz=nblvlm-1
753    !c         JM(klev)=mlz
754    !c         coef1(klev)=(playm(mlz+1)-val)
755    !c     *            /(playm(mlz+1)-playm(mlz))
756    !c         coef2(klev)=(val-playm(mlz))
757    !c     *            /(playm(mlz+1)-playm(mlz))
758    !c      endif
759
760    PRINT*, ' '
761    PRINT*, '         INTERPOLATION  : '
762    PRINT*, ' '
763    PRINT*, 'correspondance de 9 niveaux du GCM sur les 53 du meso-NH:'
764    PRINT*, (JM(k), k = 1, klev)
765    PRINT*, 'correspondance de 9 niveaux du GCM sur les 53 du meso-NH:'
766    PRINT*, (JM(k), k = 1, klev)
767    PRINT*, ' '
768    PRINT*, 'vals du premier coef d"interpolation pour les 9 niveaux: '
769    PRINT*, (coef1(k), k = 1, klev)
770    PRINT*, ' '
771    PRINT*, 'valeurs du deuxieme coef d"interpolation pour les 9 niveaux:'
772    PRINT*, (coef2(k), k = 1, klev)
773
774    RETURN
775  end
776  SUBROUTINE GETSCH(STR, DEL, TRM, NTH, SST, NCH)
777    !***************************************************************
778    !*                                                             *
779    !*                                                             *
780    !* GETSCH                                                      *
781    !*                                                             *
782    !*                                                             *
783    !* modified by :                                               *
784    !***************************************************************
785    !*   Return in SST the character string found between the NTH-1 and NTH
786    !*   occurence of the delimiter 'DEL' but before the terminator 'TRM' in
787    !*   the input string 'STR'. If TRM=DEL then STR is considered unlimited.
788    !*   NCH=Length of the string returned in SST or =-1 if NTH is <1 or if
789    !*   NTH is greater than the number of delimiters in STR.
790    IMPLICIT INTEGER (A-Z)
791    CHARACTER STR*(*), DEL*1, TRM*1, SST*(*)
792    NCH = -1
793    SST = ' '
794    IF(NTH>0) THEN
795      IF(TRM==DEL) THEN
796        LENGTH = LEN(STR)
797      ELSE
798        LENGTH = INDEX(STR, TRM) - 1
799        IF(LENGTH<0) LENGTH = LEN(STR)
800      ENDIF
801      !*     Find beginning and end of the NTH DEL-limited substring in STR
802      END = -1
803      DO N = 1, NTH
804        IF(END==LENGTH) RETURN
805        BEG = END + 2
806        END = BEG + INDEX(STR(BEG:LENGTH), DEL) - 2
807        IF(END==BEG - 2) END = LENGTH
808        !*        PRINT *,'NTH,LENGTH,N,BEG,END=',NTH,LENGTH,N,BEG,END
809      end DO
810      NCH = END - BEG + 1
811      IF(NCH>0) SST = STR(BEG:END)
812    ENDIF
813  END
814  CHARACTER*(*) FUNCTION SPACES(STR, NSPACE)
815
816    ! CERN PROGLIB# M433    SPACES          .VERSION KERNFOR  4.14  860211
817    ! ORIG.  6/05/86 M.GOOSSENS/DD
818
819    !-    The function value SPACES returns the character string STR with
820    !-    leading blanks removed and each occurence of one or more blanks
821    !-    replaced by NSPACE blanks inside the string STR
822
823    CHARACTER*(*) STR
824    INTEGER nspace
825
826    LENSPA = LEN(SPACES)
827    SPACES = ' '
828    IF (NSPACE<0) NSPACE = 0
829    IBLANK = 1
830    ISPACE = 1
831    100 INONBL = INDEXC(STR(IBLANK:), ' ')
832    IF (INONBL==0) THEN
833      SPACES(ISPACE:) = STR(IBLANK:)
834      RETURN
835    ENDIF
836    INONBL = INONBL + IBLANK - 1
837    IBLANK = INDEX(STR(INONBL:), ' ')
838    IF (IBLANK==0) THEN
839      SPACES(ISPACE:) = STR(INONBL:)
840      RETURN
841    ENDIF
842    IBLANK = IBLANK + INONBL - 1
843    SPACES(ISPACE:) = STR(INONBL:IBLANK - 1)
844    ISPACE = ISPACE + IBLANK - INONBL + NSPACE
845    IF (ISPACE<=LENSPA)                         GO TO 100
846  END
847  INTEGER FUNCTION INDEXC(STR, SSTR)
848
849    ! CERN PROGLIB# M433    INDEXC          .VERSION KERNFOR  4.14  860211
850    ! ORIG. 26/03/86 M.GOOSSENS/DD
851
852    !-    Find the leftmost position where substring SSTR does not match
853    !-    string STR scanning forward
854
855    CHARACTER*(*) STR, SSTR
856    INTEGER I
857
858    LENS = LEN(STR)
859    LENSS = LEN(SSTR)
860
861    DO I = 1, LENS - LENSS + 1
862      IF (STR(I:I + LENSS - 1)/=SSTR) THEN
863        INDEXC = I
864        RETURN
865      ENDIF
866    END DO
867    INDEXC = 0
868  END
869END MODULE lmdz_old_1dconv
Note: See TracBrowser for help on using the repository browser.