source: trunk/UTIL/SPECTRA/test_harmonic.f90 @ 3352

Last change on this file since 3352 was 1404, checked in by milmd, 10 years ago

Add the opportunity to create some harmonical wind fields for testing. Spherepack library can also be compiled with ifort.

File size: 9.9 KB
Line 
1!M. Indurain
2!March 2015
3
4PROGRAM lmdz_harmonic
5
6!Computes wind field following some vectorial harmonics with spherepack routines.
7!Wind field follows lmdz convention:
8!  u(nlong+1,nlat) zonal eastward wind, v(nlong+1,nlat) latitudinal wind
9!Grid resolution is given in the command line:
10!./test_harmonic -lat n_latitudinal_bands -lon n_longitudinal_bands.
11!By default, n_latitudinal_bands = 48. n_longitudinal_bands = 64.
12
13use netcdf
14
15implicit none
16
17!List of harmonics we want
18 character (len=100), dimension(5) :: harmonic=(/'2','10','22','6_3','15_20'/)
19!Physical grid
20integer :: nlat,nlatm1,nlong,nlongp1
21double precision, dimension(:), allocatable :: latitude,longitude
22double precision, dimension(:,:), allocatable :: merid_wind,zonal_wind !spherepack convention
23double precision, dimension(:,:), allocatable :: merid_wind_lmdz,zonal_wind_lmdz !lmdz convention
24!Spectral grid
25integer :: mmax !spectra truncation mmax=min(nalt,nlong/2) or min(nalt,(nlong+1)/2)
26double precision, dimension (:,:), allocatable :: br,bi,cr,ci !spectra coefficients
27double precision, dimension (:,:), allocatable :: norm,norm_b,norm_c !norm of spectra coefficients
28double precision, dimension (:), allocatable :: spectra,spectra_b,spectra_c
29!Spherepack declarations
30integer :: ierror,lvhsec,ldwork,lwork,l1,l2,nt=1,ityp=0,idvw,jdvw,mdab,ndab
31double precision, dimension (:), allocatable :: wvhsec,work
32double precision, dimension (:), allocatable :: dwork
33!Netcdf stuff
34integer :: idfile,idmerid_wind,idzonal_wind
35integer :: idlat,idlong,idlat_var,idlong_var
36integer :: idmdab,idndab,idbr,idbi,idcr,idci
37integer :: idspectra,idspectra_b,idspectra_c
38character (len=100) :: file_netcdf
39!Other
40integer :: i,j,k
41double precision, parameter :: pi=2.*ASIN(1.)
42character (len=100) :: tmp_char
43!Input arguments
44character (len=100), dimension(:), allocatable :: arg
45integer :: narg
46
47!**********
48!Initialisation
49nlatm1=48
50nlong=64
51
52!**********
53!Input reading
54narg = command_argument_count()
55allocate(arg(narg))
56do i = 1, narg
57  call get_command_argument(i,arg(i))
58end do
59i = 1
60do while (i .le. narg)
61  if (arg(i) == '-lat' .or. arg(i) == '-lon') then
62    select case(arg(i))
63    case('-lat')
64      read(arg(i+1),'(i10)' ) nlatm1 !number of latitudinal bands               
65    case('-lon')
66      read(arg(i+1),'(i10)' ) nlong !number of longitudinal bands
67    end select
68    i = i + 2
69  elseif (arg(i) == '-h' .or. arg(i) == '--help') then
70      print*,'Usage\n test_harmonic [option]\n [-h or --help]\t: brief help'
71      print*,'[-lat int]\t: number of latitudinal bands (default: 48)'
72      print*,'[-lon int]\t: number of longitudinal bands (default: 64)'
73      stop 'End help'
74  else
75    print*,'No option ',trim(arg(i))
76    stop
77  end if
78end do
79
80!**********
81!Physical grid
82nlat=nlatm1+1
83nlongp1=nlong+1
84print*,'harmonics computed on a ',nlatm1,' latitude bands x ',nlong,' longitude bands.'
85
86allocate(latitude(nlat))
87allocate(longitude(nlongp1))
88do j=1,nlat
89        latitude(j)=90.-(j-1)*180./(nlat-1)
90end do
91do i=1,nlongp1
92        longitude(i)=-180.+(i-1)*2*180./nlong
93end do
94allocate(zonal_wind(nlat,nlong))
95allocate(merid_wind(nlat,nlong))
96allocate(zonal_wind_lmdz(nlongp1,nlat))
97allocate(merid_wind_lmdz(nlongp1,nlat))
98
99!#####
100!Spectra computation
101!#####
102!**********Maximum value for m
103if (mod(nlong,2) == 0) then
104  mmax = min(nlat,nlong/2)
105else
106  mmax = min(nlat,(nlong+1)/2)
107end if
108
109!**********Vhaeci function (initialisations for Vhaec function)
110if (mod(nlong,2) == 0) then
111  l1 = min(nlat,nlong/2)
112else
113  l1 = min(nlat,(nlong+1)/2)
114end if
115if (mod(nlat,2) == 0) then
116  l2 = nlat/2
117else
118  l2 = (nlat+1)/2
119end if
120lvhsec=4*nlat*l2+3*max(l1-2,0)*(nlat+nlat-l1-1)+nlong+15
121allocate(wvhsec(lvhsec))
122wvhsec(:) = 0.
123ldwork=2*(nlat+2)
124allocate(dwork(ldwork))
125dwork(:) = 0.
126ierror=3
127call vhseci(nlat,nlong,wvhsec,lvhsec,dwork,ldwork,ierror)
128 
129!**********Vhseci function result
130select case (ierror)
131  case(1)
132    print*,'Vhseci: ERROR on nlat'
133  case(2)
134    print*,'Vhseci: ERROR on nlong'
135  case(3)
136    print*,'Vhseci: ERROR on lvhsec'
137  case(4)
138    print*,'Vhseci: ERROR on ldwork'
139end select
140
141!**********Loop over all harmonics
142do k=1,SIZE(harmonic)
143file_netcdf='harmonic_'//trim(integer2string(nlongp1-1))//'x'//&
144                trim(integer2string(nlat-1))//'_lmdz_'//trim(harmonic(k))//'.nc'
145
146!**********Vhsec function
147idvw=nlat
148jdvw=nlong
149mdab=mmax
150ndab=nlat
151allocate(br(mdab,ndab))
152allocate(bi(mdab,ndab))
153allocate(cr(mdab,ndab))
154allocate(ci(mdab,ndab))
155br(:,:) = 0.
156bi(:,:) = 0.
157cr(:,:) = 0.
158ci(:,:) = 0.
159select case(harmonic(k))
160  case('2')
161    br(3,3)=1.
162  case('10')
163    br(11,11)=1.
164  case('22')
165    br(23,23)=1.
166  case('6_3')
167    br(4,4)=1.
168    br(7,7)=1.
169  case('15_20')
170    br(16,16)=1.
171    br(21,21)=1.
172end select
173if (mod(nlong,2) == 0) then
174  l1 = min(nlat,nlong/2)
175else
176  l1 = min(nlat,(nlong+1)/2)
177end if
178if (mod(nlat,2) == 0) then
179  l2 = nlat/2
180else
181  l2 = (nlat+1)/2
182end if
183lvhsec=4*nlat*l2+3*max(l1-2,0)*(nlat+nlat-l1-1)+nlong+15
184if (ityp .le. 2) then
185  lwork=nlat*(2*nt*nlong+max(6*l2,nlong))
186else
187  lwork=l2*(2*nt*nlong+max(6*nlat,nlong))
188end if
189allocate(work(lwork))
190work(:) = 0.
191ierror=3
192call vhsec(nlat,nlong,ityp,nt,merid_wind,zonal_wind,idvw,jdvw,br,bi,cr,ci,mdab,ndab,wvhsec,lvhsec,work,lwork,ierror)
193
194!**********Vhsec function result
195select case (ierror)
196  case(1)
197    print*,'Vhsec: ERROR on nlat'
198  case(2)
199    print*,'Vhsec: ERROR on nlong'
200  case(3)
201    print*,'Vhsec: ERROR on ityp'
202  case(4)
203    print*,'Vhsec: ERROR on nt'
204  case(5)
205    print*,'Vhsec: ERROR on idvw'
206  case(6)
207    print*,'Vhsec: ERROR on jdvw'
208  case(7)
209    print*,'Vhsec: ERROR on mdab'
210  case(8)
211    print*,'Vhsec: ERROR on ndab'
212  case(9)
213    print*,'Vhsec: ERROR on lvhsec'
214  case(10)
215    print*,'Vhsec: ERROR on lwork'
216end select
217
218!**********Energy spectra
219allocate(norm(mMax,nLat))
220allocate(norm_b(mMax,nLat))
221allocate(norm_c(mMax,nLat))
222do i = 1,mMax
223do j = 1,nLat
224  norm(i,j)=(br(i,j)*br(i,j)+bi(i,j)*bi(i,j)+cr(i,j)*cr(i,j)+ci(i,j)*ci(i,j))
225  norm_b(i,j)=(br(i,j)*br(i,j)+bi(i,j)*bi(i,j))
226  norm_c(i,j)=(cr(i,j)*cr(i,j)+ci(i,j)*ci(i,j))
227end do
228end do
229allocate(spectra(nLat))
230allocate(spectra_b(nLat))
231allocate(spectra_c(nLat))
232do j = 1,nLat
233  spectra(j) = 0.5*norm(1,j)
234  spectra_b(j) = 0.5*norm_b(1,j)
235  spectra_c(j) = 0.5*norm_c(1,j)
236  do i = 2,mMax
237    spectra(j) = spectra(j) + norm(i,j)
238    spectra_b(j) = spectra_b(j) + norm_b(i,j)
239    spectra_c(j) = spectra_c(j) + norm_c(i,j)
240  end do
241end do
242
243!**********From spherepack to lmdz convention
244zonal_wind_lmdz(1:nlong,:)=transpose(zonal_wind(:,:))
245merid_wind_lmdz(1:nlong,:)=transpose(merid_wind(:,:))
246zonal_wind_lmdz(nlongp1,:)=zonal_wind_lmdz(1,:)
247merid_wind_lmdz(nlongp1,:)=merid_wind_lmdz(1,:)
248
249!**********Write netcdf file
250  call check(nf90_create(trim(file_netcdf),NF90_CLOBBER,idfile))
251 
252  call check( nf90_def_dim(idfile,"mdab",mdab,idmdab))
253  call check( nf90_def_dim(idfile,"ndab",ndab,idndab))
254  call check(nf90_def_var(idfile,"br",NF90_DOUBLE,(/idmdab,idndab/),idbr))
255  call check(nf90_def_var(idfile,"bi",NF90_DOUBLE,(/idmdab,idndab/),idbi))
256  call check(nf90_def_var(idfile,"cr",NF90_DOUBLE,(/idmdab,idndab/),idcr))
257  call check(nf90_def_var(idfile,"ci",NF90_DOUBLE,(/idmdab,idndab/),idci))
258  call check(nf90_def_var(idfile,"spectra",NF90_DOUBLE,(/idndab/),idspectra))
259  call check(nf90_def_var(idfile,"spectra_div",NF90_DOUBLE,(/idndab/),idspectra_b))
260  call check(nf90_def_var(idfile,"spectra_vort",NF90_DOUBLE,(/idndab/),idspectra_c))
261 
262  call check( nf90_def_dim(idfile,"latitude",nlat,idlat))
263  call check( nf90_def_dim(idfile,"longitude",nlongp1,idlong))
264  call check(nf90_def_var(idfile,"latitude",NF90_DOUBLE,(/idlat/),idlat_var))
265  call check(nf90_def_var(idfile,"longitude",NF90_DOUBLE,(/idlong/),idlong_var))
266  call check(nf90_def_var(idfile,"u",NF90_DOUBLE,(/idlong,idlat/),idzonal_wind))
267  call check(nf90_def_var(idfile,"v",NF90_DOUBLE,(/idlong,idlat/),idmerid_wind))
268  ! End define mode. This tells netCDF we are done defining metadata.
269  call check(nf90_enddef(idfile))
270
271  ! Write the pretend data to the file. Although netCDF supports
272  ! reading and writing subsets of data, in this case we write all the
273  ! data in one operation.
274  call check(nf90_put_var(idfile,idbr,br))
275  call check(nf90_put_var(idfile,idbi,bi))
276  call check(nf90_put_var(idfile,idcr,cr))
277  call check(nf90_put_var(idfile,idci,ci))
278  call check(nf90_put_var(idfile,idspectra,spectra))
279  call check(nf90_put_var(idfile,idspectra_b,spectra_b))
280  call check(nf90_put_var(idfile,idspectra_c,spectra_c))
281 
282  call check(nf90_put_var(idfile,idlat_var,latitude))
283  call check(nf90_put_var(idfile,idlong_var,longitude))
284  call check(nf90_put_var(idfile,idzonal_wind,zonal_wind_lmdz))
285  call check(nf90_put_var(idfile,idmerid_wind,merid_wind_lmdz))
286  ! Close the file. This frees up any internal netCDF resources
287  ! associated with the file, and flushes any buffers.
288  call check(nf90_close(idfile))
289
290  deallocate(br)
291  deallocate(bi)
292  deallocate(cr)
293  deallocate(ci)
294  deallocate(work)
295  deallocate(norm)
296  deallocate(norm_b)
297  deallocate(norm_c)
298  deallocate(spectra)
299  deallocate(spectra_b)
300  deallocate(spectra_c)
301 
302 
303  print*,trim(file_netcdf),' computed!'
304end do
305
306
307contains
308  subroutine check(status)
309    integer, intent (in) :: status
310   
311    if(status /= nf90_noerr) then
312      print *, trim(nf90_strerror(status))
313      stop "Stopped"
314    end if
315  end subroutine check 
316 
317  function integer2string(n)
318    implicit none
319    character(len=10) :: integer2string
320    integer, intent(in) :: n
321    integer :: nn
322
323    nn=n
324    if (n .lt. 0) nn=-n
325    if (nn .ge. 0 .and. nn .lt. 10) write(integer2string,'(i1)') nn
326    if (nn .ge. 10 .and. nn .lt. 100) write(integer2string,'(i2)') nn
327    if (nn .ge. 100 .and. nn .lt. 1000) write(integer2string,'(i3)') nn
328    if (nn .ge. 1000 .and. nn .lt. 10000) write(integer2string,'(i4)') nn
329    if (nn .ge. 10000 .and. nn .lt. 100000) write(integer2string,'(i4)') nn
330    if (nn .ge. 100000 .and. nn .lt. 1000000) write(integer2string,'(i4)') nn
331    if (nn .ge. 1000000 .and. nn .lt. 10000000) write(integer2string,'(i4)') nn
332    if (nn .ge. 10000000 .and. nn .lt. 100000000) write(integer2string,'(i4)') nn
333   
334  end function integer2string
335 
336END PROGRAM lmdz_harmonic
Note: See TracBrowser for help on using the repository browser.