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

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

Put .h into modules

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