source: trunk/LMDZ.VENUS/libf/phyvenus/ballon.F

Last change on this file was 3884, checked in by ikovalenko, 4 months ago
File size: 12.6 KB
Line 
1      subroutine ballon (iam,dtphys,rjour,rsec,plat,plon,
2     i                   temp, p, u, v, geop)
3
4      use dimphy
5      use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat
6      use YOMCST_mod
7      implicit none
8
9c======================================================================
10c Auteur: S. Lebonnois (LMD/CNRS) date: 20091201
11c Object: Compute balloon trajectories.
12C No outputs, every quantities are written on the iam+ Files.
13c
14c Called by physiq.F if flag ballons activated:
15c
16c      integer ballons
17c (...)
18c      ballons  = 1         ! (in initialisations)
19c (...)
20C  OUVERTURE DES FICHIERS FORMATTES CONTENANT LES POSITIONS ET VITESSES
21C  DES BALLONS
22c      if (ballons.eq.1) then
23c      open(30,file='ballons-lat.out',form='formatted')
24c      open(31,file='ballons-lon.out',form='formatted')
25c      open(32,file='ballons-u.out',form='formatted')
26c      open(33,file='ballons-v.out',form='formatted')
27c      open(34,file='ballons-alt.out',form='formatted')
28c      write(*,*)'Ouverture des ballons*.out'
29c      endif !ballons
30c (...)
31C        CALL ballon(30,pdtphys,rjourvrai,gmtime,rlatd,rlond,
32CC    C               t,pplay,u,v,pphi)   ! alt above surface (smoothed for GCM)
33C     C               t,pplay,u,v,zphi)   ! alt above planet average radius
34c (...)
35C  FERMETURE DES FICHIERS FORMATTES CONTENANT LES POSITIONS ET VITESSES
36C  DES BALLONS
37c      if (ballons.eq.1) then
38c        write(*,*)'Fermeture des ballons*.out'
39c        close(30)                                     
40c        close(31)                                     
41c        close(32)                                     
42c        close(33)                                     
43c        close(34)                                     
44c      endif !ballons
45c
46C======================================================================
47c Explicit Arguments:
48c ==================
49c iam-----input-I-File number where latitudes are written
50c                 It is a formatted file that has been opened
51c                 in physiq.F
52c   other files: iam+1=longitudes
53c                iam+2=zonal speeds
54c                iam+3=meridional speeds
55c                iam+4=altitudes
56c dtphys--input-R-pas de temps physique
57c rjour---input-R-Jour compte depuis le debut de la simu (run.def)
58c rsec----input-R-Seconde de la journee
59c plat ---input-R-Latitude en degres
60c plon ---input-R-Longitude en degres
61c temp----input-R-Temperature (K) at model levels
62c p-------input-R-Pressure (Pa) at model levels
63c u-------input-R-Horizontal wind (m/s)
64c v-------input-R-Meridional wind (m/s)
65c geop----input-R-Geopotential !! above surface OR average radius
66c
67c
68c Implicit Arguments:
69c ===================
70c
71c iim--common-I: Number of longitude intervals
72c jjm--common-I: Number of latitude intervals
73c klon-common-I: Number of points seen by the physics
74c                iim*(jjm-1)+2 for instance
75c klev-common-I: Number of vertical layers
76c RPI,RKBOL--common-R: Pi, KBoltzman
77c RDAY,RA,RG-common-R: day length in s, planet radius, gravity
78c======================================================================
79c Local Variables:
80c ================
81c
82c nb    ---I: number of balloons (parameter)
83c phib  ---R: Latitude of balloon in radians
84c lamb  ---R: Longitude of balloon in radians
85c lognb ---R: log(density) of balloon
86c ub    ---R: zonal speed of balloon
87c vb    ---R: meridional speed of balloon
88c altb  ---R: altitude of balloon
89c zlat  ---R: Latitude in radians
90c zlon  ---R: Longitude in radians
91c logn  ---R: log(density)
92c alt   ---R: altitude !! above surface OR average radius
93c ull   ---R: zonal wind for one balloon on the lognb surface
94c vll   ---R: meridional wind for one balloon on the lognb surface
95c aal   ---R: altitude for one balloon on the lognb surface
96c======================================================================
97
98c#include "YOMCST.h"
99c
100c ARGUMENTS
101c
102      INTEGER iam
103      REAL dtphys,rjour,rsec,plat(klon),plon(klon)
104      REAL temp(klon,klev),p(klon,klev)
105      REAL u(klon,klev),v(klon,klev),geop(klon,klev)
106c
107c Variables locales:
108c
109      INTEGER i,j,k,l,nb,n
110      parameter (nb=20)  !! Adjust the format on line 100 !!
111      INTEGER jj,ii,ll
112
113      REAL,SAVE,ALLOCATABLE :: zlon(:),zlat(:)
114
115      REAL time
116      REAL logn(klon,klev),ull(klon),vll(klon)
117      REAL alt(klon,klev),aal(klon)
118      real ub(nb),vb(nb),phib(nb),lamb(nb),lognb(nb),altb(nb)
119      save phib,lamb,lognb
120
121      REAL factalt
122
123c RungeKutta order - If not RK, Nrk=1
124      integer Nrk,irk
125      parameter (Nrk=1)
126      real    dtrk
127
128      logical first
129      save first
130      data first/.true./
131
132      time = rjour*RDAY+rsec
133      logn(:,:) = log10(p(:,:)/(RKBOL*temp(:,:)))
134      alt(:,:)  = geop(:,:)/RG
135
136c---------------------------------------------
137C INITIALIZATIONS
138c---------------------------------------------
139      if (first) then
140
141      print*,"BALLOONS ACTIVATED"
142
143      allocate(zlon(nbp_lon+1))
144      allocate(zlat(nbp_lat))
145     
146C Latitudes:
147      zlat(1)=plat(1)*RPI/180.
148      do j = 2,nbp_lat-1
149         k=(j-2)*nbp_lon+2
150         zlat(j)=plat(k)*RPI/180.
151      enddo
152      zlat(nbp_lat)=plat(klon)*RPI/180.
153
154C Longitudes:
155      do i = 1,nbp_lon
156         k=i+1
157         zlon(i)=plon(k)*RPI/180.
158      enddo
159      zlon(nbp_lon+1)=zlon(1)+2.*RPI
160
161c verif init     lat de 90 � -90, lon de -180 � 180
162c     print*,"Latitudes:",zlat*180./RPI
163c     print*,"Longitudes:",zlon*180./RPI
164c     stop
165
166c initial positions of balloons (in degrees for lat/lon)
167      do j=1,5
168      do i=1,4
169        k=(j-1)*4+i
170      phib(k)= (j-1)*20.*RPI/180.
171      lamb(k)= (i-3)*90.*RPI/180.   ! de -180 � 90
172c     lognb(k)= log10(5.e4/(RKBOL*300.)) ! ~55km in VIRA model
173      lognb(k)= log10(5.e5/(RKBOL*300.)) ! 5 bars (for Blamont, mai2015)
174      enddo
175      enddo
176      print*,"Balloon density (m^-3)=",10.**(lognb(1))
177
178c     print*,"log(density) profile:"
179c     do l=1,klev
180c        print*,logn(klon/2,l)
181c     enddo
182c     stop !verif init
183
184      first=.false.
185      endif ! first
186c---------------------------------------------
187
188c-------------------------------------------------
189c loop over the balloons
190c-------------------------------------------------
191      do n=1,nb
192
193c Interpolation in altitudes
194c-------------------------------------------------
195        do k=1,klon
196         ll=1 ! en bas
197         do l=2,klev
198          if (lognb(n).lt.logn(k,l)) ll=l
199         enddo
200         factalt= (lognb(n)-logn(k,ll))/(logn(k,ll+1)-logn(k,ll))
201         ull(k) =   u(k,ll+1)*factalt +   u(k,ll)*(1-factalt)
202         vll(k) =   v(k,ll+1)*factalt +   v(k,ll)*(1-factalt)
203         aal(k) = alt(k,ll+1)*factalt + alt(k,ll)*(1-factalt)
204        enddo
205
206c Interpolation in latitudes and longitudes
207c-------------------------------------------
208        call wind_interp(ull,vll,aal,zlat,zlon,
209     .                   phib(n),lamb(n),ub(n),vb(n),altb(n))
210       
211      enddo ! over balloons
212c-------------------------------------------------
213
214c-------------------------------------------------
215c Output of positions and speed at time
216c-------------------------------------------------
217
218c Venus regardee a l'envers: lon et lat inversees
219      write(iam,  100) time, (-1)*phib*180./RPI
220      write(iam+1,100) time, (-1)*lamb*180./RPI
221      write(iam+2,100) time, ub
222c Venus regardee a l'envers: v inversee
223      write(iam+3,100) time, (-1)*vb
224      write(iam+4,100) time, altb
225c     stop !verif init
226
227c !!!!!!!!!!!!!!!! nb !!!!!!!!!!!!!!!!!
228100   format(E14.7,20(1x,E12.5))
229
230c-------------------------------------------------
231c Implementation: positions at time+dt
232c RK order Nrk
233c-------------------------------------------------
234
235      dtrk = dtphys/Nrk
236      time=time+dtrk
237
238      do n=1,nb
239        call pos_implem(phib(n),lamb(n),ub(n),vb(n),dtrk)
240      enddo
241
242      if (Nrk.gt.1) then
243       do irk=2,Nrk
244        do n=1,nb
245          time=time+dtrk
246          call wind_interp(ull,vll,aal,zlat,zlon,
247     .                   phib(n),lamb(n),ub(n),vb(n),altb(n))
248          call pos_implem(phib(n),lamb(n),ub(n),vb(n),dtrk)
249        enddo
250       enddo
251      endif
252
253      end
254
255c======================================================================
256c======================================================================
257c======================================================================
258
259      subroutine wind_interp(map_u,map_v,map_a,latit,longit,
260     .                       phi,lam,ubal,vbal,abal)
261
262      use dimphy
263      use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat
264      use YOMCST_mod
265      implicit none
266
267c======================================================================
268c Auteur: S. Lebonnois (LMD/CNRS) date: 20091201
269c Object: interpolate balloon speed from its position.
270C======================================================================
271c Explicit Arguments:
272c ==================
273c map_u ---R: zonal wind on the lognb surface
274c map_v ---R: meridional wind on the lognb surface
275c map_a ---R: altitude on the lognb surface
276c latit ---R: Latitude in radians
277c longit---R: Longitude in radians
278c phi   ---R: Latitude of balloon in radians
279c lam   ---R: Longitude of balloon in radians
280c ubal  ---R: zonal speed of balloon
281c vbal  ---R: meridional speed of balloon
282c abal  ---R: altitude of balloon
283c======================================================================
284c Local Variables:
285c ================
286c
287c ujj   ---R: zonal wind interpolated in latitude
288c vjj   ---R: meridional wind interpolated in latitude
289c ajj   ---R: altitude interpolated in latitude
290c======================================================================
291
292c#include "YOMCST.h"
293c
294c ARGUMENTS
295c
296      real map_u(klon),map_v(klon),map_a(klon)
297      real latit(nbp_lat),longit(nbp_lon)
298      real phi,lam,ubal,vbal,abal
299c
300c Variables locales:
301c
302      INTEGER i,j,k
303      INTEGER jj,ii
304      REAL    ujj(nbp_lon+1),vjj(nbp_lon+1),ajj(nbp_lon+1)
305      REAL    factlat,factlon
306
307c Interpolation in latitudes
308c-------------------------------------------------
309        jj=1  ! POLE NORD
310        do j=2,nbp_lat-1
311          if (phi.lt.latit(j)) jj=j
312        enddo
313        factlat  = (phi-latit(jj))/(latit(jj+1)-latit(jj))
314
315c pole nord
316        if (jj.eq.1) then
317         do i=1,nbp_lon
318          ujj(i) = map_u(i+1)*factlat + map_u(1)*(1-factlat)
319          vjj(i) = map_v(i+1)*factlat + map_v(1)*(1-factlat)
320          ajj(i) = map_a(i+1)*factlat + map_a(1)*(1-factlat)
321         enddo
322c pole sud
323        elseif (jj.eq.nbp_lat-1) then
324         do i=1,nbp_lon
325          k = (jj-2)*nbp_lon+1+i
326          ujj(i) = map_u(klon)*factlat + map_u(k)*(1-factlat)
327          vjj(i) = map_v(klon)*factlat + map_v(k)*(1-factlat)
328          ajj(i) = map_a(klon)*factlat + map_a(k)*(1-factlat)
329         enddo
330c autres latitudes
331        else
332         do i=1,nbp_lon
333          k = (jj-2)*nbp_lon+1+i
334          ujj(i) = map_u(k+nbp_lon)*factlat + map_u(k)*(1-factlat)
335          vjj(i) = map_v(k+nbp_lon)*factlat + map_v(k)*(1-factlat)
336          ajj(i) = map_a(k+nbp_lon)*factlat + map_a(k)*(1-factlat)
337         enddo
338        endif
339        ujj(nbp_lon+1)=ujj(1)
340        vjj(nbp_lon+1)=vjj(1)
341        ajj(nbp_lon+1)=ajj(1)
342
343c Interpolation in longitudes
344c-------------------------------------------------
345        ii=1  ! lon=-180
346        do i=2,nbp_lon
347          if (lam.gt.longit(i)) ii=i
348        enddo
349        factlon = (lam-longit(ii))/(longit(ii+1)-longit(ii))
350        ubal    = ujj(ii+1)*factlon + ujj(ii)*(1-factlon)
351        vbal    = vjj(ii+1)*factlon + vjj(ii)*(1-factlon)
352        abal    = ajj(ii+1)*factlon + ajj(ii)*(1-factlon)
353
354      end
355
356c======================================================================
357c======================================================================
358c======================================================================
359
360      subroutine pos_implem(phi,lam,ubal,vbal,dt)
361
362      use dimphy
363      use YOMCST_mod
364      implicit none
365
366c======================================================================
367c Auteur: S. Lebonnois (LMD/CNRS) date: 20091201
368c Object: implementation of balloon position.
369C======================================================================
370c Explicit Arguments:
371c ==================
372c phi   ---R: Latitude of balloon in radians
373c lam   ---R: Longitude of balloon in radians
374c ubal  ---R: zonal speed of balloon
375c vbal  ---R: meridional speed of balloon
376c dt    ---R: time step
377c======================================================================
378
379c#include "YOMCST.h"
380c
381c ARGUMENTS
382c
383      real phi,lam,ubal,vbal,abal,dt
384
385c incrementation longitude
386        lam = lam + ubal*dt/(RA*cos(phi))
387c maintenue entre -PI et PI:
388        do while (lam.ge.RPI)     
389              lam=lam-2*RPI
390        enddo
391        do while (lam.lt.(-1.*RPI)) 
392              lam=lam+2*RPI
393        enddo
394c incrementation latitude
395        phi = phi + vbal*dt/RA
396c maintenue entre -PI/2 et PI/2:
397        if (phi.ge.( 0.5*RPI)) phi=    RPI-phi
398        if (phi.le.(-0.5*RPI)) phi=-1.*RPI-phi
399
400      end
Note: See TracBrowser for help on using the repository browser.