source: trunk/LMDZ.TITAN/utilities/streamfunction.F90 @ 3404

Last change on this file since 3404 was 1821, checked in by jvatant, 7 years ago

Minor change : in util streamfunction, psi
shall be vertically integrated according to
meridional wind conventions
--JVO

File size: 36.8 KB
Line 
1module planet_const
2! planetary constants (set via init_planet_const routine)
3implicit none
4real :: a0 ! Mean planetary radius
5real :: g0 ! gravity
6real :: Rmean ! reduced gaz constant
7real :: omega ! rotation rate
8end module planet_const
9
10program streamfunction
11
12! ----------------------------------------------------------------------------
13! Program to calculate the stream function and the total angular momentum
14! from stats and diagfi files
15! input : diagfi.nc  / concat.nc / stats.nc kind of files
16! author: F. Gonzalez-Galindo
17!
18! Updates :
19!
20! - 02/2016 (M. Turbet) : The code was adapted to work for any planet.
21!
22! ----------------------------------------------------------------------------
23
24use planet_const
25implicit none
26
27include "netcdf.inc" ! NetCDF definitions
28
29character (len=128) :: infile ! input file name (diagfi.nc or stats.nc format)
30character (len=128) :: infile2 ! second input file (may be needed for 'aire' and 'cv')
31character (len=64) :: text ! to store some text
32
33character (len=50), dimension(:), allocatable :: var
34! var(): name(s) of variable(s) that will be concatenated
35character (len=100) :: filename
36! filename(): output file name
37integer :: nid,ierr,miss
38! nid: [netcdf] file ID #
39! ierr: [netcdf] subroutine returned error code
40! miss: [netcdf] subroutine returned error code
41integer :: tmpvarid
42! varid: temporary store a variable ID #
43integer tmpdimid ! temporarily store a dimension ID
44integer infid ! NetCDF input file ID (of diagfi.nc or stats.nc format)
45integer infid2 ! NetCDF input file which contains 'phisini' dataset (diagfi.nc)
46integer nbvarinfile ! # of variables in input file
47real, dimension(:), allocatable:: lat,lon,alt,time
48! lat(): array, stores latitude coordinates
49! lon(): array, stores longitude coordinates
50! alt(): array, stores altitude coordinates
51! time(): array, stores time coordinates
52integer :: ilat,ilon,ialt,it,i
53! ilat: index for loops on latitude
54! ilon: index for loops on longitude
55! ialt: index for loops on altitude
56! it: # index for loops on time
57! i: index for loops
58integer :: nout,latdimout,londimout,altdimout,timedimout,lonvarout,timevarout
59integer :: psivarout,momvarout,uvarout,vvarout,rhovarout,tempvarout
60integer :: psvarout, phisinitvarout
61! nout: [netcdf] output file ID
62! latdimout: [netcdf] output latitude (dimension) ID
63! londimout: [netcdf] output longitude (dimension) ID
64! altdimout: [netcdf] output altitude (dimension) ID
65! timedimout: [netcdf] output time (dimension) ID
66! lonvarout: [netcdf] ID of output "Time" variable
67integer lonlength ! # of grid points along longitude
68integer latlength ! # of grid points along latitude
69integer altlength ! # of grid point along altitude (of input datasets)
70integer timelength ! # of points along time
71real,dimension(:),allocatable :: aps,bps ! hybrid vertical coordinates
72real,dimension(:),allocatable :: sigma ! sigma levels
73real,dimension(:),allocatable :: lon_fake ! Fake longitude to be written
74real,dimension(:,:),allocatable :: aire ! Area of the box
75real,dimension(:,:),allocatable :: cv ! Conversion between natural and covariant v
76real,dimension(:,:),allocatable :: phisinit ! Ground geopotential
77real,dimension(:,:,:),allocatable :: ps ! GCM surface pressure
78real,dimension(:,:,:,:),allocatable :: press ! GCM atmospheric pressure
79real,dimension(:,:,:,:),allocatable :: temp ! GCM atmospheric temperature
80real,dimension(:,:,:,:),allocatable :: u ! GCM zonal wind
81real,dimension(:,:,:,:),allocatable :: v ! GCM meridional wind
82real,dimension(:,:,:,:),allocatable :: rho ! GCM atmospheric density
83real,dimension(:,:,:),allocatable :: vcont ! Covariant meridional wind
84real,dimension(:,:),allocatable :: vcontcum ! Zonal mean covariant meridional wind
85real,dimension(:,:,:),allocatable :: plev ! Pressure from hybrid coordinates
86real,dimension(:,:,:),allocatable :: mass ! Mass in a grid box
87real,dimension(:,:,:),allocatable :: dmass ! Mass variation
88real,dimension(:,:),allocatable :: psi ! Stream function
89real,dimension(:,:,:),allocatable :: mom ! Angular momentum
90real,dimension(:,:),allocatable :: momave ! Zonally averaged angular momentum
91real,dimension(:,:,:),allocatable :: ucum ! Temporally averaged zonal wind
92real,dimension(:,:,:),allocatable :: vcum ! Temporally averaged meridional wind
93real,dimension(:,:,:),allocatable :: rhocum ! Temporally averaged density
94real,dimension(:,:,:),allocatable :: tempcum ! Temporally averaged zonal wind
95real,dimension(:,:),allocatable :: pscum ! Temporally averaged zonal wind
96real,dimension(:,:),allocatable :: uzm ! Zonally averaged zonal wind
97real,dimension(:,:),allocatable :: vzm ! Zonally averaged meridional wind
98real,dimension(:,:),allocatable :: rhozm ! Zonally averaged density
99real,dimension(:,:),allocatable :: tempzm ! Zonally averaged temperature
100real,dimension(:),allocatable :: pszm ! Zonally averaged surface pressure
101real,dimension(:),allocatable :: phisinitzm ! Zonally averaged ground geopotential
102
103!===============================================================================
104! 1.1 Input file
105!===============================================================================
106
107write(*,*) ""
108write(*,*) " Program valid for diagfi.nc, concatnc.nc and stats.nc files"
109write(*,*) "Enter input file name:"
110
111read(*,'(a128)') infile
112write(*,*) ""
113
114! open input file
115
116ierr = NF_OPEN(infile,NF_NOWRITE,infid)
117if (ierr.ne.NF_NOERR) then
118   write(*,*) 'ERROR: Pb opening input file'
119   stop ""
120endif
121
122! load planet constants (radius, gravity, ...)
123
124call init_planet_const(infid)
125
126!===============================================================================
127! 1.2 Get grids in lon,lat,alt,time,
128!     as well as hybrid coordinates aps() and bps() (or sigma levels sigma())
129!     aire() and cv() from input file
130!===============================================================================
131
132! 1.2.1 longitude, latitude, altitude and time
133
134! latitude
135ierr=NF_INQ_DIMID(infid,"latitude",tmpdimid)
136if (ierr.ne.NF_NOERR) then
137  stop "Error: Failed to get latitude dimension ID"
138else
139  ierr=NF_INQ_VARID(infid,"latitude",tmpvarid)
140  if (ierr.ne.NF_NOERR) then
141    stop "Error: Failed to get latitude ID"
142  else
143    ierr=NF_INQ_DIMLEN(infid,tmpdimid,latlength)
144    if (ierr.ne.NF_NOERR) then
145      stop "Error: Failed to get latitude length"
146    else
147      allocate(lat(latlength))
148      ierr=NF_GET_VAR_REAL(infid,tmpvarid,lat)
149      if (ierr.ne.NF_NOERR) then
150        stop "Error: Failed reading latitude"
151      endif
152    endif
153  endif
154endif
155
156! longitude
157ierr=NF_INQ_DIMID(infid,"longitude",tmpdimid)
158if (ierr.ne.NF_NOERR) then
159  stop "Error: Failed to get longitude dimension ID"
160else
161  ierr=NF_INQ_VARID(infid,"longitude",tmpvarid)
162  if (ierr.ne.NF_NOERR) then
163    stop "Error: Failed to get longitude ID"
164  else
165    ierr=NF_INQ_DIMLEN(infid,tmpdimid,lonlength)
166    if (ierr.ne.NF_NOERR) then
167      stop "Error: Failed to get longitude length"
168    else
169      allocate(lon(lonlength))
170      ierr=NF_GET_VAR_REAL(infid,tmpvarid,lon)
171      if (ierr.ne.NF_NOERR) then
172        stop "Error: Failed reading longitude"
173      endif
174    endif
175  endif
176endif
177
178! time
179ierr=NF_INQ_DIMID(infid,"Time",tmpdimid)
180if (ierr.ne.NF_NOERR) then
181  stop "Error: Failed to get Time dimension ID"
182else
183  ierr=NF_INQ_VARID(infid,"Time",tmpvarid)
184  if (ierr.ne.NF_NOERR) then
185    stop "Error: Failed to get Time ID"
186  else
187    ierr=NF_INQ_DIMLEN(infid,tmpdimid,timelength)
188    if (ierr.ne.NF_NOERR) then
189      stop "Error: Failed to get Time length"
190    else
191      allocate(time(timelength))
192      ierr=NF_GET_VAR_REAL(infid,tmpvarid,time)
193      if (ierr.ne.NF_NOERR) then
194        stop "Error: Failed reading Time"
195      endif
196    endif
197  endif
198endif
199
200! altlength
201ierr=NF_INQ_DIMID(infid,"altitude",tmpdimid)
202if (ierr.ne.NF_NOERR) then
203  stop "Error: Failed to get altitude dimension ID"
204else
205  ierr=NF_INQ_VARID(infid,"altitude",tmpvarid)
206  if (ierr.ne.NF_NOERR) then
207     stop "Error: Failed to get altitude length"
208  else
209     ierr=NF_INQ_DIMLEN(infid,tmpdimid,altlength)
210     if (ierr.ne.NF_NOERR) then
211        stop "Error: Failed to get altitude length"
212     else   
213        allocate(alt(altlength))
214        ierr=NF_GET_VAR_REAL(infid,tmpvarid,alt)
215        if (ierr.ne.NF_NOERR) then
216           stop "Error: Failed reading Altitude"
217        endif
218     endif
219  endif
220endif
221
222! 1.2.2 Get hybrid coordinates
223
224! look for hybrid coordinates
225
226! hybrid coordinate aps
227ierr=NF_INQ_VARID(infid,"aps",tmpvarid)
228if (ierr.ne.NF_NOERR) then
229   stop "Error: Failed to get aps ID"
230else
231   allocate(aps(altlength))
232   ierr=NF_GET_VAR_REAL(infid,tmpvarid,aps)
233   if (ierr.ne.NF_NOERR) then
234      stop "Error: Failed reading aps"
235   endif
236endif
237
238! hybrid coordinate bps
239ierr=NF_INQ_VARID(infid,"bps",tmpvarid)
240if (ierr.ne.NF_NOERR) then
241   stop "Error: Failed to get bps ID"
242else
243   allocate(bps(altlength))
244   ierr=NF_GET_VAR_REAL(infid,tmpvarid,bps)
245   if (ierr.ne.NF_NOERR) then
246      stop "Error: Failed reading bps"
247   endif
248endif
249
250!surface pressure
251ierr=NF_INQ_VARID(infid,"ps",tmpvarid)
252if (ierr.ne.NF_NOERR) then
253   stop "Error: Failed to get ps ID"
254else
255   allocate(ps(lonlength,latlength,timelength))
256   ierr=NF_GET_VAR_REAL(infid,tmpvarid,ps)
257   if (ierr.ne.NF_NOERR) then
258      stop "Error: Failed reading ps"
259   endif
260endif
261
262
263!===============================================================================
264! 1.3 Reads variables in input file
265!===============================================================================
266
267ierr=NF_INQ_NVARS(infid,nbvarinfile)
268if (ierr.ne.NF_NOERR) then
269  write(*,*) 'ERROR: Failed geting number of variables from file'
270  stop
271endif
272
273!1.3.1 Zonal wind, meridional wind
274
275!Zonal wind
276ierr=NF_INQ_VARID(infid,"u",tmpvarid)
277if (ierr.ne.NF_NOERR) then
278  stop "Error: Failed to get u ID"
279else
280  allocate(u(lonlength,latlength,altlength,timelength))
281  ierr=NF_GET_VAR_REAL(infid,tmpvarid,u)
282  if (ierr.ne.NF_NOERR) then
283    stop "Error: Failed reading zonal wind"
284  endif
285endif
286
287!Meridional wind
288ierr=NF_INQ_VARID(infid,"v",tmpvarid)
289if (ierr.ne.NF_NOERR) then
290  stop "Error: Failed to get v ID"
291else
292  allocate(v(lonlength,latlength,altlength,timelength))
293  ierr=NF_GET_VAR_REAL(infid,tmpvarid,v)
294  if (ierr.ne.NF_NOERR) then
295    stop "Error: Failed reading zonal wind"
296  endif
297endif
298
299
300! 1.3.2 aire
301
302allocate(aire(lonlength,latlength))
303! look for 'aire' in current file
304ierr=NF_INQ_VARID(infid,"aire",tmpvarid)
305if (ierr.ne.NF_NOERR) then
306  write(*,*) "Warning: Failed to get aire ID from file ",trim(infile)
307  infile2="diagfi.nc"
308  write(*,*) "         Trying file ",trim(infile2)
309  ierr=NF_OPEN(infile2,NF_NOWRITE,infid2)
310  if (ierr.ne.NF_NOERR) then
311     infile2="diagfi1.nc"
312     write(*,*) "         Trying file ",trim(infile2)
313     ierr=NF_OPEN(infile2,NF_NOWRITE,infid2)
314     if (ierr.ne.NF_NOERR) then
315        write(*,*) "Problem: Could not find/open these files"
316        stop "Might as well stop here"
317     endif
318  endif
319
320   ! Get ID for aire
321   ierr=NF_INQ_VARID(infid2,"aire",tmpvarid)
322   if (ierr.ne.NF_NOERR) then
323      stop "Error: Failed to get aire ID"
324   endif
325   ! Get aire
326   ierr=NF_GET_VAR_REAL(infid2,tmpvarid,aire)
327   if (ierr.ne.NF_NOERR) then
328      stop "Error: Failed reading aire"
329   endif
330   ! Close file
331   write(*,*) 'OK, got aire'
332   ierr=NF_CLOSE(infid2)
333else
334   ierr=NF_GET_VAR_REAL(infid,tmpvarid,aire)
335   if (ierr.ne.NF_NOERR) then
336      stop "Error: Failed reading aire"
337   endif
338endif
339
340
341! 1.3.3 phisinit
342
343allocate(phisinit(lonlength,latlength))
344! look for '' in current file
345ierr=NF_INQ_VARID(infid,"phisinit",tmpvarid)
346if (ierr.ne.NF_NOERR) then
347  write(*,*) "Warning: Failed to get phisinit ID from file ",trim(infile)
348  infile2="diagfi.nc"
349  write(*,*) "         Trying file ",trim(infile2)
350  ierr=NF_OPEN(infile2,NF_NOWRITE,infid2)
351  if (ierr.ne.NF_NOERR) then
352     infile2="diagfi1.nc"
353     write(*,*) "         Trying file ",trim(infile2)
354     ierr=NF_OPEN(infile2,NF_NOWRITE,infid2)
355     if (ierr.ne.NF_NOERR) then
356        write(*,*) "Problem: Could not find/open these files"
357        stop "Might as well stop here"
358     endif
359  endif
360
361
362   ! Get ID for phisinit
363   ierr=NF_INQ_VARID(infid2,"phisinit",tmpvarid)
364   if (ierr.ne.NF_NOERR) then
365      stop "Error: Failed to get phisinit ID"
366   endif
367   ! Get phisinit
368   ierr=NF_GET_VAR_REAL(infid2,tmpvarid,phisinit)
369   if (ierr.ne.NF_NOERR) then
370      stop "Error: Failed reading phisinit"
371   endif
372   ! Close file
373   write(*,*) 'OK, got phisinit'
374   ierr=NF_CLOSE(infid2)
375else
376   ierr=NF_GET_VAR_REAL(infid,tmpvarid,phisinit)
377   if (ierr.ne.NF_NOERR) then
378      stop "Error: Failed reading phisinit"
379   endif
380endif
381
382
383! 1.3.4 cv
384
385allocate(cv(lonlength,latlength))
386! look for 'cv' in current file
387ierr=NF_INQ_VARID(infid,"cv",tmpvarid)
388if (ierr.ne.NF_NOERR) then
389  write(*,*) "Warning: Failed to get cv ID from file ",trim(infile)
390  infile2="diagfi.nc"
391  write(*,*) "         Trying file ",trim(infile2)
392  ierr=NF_OPEN(infile2,NF_NOWRITE,infid2)
393  if (ierr.ne.NF_NOERR) then
394     infile2="diagfi1.nc"
395     write(*,*) "         Trying file ",trim(infile2)
396     ierr=NF_OPEN(infile2,NF_NOWRITE,infid2)
397     if (ierr.ne.NF_NOERR) then
398        write(*,*) "Problem: Could not find/open these files"
399        stop "Might as well stop here"
400     endif
401  endif
402
403
404   ! Get ID for cv
405   ierr=NF_INQ_VARID(infid2,"cv",tmpvarid)
406   if (ierr.ne.NF_NOERR) then
407      stop "Error: Failed to get cv ID"
408   endif
409   ! Get cv
410   ierr=NF_GET_VAR_REAL(infid2,tmpvarid,cv)
411   if (ierr.ne.NF_NOERR) then
412      stop "Error: Failed reading cv"
413   endif
414   ! Close file
415   write(*,*) 'OK, got cv'
416   ierr=NF_CLOSE(infid2)
417else
418   ierr=NF_GET_VAR_REAL(infid,tmpvarid,cv)
419   if (ierr.ne.NF_NOERR) then
420      stop "Error: Failed reading cv"
421   endif
422endif
423
424
425!Other variables: rho, temp
426
427ierr=NF_INQ_VARID(infid,"temp",tmpvarid)
428if (ierr.ne.NF_NOERR) then
429  stop "Error: Failed to get temp ID"
430else
431  allocate(temp(lonlength,latlength,altlength,timelength))
432  ierr=NF_GET_VAR_REAL(infid,tmpvarid,temp)
433  if (ierr.ne.NF_NOERR) then
434    stop "Error: Failed reading temperature"
435  endif
436endif
437
438ierr=NF_INQ_VARID(infid,"rho",tmpvarid)
439if (ierr.ne.NF_NOERR) then
440  write(*,*) "Error: Failed to get rho ID"
441  write(*,*) "Let's compute it from temperature"
442  allocate(rho(lonlength,latlength,altlength,timelength))
443 
444  do it=1,timelength
445    do ilat=1,latlength
446      do ilon=1,lonlength
447        do ialt=1,altlength
448          rho(ilon,ilat,ialt,it)= (aps(ialt)+bps(ialt)*ps(ilon,ilat,it))/(Rmean*temp(ilon,ilat,ialt,it))
449        enddo
450      enddo
451    enddo
452  enddo
453else
454  allocate(rho(lonlength,latlength,altlength,timelength))
455  ierr=NF_GET_VAR_REAL(infid,tmpvarid,rho)
456  if (ierr.ne.NF_NOERR) then
457    stop "Error: Failed reading mass density"
458  endif
459endif
460
461!==============================================================================
462! 1.4. Output file name
463!==============================================================================
464filename=infile(1:len_trim(infile)-3)//"_stream.nc"
465write(*,*)'The output file has name:'
466write(*,*) filename
467
468
469!==============================================================================
470! 2.1. Temporal averages
471!==============================================================================
472
473allocate(ucum(lonlength,latlength,altlength)) !Time mean zonal wind
474allocate(vcum(lonlength,latlength,altlength)) !Time mean meridional wind
475allocate(tempcum(lonlength,latlength,altlength)) !Time mean temperature
476allocate(rhocum(lonlength,latlength,altlength)) !Time mean density
477allocate(pscum(lonlength,latlength)) !Time mean surface pressure
478do ilat=1,latlength
479   do ilon=1,lonlength
480      pscum(ilon,ilat)=0.
481      do ialt=1,altlength
482            ucum(ilon,ilat,ialt)=0.
483            vcum(ilon,ilat,ialt)=0.
484            tempcum(ilon,ilat,ialt)=0.
485            rhocum(ilon,ilat,ialt)=0.
486            do it=1,timelength
487               ucum(ilon,ilat,ialt)=ucum(ilon,ilat,ialt)+u(ilon,ilat,ialt,it)
488               vcum(ilon,ilat,ialt)=vcum(ilon,ilat,ialt)+v(ilon,ilat,ialt,it)
489               tempcum(ilon,ilat,ialt)=tempcum(ilon,ilat,ialt)+temp(ilon,ilat,ialt,it)
490               rhocum(ilon,ilat,ialt)=rhocum(ilon,ilat,ialt)+rho(ilon,ilat,ialt,it)
491            enddo
492            ucum(ilon,ilat,ialt)=ucum(ilon,ilat,ialt)/timelength
493            vcum(ilon,ilat,ialt)=vcum(ilon,ilat,ialt)/timelength
494            tempcum(ilon,ilat,ialt)=tempcum(ilon,ilat,ialt)/timelength
495            rhocum(ilon,ilat,ialt)=rhocum(ilon,ilat,ialt)/timelength
496      enddo
497      do it=1,timelength
498         pscum(ilon,ilat)=pscum(ilon,ilat)+ps(ilon,ilat,it)
499      enddo
500      pscum(ilon,ilat)=pscum(ilon,ilat)/timelength
501   enddo
502enddo
503
504!==============================================================================
505! 2.2. Calculation of the stream function
506!==============================================================================
507
508!Contravariant meridional wind
509allocate(vcont(lonlength,latlength,altlength))
510do ilon=1,lonlength
511   do ialt=1,altlength
512      do ilat=1,latlength-1
513         vcont(ilon,ilat,ialt)=0.5*&
514              (vcum(ilon,ilat,ialt)+vcum(ilon,ilat+1,ialt))/cv(ilon,ilat)
515      enddo
516      vcont(ilon,latlength,ialt)=0.!vcont(ilon,latlength-1,ialt)
517   enddo
518enddo
519
520!Pressure from hybrid levels
521allocate(Plev(lonlength,latlength,altlength))
522do ilon=1,lonlength
523   do ilat=1,latlength
524      do ialt=1,altlength
525         Plev(ilon,ilat,ialt)=aps(ialt)+bps(ialt)*pscum(ilon,ilat)
526      enddo
527   enddo
528enddo
529
530!Mass in the box
531allocate(mass(lonlength,latlength,altlength))
532do ilon=1,lonlength
533   do ilat=1,latlength
534      do ialt=1,altlength
535         mass(ilon,ilat,ialt)=aire(ilon,ilat)*&
536              Plev(ilon,ilat,ialt)/g0
537      enddo
538   enddo
539enddo
540
541!Mass variation in the box
542allocate(dmass(lonlength,latlength,altlength))
543do ilon=1,lonlength
544   do ilat=1,latlength
545      do ialt=1,altlength-1
546         dmass(ilon,ilat,ialt)=mass(ilon,ilat,ialt)-&
547              mass(ilon,ilat,ialt+1)
548      enddo
549      dmass(ilon,ilat,altlength)=0.!dmass(ilon,ilat,altlength-1)
550   enddo
551enddo
552
553!Stream function
554allocate(psi(latlength,altlength))
555allocate(vcontcum(latlength,altlength))
556do ilat=1,latlength-1
557   psi(ilat,altlength)=0.
558   do ialt=altlength-1,1,-1
559      psi(ilat,ialt)=psi(ilat,ialt+1)
560      vcontcum(ilat,ialt)=0.
561      do ilon=1,lonlength
562         vcontcum(ilat,ialt)=vcontcum(ilat,ialt)+vcont(ilon,ilat,ialt)/lonlength
563         psi(ilat,ialt)=psi(ilat,ialt)+(vcont(ilon,ilat,ialt)&
564              *(dmass(ilon,ilat,ialt)+dmass(ilon,ilat+1,ialt)))
565      enddo
566      psi(latlength,ialt)=0.!psi(latlength-1,ialt)
567   enddo
568enddo
569
570!==============================================================================
571! 2.3. Calculation of the total angular momentum
572!==============================================================================
573
574!Angular momentum
575allocate(mom(lonlength,latlength,altlength))
576allocate(momave(latlength,altlength))
577do ilat=1,latlength
578   do ialt=1,altlength
579      momave(ilat,ialt)=0.
580      do ilon=1,lonlength
581!            mom(ilon,ilat,ialt,it)=dmass(ilon,ilat,ialt,it)*a0*&
582         mom(ilon,ilat,ialt)=a0*cos(lat(ilat)*3.141592/180.)*&
583              (omega*a0*cos(lat(ilat)*3.141592/180.)+ucum(ilon,ilat,ialt))
584         
585         momave(ilat,ialt)=momave(ilat,ialt)+mom(ilon,ilat,ialt)
586      enddo
587      momave(ilat,ialt)=momave(ilat,ialt)/lonlength
588   enddo
589enddo
590
591!==============================================================================
592! 2.4. Zonal mean winds, temperature and density
593!==============================================================================
594
595allocate(uzm(latlength,altlength)) !Zonal mean zonal wind
596allocate(vzm(latlength,altlength)) !Zonal mean meridional wind
597allocate(tempzm(latlength,altlength)) !Zonal mean temperature
598allocate(rhozm(latlength,altlength)) !Zonal mean density
599allocate(pszm(latlength)) !Zonal mean surface pressure
600allocate(phisinitzm(latlength)) !Zonal mean ground geopotential
601do ilat=1,latlength
602   phisinitzm(ilat)=0.
603   pszm(ilat)=0.
604   do ialt=1,altlength
605      uzm(ilat,ialt)=0.
606      vzm(ilat,ialt)=0.
607      tempzm(ilat,ialt)=0.
608      rhozm(ilat,ialt)=0.
609      do ilon=1,lonlength
610         uzm(ilat,ialt)=uzm(ilat,ialt)+ucum(ilon,ilat,ialt)
611         vzm(ilat,ialt)=vzm(ilat,ialt)+vcum(ilon,ilat,ialt)
612         tempzm(ilat,ialt)=tempzm(ilat,ialt)+tempcum(ilon,ilat,ialt)
613         rhozm(ilat,ialt)=rhozm(ilat,ialt)+rhocum(ilon,ilat,ialt)
614      enddo
615      uzm(ilat,ialt)=uzm(ilat,ialt)/lonlength
616      vzm(ilat,ialt)=vzm(ilat,ialt)/lonlength
617      tempzm(ilat,ialt)=tempzm(ilat,ialt)/lonlength
618      rhozm(ilat,ialt)=rhozm(ilat,ialt)/lonlength
619   enddo
620   do ilon=1,lonlength
621      pszm(ilat)=pszm(ilat)+pscum(ilon,ilat)
622      phisinitzm(ilat)=phisinitzm(ilat)+phisinit(ilon,ilat)
623   enddo
624   pszm(ilat)=pszm(ilat)/lonlength
625   phisinitzm(ilat)=phisinitzm(ilat)/lonlength 
626enddo
627
628
629!==============================================================================
630! 2.3. Recalculation of angular momentum using zonally averaged wind
631!==============================================================================
632
633do ilat=1,latlength
634   do ialt=1,altlength
635      momave(ilat,ialt)=a0*cos(lat(ilat)*3.141592/180.)*&
636           (omega*a0*cos(lat(ilat)*3.141592/180.)+uzm(ilat,ialt))
637   enddo
638enddo
639
640
641!==============================================================================
642! 3.1 Dimensions in output file
643!==============================================================================
644
645! 3.1.1 Initialize output file's lat,lon,alt and time dimensions
646call initiate (filename,lat,alt,time,nout,&
647     latdimout,londimout,altdimout,timedimout,lonvarout,timevarout)
648! Initialize output file's aps,bps variables
649call init2(infid,lonlength,latlength,altlength,&
650     nout,londimout,latdimout,altdimout)
651
652! 3.1.2 New longitude dimension/value in output file
653allocate(lon_fake(1))
654lon_fake(1)=0.
655#ifdef NC_DOUBLE
656        ierr= NF_PUT_VARA_DOUBLE(nout,lonvarout,1,1,lon_fake)
657#else
658        ierr= NF_PUT_VARA_REAL(nout,lonvarout,1,1,lon_fake)
659#endif
660
661! 3.1.3 New time dimension/value in output file
662#ifdef NC_DOUBLE
663        ierr= NF_PUT_VARA_DOUBLE(nout,timevarout,1,1,lon_fake)
664#else
665        ierr= NF_PUT_VARA_REAL(nout,timevarout,1,1,lon_fake)
666#endif
667
668
669!==============================================================================
670! 3.2 Write variables
671!==============================================================================
672
673!Define the dimensions of the variables to be written
674
675!!3.2.1 Stream function
676call def_var(nout,"psi","Stream function","",4,&
677             (/londimout,latdimout,altdimout,timedimout/),psivarout,ierr)
678if (ierr.ne.NF_NOERR) then
679   write(*,*) 'Error, could not define variable psi'
680   stop ""
681endif
682
683!Write in the output file
684ierr=NF_PUT_VAR_REAL(nout,psivarout,psi)
685if (ierr.ne.NF_NOERR) then
686   write(*,*)'Error, Failed to write variable psi'
687   stop
688endif
689
690!3.2.2 Momentum
691call def_var(nout,"momave","Angular momentum","",4,&
692             (/londimout,latdimout,altdimout,timedimout/),momvarout,ierr)
693if (ierr.ne.NF_NOERR) then
694   write(*,*) 'Error, could not define variable momave'
695   stop ""
696endif
697
698!Write in the output file
699ierr=NF_PUT_VAR_REAL(nout,momvarout,momave)
700if (ierr.ne.NF_NOERR) then
701   write(*,*)'Error, Failed to write variable momave'
702   stop
703endif
704
705
706!3.2.3 Zonal mean zonal wind
707call def_var(nout,"u","Zonal mean zonal wind","m/s",4,&
708             (/londimout,latdimout,altdimout,timedimout/),uvarout,ierr)
709if (ierr.ne.NF_NOERR) then
710   write(*,*) 'Error, could not define variable u'
711   stop ""
712endif
713
714!Write in the output file
715ierr=NF_PUT_VAR_REAL(nout,uvarout,uzm)
716if (ierr.ne.NF_NOERR) then
717   write(*,*)'Error, Failed to write variable u'
718   stop
719endif
720
721
722!3.2.4 Zonal mean meridional wind
723call def_var(nout,"v","Zonal mean meridional wind","m/s",4,&
724             (/londimout,latdimout,altdimout,timedimout/),vvarout,ierr)
725if (ierr.ne.NF_NOERR) then
726   write(*,*) 'Error, could not define variable v'
727   stop ""
728endif
729
730!Write in the output file
731ierr=NF_PUT_VAR_REAL(nout,vvarout,vzm)
732if (ierr.ne.NF_NOERR) then
733   write(*,*)'Error, Failed to write variable v'
734   stop
735endif
736
737!3.2.5 Zonal mean density
738call def_var(nout,"rho","Zonal mean atmospheric density","",4,&
739             (/londimout,latdimout,altdimout,timedimout/),rhovarout,ierr)
740if (ierr.ne.NF_NOERR) then
741   write(*,*) 'Error, could not define variable rho'
742   stop ""
743endif
744
745!Write in the output file
746ierr=NF_PUT_VAR_REAL(nout,rhovarout,rhozm)
747if (ierr.ne.NF_NOERR) then
748   write(*,*)'Error, Failed to write variable rho'
749   stop
750endif
751
752!3.2.6 Zonal mean temperature
753call def_var(nout,"temp","Zonal mean temperature","K",4,&
754             (/londimout,latdimout,altdimout,timedimout/),tempvarout,ierr)
755if (ierr.ne.NF_NOERR) then
756   write(*,*) 'Error, could not define variable temp'
757   stop ""
758endif
759
760!Write in the output file
761ierr=NF_PUT_VAR_REAL(nout,tempvarout,tempzm)
762if (ierr.ne.NF_NOERR) then
763   write(*,*)'Error, Failed to write variable temp'
764   stop
765endif
766
767!3.2.7 Zonal mean surface pressure
768call def_var(nout,"ps","Zonal mean surface pressure","Pa",3,&
769             (/londimout,latdimout,timedimout/),psvarout,ierr)
770if (ierr.ne.NF_NOERR) then
771   write(*,*) 'Error, could not define variable ps'
772   stop ""
773endif
774
775!Write in the output file
776ierr=NF_PUT_VAR_REAL(nout,psvarout,pszm)
777if (ierr.ne.NF_NOERR) then
778   write(*,*)'Error, Failed to write variable ps'
779   stop
780endif
781
782
783!3.2.8 Zonal mean geopotential
784call def_var(nout,"phisinit","Zonal mean initial geopotential","",2,&
785             (/londimout,latdimout/),phisinitvarout,ierr)
786if (ierr.ne.NF_NOERR) then
787   write(*,*) 'Error, could not define variable phisinit'
788   stop ""
789endif
790
791!Write in the output file
792ierr=NF_PUT_VAR_REAL(nout,phisinitvarout,phisinitzm)
793if (ierr.ne.NF_NOERR) then
794   write(*,*)'Error, Failed to write variable phisinit'
795   stop
796endif
797
798! Close input file
799ierr=nf_close(nid)
800
801! Close output file
802ierr=NF_CLOSE(nout)
803
804contains
805
806!******************************************************************************
807Subroutine initiate (filename,lat,alt,time,&
808                     nout,latdimout,londimout,altdimout,timedimout,&
809                     lonvarout,timevarout)
810!==============================================================================
811! Purpose:
812! Create and initialize a data file (NetCDF format)
813!==============================================================================
814! Remarks:
815! The NetCDF file (created in this subroutine) remains open
816!==============================================================================
817
818implicit none
819
820include "netcdf.inc" ! NetCDF definitions
821
822!==============================================================================
823! Arguments:
824!==============================================================================
825character (len=*), intent(in):: filename
826! filename(): the file's name
827real, dimension(:), intent(in):: lat
828! lat(): latitude
829real, dimension(:), intent(in):: alt
830! alt(): altitude
831real, dimension(:), intent(in):: time
832! time(): Time
833integer, intent(out):: nout
834! nout: [netcdf] file ID
835integer, intent(out):: latdimout
836! latdimout: [netcdf] lat() (i.e.: latitude)  ID
837integer, intent(out):: londimout
838! londimout: [netcdf] lon()  ID
839integer, intent(out):: altdimout
840! altdimout: [netcdf] alt()  ID
841integer, intent(out):: timedimout
842! timedimout: [netcdf] "Time"  ID
843integer, intent(out):: lonvarout
844! timevarout: [netcdf] Longiture (considered as a variable) ID
845integer, intent(out):: timevarout
846! timevarout: [netcdf] Time (considered as a variable) ID
847
848!==============================================================================
849! Local variables:
850!==============================================================================
851!integer :: latdim,londim,altdim,timedim
852integer :: nvarid,ierr
853! nvarid: [netcdf] ID of a variable
854! ierr: [netcdf]  return error code (from called subroutines)
855
856!==============================================================================
857! 1. Create (and open) output file
858!==============================================================================
859write(*,*) "creating "//trim(adjustl(filename))//'...'
860ierr = NF_CREATE(filename,NF_CLOBBER,nout)
861! NB: setting NF_CLOBBER mode means that it's OK to overwrite an existing file
862if (ierr.NE.NF_NOERR) then
863   WRITE(*,*)'ERROR: Impossible to create the file.'
864   stop ""
865endif
866
867!==============================================================================
868! 2. Define/write "dimensions" and get their IDs
869!==============================================================================
870
871ierr = NF_DEF_DIM(nout, "latitude", size(lat), latdimout)
872!ierr = NF_DEF_DIM(nout, "longitude", NF_UNLIMITED, londimout)
873ierr = NF_DEF_DIM(nout, "longitude", 1, londimout)
874ierr = NF_DEF_DIM(nout, "altitude", size(alt), altdimout)
875ierr = NF_DEF_DIM(nout, "Time", 1, timedimout)
876
877! End netcdf define mode
878ierr = NF_ENDDEF(nout)
879
880!==============================================================================
881! 3. Write "Time" (attributes)
882!==============================================================================
883
884call def_var(nout,"Time","Time","years since 0000-00-0 00:00:00",1,&
885             (/timedimout/),timevarout,ierr)
886
887!==============================================================================
888! 4. Write "latitude" (data and attributes)
889!==============================================================================
890
891call def_var(nout,"latitude","latitude","degrees_north",1,&
892             (/latdimout/),nvarid,ierr)
893
894#ifdef NC_DOUBLE
895ierr = NF_PUT_VAR_DOUBLE (nout,nvarid,lat)
896#else
897ierr = NF_PUT_VAR_REAL (nout,nvarid,lat)
898#endif
899
900!==============================================================================
901! 4. Write "longitude" (attributes)
902!==============================================================================
903
904call def_var(nout,"longitude","East longitude","degrees_east",1,&
905             (/londimout/),lonvarout,ierr)
906
907
908!==============================================================================
909! 4. Write "altitude" (data and attributes)
910!==============================================================================
911
912! Switch to netcdf define mode
913
914call def_var(nout,"altitude","Altitude","km",1,&
915             (/altdimout/),nvarid,ierr)
916
917#ifdef NC_DOUBLE
918ierr = NF_PUT_VAR_DOUBLE (nout,nvarid,alt)
919#else
920ierr = NF_PUT_VAR_REAL (nout,nvarid,alt)
921#endif
922
923end Subroutine initiate
924!******************************************************************************
925subroutine init2(infid,lonlen,latlen,altlen, &
926                 outfid,londimout,latdimout,altdimout)
927!==============================================================================
928! Purpose:
929! Copy aps() and bps() from input file to outpout file
930!==============================================================================
931! Remarks:
932! The NetCDF files must be open
933!==============================================================================
934
935implicit none
936
937include "netcdf.inc" ! NetCDF definitions
938
939!==============================================================================
940! Arguments:
941!==============================================================================
942integer, intent(in) :: infid  ! NetCDF output file ID
943integer, intent(in) :: lonlen ! # of grid points along longitude
944integer, intent(in) :: latlen ! # of grid points along latitude
945integer, intent(in) :: altlen ! # of grid points along latitude
946integer, intent(in) :: outfid ! NetCDF output file ID
947integer, intent(in) :: londimout ! longitude dimension ID
948integer, intent(in) :: latdimout ! latitude dimension ID
949integer, intent(in) :: altdimout ! altitude dimension ID
950!==============================================================================
951! Local variables:
952!==============================================================================
953real,dimension(:),allocatable :: aps,bps ! hybrid vertical coordinates
954integer :: apsid,bpsid
955integer :: ierr
956integer :: tmpvarid ! temporary variable ID
957logical :: aps_ok, bps_ok ! are "phisinit" "aps" "bps" available ?
958
959
960!==============================================================================
961! 1. Read data from input file
962!==============================================================================
963
964! hybrid coordinate aps
965  allocate(aps(altlen))
966ierr=NF_INQ_VARID(infid,"aps",tmpvarid)
967if (ierr.ne.NF_NOERR) then
968  write(*,*) "oops Failed to get aps ID. OK"
969  aps_ok=.false.
970else
971  ierr=NF_GET_VAR_REAL(infid,tmpvarid,aps)
972  if (ierr.ne.NF_NOERR) then
973   stop "error: Failed reading aps"
974  endif
975  aps_ok=.true.
976endif
977
978! hybrid coordinate bps
979  allocate(bps(altlen))
980ierr=NF_INQ_VARID(infid,"bps",tmpvarid)
981if (ierr.ne.NF_NOERR) then
982  write(*,*) "oops: Failed to get bps ID. OK"
983  bps_ok=.false.
984else
985  ierr=NF_GET_VAR_REAL(infid,tmpvarid,bps)
986  if (ierr.ne.NF_NOERR) then
987    stop "Error: Failed reading bps"
988  endif
989  bps_ok=.true.
990endif
991
992!==============================================================================
993! 2. Write
994!==============================================================================
995
996!==============================================================================
997! 2.2. Hybrid coordinates aps() and bps()
998!==============================================================================
999
1000IF (aps_ok) then
1001   ! define aps
1002   call def_var(nout,"aps","hybrid pressure at midlayers"," ",1,&
1003        (/altdimout/),apsid,ierr)
1004   if (ierr.ne.NF_NOERR) then
1005      stop "Error: Failed to def_var aps"
1006   endif
1007
1008   ! write aps
1009#ifdef NC_DOUBLE
1010   ierr=NF_PUT_VAR_DOUBLE(outfid,apsid,aps)
1011#else
1012   ierr=NF_PUT_VAR_REAL(outfid,apsid,aps)
1013#endif
1014   if (ierr.ne.NF_NOERR) then
1015      stop "Error: Failed to write aps"
1016   endif
1017ENDIF
1018
1019IF (bps_ok) then
1020   ! define bps
1021   call def_var(nout,"bps","hybrid sigma at midlayers"," ",1,&
1022        (/altdimout/),bpsid,ierr)
1023   if (ierr.ne.NF_NOERR) then
1024      stop "Error: Failed to def_var bps"
1025   endif
1026
1027   ! write bps
1028#ifdef NC_DOUBLE
1029   ierr=NF_PUT_VAR_DOUBLE(outfid,bpsid,bps)
1030#else
1031   ierr=NF_PUT_VAR_REAL(outfid,bpsid,bps)
1032#endif
1033   if (ierr.ne.NF_NOERR) then
1034      stop "Error: Failed to write bps"
1035   endif
1036ENDIF
1037
1038
1039
1040! Cleanup
1041deallocate(aps)
1042deallocate(bps)
1043
1044end subroutine init2
1045!******************************************************************************
1046subroutine def_var(nid,name,title,units,nbdim,dim,nvarid,ierr)
1047!==============================================================================
1048! Purpose: Write a variable (i.e: add a variable to a dataset)
1049! called "name"; along with its attributes "title", "units"...
1050! to a file (following the NetCDF format)
1051!==============================================================================
1052! Remarks:
1053! The NetCDF file must be open
1054!==============================================================================
1055
1056implicit none
1057
1058include "netcdf.inc" ! NetCDF definitions
1059
1060!==============================================================================
1061! Arguments:
1062!==============================================================================
1063integer, intent(in) :: nid
1064! nid: [netcdf] file ID #
1065character (len=*), intent(in) :: name
1066! name(): [netcdf] variable's name
1067character (len=*), intent(in) :: title
1068! title(): [netcdf] variable's "title" attribute
1069character (len=*), intent(in) :: units
1070! unit(): [netcdf] variable's "units" attribute
1071integer, intent(in) :: nbdim
1072! nbdim: number of dimensions of the variable
1073integer, dimension(nbdim), intent(in) :: dim
1074! dim(nbdim): [netcdf] dimension(s) ID(s)
1075integer, intent(out) :: nvarid
1076! nvarid: [netcdf] ID # of the variable
1077integer, intent(out) :: ierr
1078! ierr: [netcdf] subroutines returned error code
1079
1080! Switch to netcdf define mode
1081ierr=NF_REDEF(nid)
1082
1083! Insert the definition of the variable
1084#ifdef NC_DOUBLE
1085ierr=NF_DEF_VAR(nid,adjustl(name),NF_DOUBLE,nbdim,dim,nvarid)
1086#else
1087ierr=NF_DEF_VAR(nid,adjustl(name),NF_FLOAT,nbdim,dim,nvarid)
1088#endif
1089
1090! Write the attributes
1091ierr=NF_PUT_ATT_TEXT(nid,nvarid,"title",len_trim(adjustl(title)),adjustl(title))
1092ierr=NF_PUT_ATT_TEXT(nid,nvarid,"units",len_trim(adjustl(units)),adjustl(units))
1093
1094! End netcdf define mode
1095ierr=NF_ENDDEF(nid)
1096
1097end subroutine def_var
1098
1099end program streamfunction
1100
1101subroutine init_planet_const(infid)
1102! initialize planetary constants using the "controle" array in the file
1103! if "controle" array not found in file, look for it in "diagfi.nc"
1104use planet_const
1105use netcdf
1106implicit none
1107
1108integer,intent(in) :: infid ! input file ID
1109
1110! local variables
1111character(len=100) :: varname
1112integer :: varid ! variable ID
1113integer :: status
1114integer :: infid2 ! for an alternate input file
1115real :: controle(100) ! to store "controle" array
1116
1117! look for "controle" in input file
1118infid2=infid ! initialization
1119varname="controle"
1120status=nf90_inq_varid(infid,trim(varname),varid)
1121if (status.ne.nf90_noerr) then
1122  write(*,*) "init_planet_const: Failed to find ",trim(varname)
1123  write(*,*) " looking for it in file diagfi.nc"
1124  status=nf90_open("diagfi.nc",NF90_NOWRITE,infid2)
1125  if (status.ne.nf90_noerr) then
1126    write(*,*) " no diafi.nc file ... looking for diagfi1.nc"
1127    status=nf90_open("diagfi1.nc",NF90_NOWRITE,infid2)
1128    if (status.ne.nf90_noerr) then
1129      write(*,*) "might as well stop here..."
1130      stop
1131    endif
1132  endif
1133  status=nf90_inq_varid(infid2,trim(varname),varid)
1134  if (status.ne.nf90_noerr) then
1135    write(*,*) " Failed to find ",trim(varname)," in file!!"
1136    stop
1137  endif
1138  write(*,*) "OK, found ",trim(varname)
1139endif
1140status=nf90_get_var(infid2,varid,controle)
1141if (status.ne.nf90_noerr) then
1142  write(*,*) "init_planet_const: Failed to load ",trim(varname)
1143  stop
1144endif
1145
1146! now that we have "controle"; extract relevent informations
1147a0=controle(5) ! = radius of planet (m)
1148g0=controle(7) ! = gravity (m.s-2) at a0
1149Rmean=1000.*8.3144598/controle(8) ! controle(8)=mugaz = molar mass (g.mol-1) of atm.
1150omega=controle(6) ! rotation rate (rad.s-1)
1151
1152end subroutine init_planet_const
Note: See TracBrowser for help on using the repository browser.