sractl.f90 13 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416
  1. program srvctl
  2. ! SERVICE to GrADS format converter
  3. ! INPUT (on commandline):
  4. ! arg#1: name of inputfile with data in SERVICE-format
  5. ! The program assumes that the records of the file in SERVICE format
  6. ! are in the order produced by the PUMABURNER or AFTERBURNER program,
  7. ! i. e. the sequence and the number of codes for each timestep must not
  8. ! vary in the inputfile, different levels of one code at one timestep
  9. ! must be ordered and in sequence. Usually this is not a problem.
  10. !
  11. ! The order is (because GrADS assumes this): level - code - time
  12. !
  13. ! Author: Simon Blessing (blessing(at)dkrz.de), 27.11.2000
  14. ! Last maintenance: Oct. 27, 2004, got rid of complaint by sunf90
  15. ! Jan. 1st, 2005, added recunit detection
  16. !
  17. implicit none
  18. type levlst
  19. integer :: level
  20. type (levlst), pointer :: next
  21. end type levlst
  22. type codelst
  23. integer :: code
  24. integer :: nlev
  25. type (codelst), pointer :: next
  26. end type codelst
  27. type (codelst), pointer :: cl_first, cl_help, codelist
  28. type (levlst), pointer :: ll_first, levlist, ll_help
  29. integer :: nlon, nlat, nlev,j, deltat,fdate,fhour,flev, nlevmax
  30. integer :: dd,mm,mi,yyyy
  31. integer :: ddl,mml,mil,yyyyl,lhour,ldate
  32. integer :: tdef=1
  33. integer :: nvar=1
  34. logical :: l_vsect=.false.
  35. real, allocatable :: si(:) !sinus of gaussian latitude
  36. real, parameter :: PI = 3.14159265359 ! Pi
  37. character*2 :: ut
  38. character*16 :: vform = '(a1,i3,i6,a,3i6)'
  39. integer,parameter :: maxdpm(12) =(/ 31,29,31,30,31,30,31,31,30,31,30,31/)
  40. character*3,parameter :: month(12) = (/'jan','feb','mar','apr','may','jun',&
  41. 'jul','aug','sep','oct','nov','dec'/)
  42. integer irec, i, narg
  43. integer ih(8) !header of the SERVICE file
  44. REAL, ALLOCATABLE :: x(:) !data array
  45. Character*255 filein, filedes,filesrv !filenames
  46. ! external iargc
  47. !==========================================================================
  48. narg=iargc()
  49. if (narg < 1) call usage
  50. call getarg(1,filein)
  51. if ( filein == '' .or. filein(1:1) == '-' ) call usage
  52. i = len_trim(filein)
  53. if (i > 4 .and. filein(i-3:i) == '.sra') i = i - 4
  54. filedes = filein(1:i) // '.ctl'
  55. filesrv = filein(1:i) // '.srv'
  56. if (narg > 1) call getarg(2,filedes)
  57. print*,'reading formatted service file <',trim(filein),'>'
  58. print*,'writing grads control file <',trim(filedes),'>'
  59. !
  60. ! Open the input file
  61. !
  62. open(1,File=filein,FORM='FORMATTED',status='OLD')
  63. open(21,file=filesrv,form='UNFORMATTED')
  64. !
  65. ! Read the first header to know the length of the data array
  66. !
  67. irec=0
  68. read (1,*,End=999) ih
  69. write (21) ih
  70. nlon = ih(5)
  71. nlat = ih(6)
  72. nlev = ih(2) !very first guess
  73. if (ih(2)==-1) l_vsect=.true.
  74. flev = ih(2) !remember first level in file
  75. fdate = ih(3) !first date in dataset
  76. fhour = ih(4) !first hour in dataset
  77. deltat = 1 !first guess
  78. nlevmax = 1 !first guess
  79. if ( NLAT .lt. 32 .or. NLAT .gt. 1000) then
  80. print*,ih
  81. print*,'Unusual number of Latitudes in header of inputfile:', &
  82. & ' "" ',filein(1:len_trim(filein)),'"" : ',NLAT
  83. if (nlat.gt.1000) then
  84. print*,'Exiting.'
  85. stop
  86. end if
  87. end if
  88. !
  89. ALLOCATE( x(ih(5)*ih(6)) )
  90. !
  91. ! Open the descriptor file (formatted, sequential)
  92. !
  93. Open (3,File=filedes,FORM='FORMATTED',ACCESS='SEQUENTIAL')
  94. !
  95. ! Calculate Gaussian latitudes
  96. !
  97. if (l_vsect) then
  98. print*,'Presuming ',nlon,' gaussian latitudes.'
  99. allocate (si(nlon))
  100. call inigau(nlon,si)
  101. else
  102. print*,'Presuming ',nlat,' gaussian latitudes.'
  103. allocate (si(nlat))
  104. call inigau(nlat,si)
  105. end if
  106. !
  107. ! Write to descriptor file what we know so far
  108. !
  109. write(3,'(2a)')'DSET ^',trim(filesrv)
  110. ! write(3,'(2a)')'TITLE ',name
  111. if (kind(x)==8) then
  112. write(3,'(a)')'UNDEF 9e+99'
  113. else
  114. write(3,'(a)')'UNDEF 9e+09'
  115. end if
  116. ! write(3,'(a)')'OPTIONS BIG_ENDIAN'
  117. if (l_vsect) then
  118. write(3,'(a,i6,a,f8.4,a,f8.4)')'XDEF ',1, &
  119. & ' LEVELS ',1.
  120. write(3,'(a)')'OPTIONS YREV'
  121. write(3,'(a,i6,a/(8f10.4))')'YDEF ',nlon, &
  122. & ' LEVELS ',-180./PI*asin(si(:))
  123. else
  124. write(3,'(a,i6,a,f8.4,a,f8.4)')'XDEF ',nlon, &
  125. & ' LINEAR ',0.,' ',(360./float(nlon))
  126. write(3,'(a)')'OPTIONS YREV'
  127. if (nlat.gt.1) then
  128. write(3,'(a,i6,a/(8f10.4))')'YDEF ',nlat, &
  129. & ' LEVELS ',-180./PI*asin(si(:))
  130. else
  131. write(3,'(a,i6,a,f8.4,a,f8.4)')'YDEF ',nlat, &
  132. & ' LINEAR ',0.,' ',180.
  133. end if
  134. end if
  135. write(3,'(A)') 'OPTIONS SEQUENTIAL'
  136. write(3,'(A)') 'XYHEADER 40'
  137. !
  138. ! Start list about codes and levels
  139. !
  140. nvar=1
  141. allocate(cl_first)
  142. cl_first%code=ih(1)
  143. cl_first%nlev=min(ih(2),1) !special treatment of level zero
  144. nullify(cl_first%next) !last in list so far; Lahey and VAST need this
  145. allocate(ll_first)
  146. ll_first%level=ih(2)
  147. nullify(ll_first%next) !last in list so far
  148. !
  149. ! Do the real work (read & write data)
  150. !
  151. irec = 1 !start record count
  152. do
  153. !
  154. ! Read the input data
  155. !
  156. read (1,*,END=999) x
  157. write(21) x
  158. !
  159. ! Do for the next record
  160. !
  161. read (1,*,End=999) ih
  162. write(21) ih
  163. irec = irec+1 !count records
  164. !
  165. ! count time
  166. !
  167. if ( ih(1)==cl_first%code.and.ih(2)==flev ) then
  168. !first code first level again?
  169. tdef=tdef+1 !so time must have advanced!
  170. end if
  171. !
  172. ! get first non-zero level
  173. !
  174. if (ll_first%level==0 .and. ih(2).ne.0) then
  175. ll_first%level=ih(2)
  176. end if
  177. !
  178. ! Work on codelist
  179. !
  180. codelist=>cl_first
  181. do while (ih(1).ne.codelist%code)
  182. if (.not. associated(codelist%next)) then !add new code to list
  183. cl_help=>codelist
  184. allocate(codelist)
  185. cl_help%next=>codelist
  186. nvar=nvar+1 !count codes
  187. codelist%code=ih(1)
  188. codelist%nlev=min(ih(2),1) !special treatment of level zero
  189. nullify(codelist%next) !this is last in list
  190. else
  191. codelist=>codelist%next !try next code in list
  192. end if
  193. end do
  194. ! count levels for that code
  195. if ( ih(2).ne.ll_first%level .and. ih(2).ne.0 .and. tdef==1 ) &
  196. & then
  197. !level information should be complete in
  198. !first time level so we are only looking there
  199. codelist%nlev=codelist%nlev+1 !code repeats at first~
  200. ! timelevel => must be new level and can't be zero
  201. levlist=>ll_first
  202. ! maintain list of levels
  203. do while (levlist%level.ne.ih(2))
  204. if (.not. associated(levlist%next)) then
  205. ll_help=>levlist
  206. allocate(levlist)
  207. ll_help%next=>levlist
  208. nullify(levlist%next)
  209. levlist%level=ih(2)
  210. nlevmax=nlevmax+1
  211. else
  212. levlist=>levlist%next !try next level in list
  213. end if
  214. end do
  215. end if
  216. end do
  217. 999 Continue
  218. if (irec==0) then
  219. print*,"*** No records processed. Input file was empty! ***"
  220. stop
  221. end if
  222. !
  223. ! write to descriptorfile levels and codes
  224. !
  225. if (l_vsect) then
  226. write(3,'(a,i4,a,i8,a)')'ZDEF ',nlat,' LINEAR ', &
  227. & abs(ll_first%level),' 1'
  228. else
  229. if (nlevmax==1) then
  230. write(3,'(a,i8,a)')'ZDEF 1 LINEAR ',ll_first%level,' 1'
  231. else
  232. write(3,'(a,i6,a)')'ZDEF ',nlevmax,' LEVELS '
  233. levlist=>ll_first
  234. do while (associated(levlist))
  235. write(3,'(i10)')levlist%level
  236. levlist=>levlist%next
  237. end do
  238. endif
  239. end if
  240. ! make a date
  241. ! fdate and ih(3) are of the form yyyymmdd
  242. ! extract first time:
  243. if (fhour.gt.99) then
  244. mi=mod(fhour,100)
  245. fhour=max(min(fhour/100,23),0)
  246. else
  247. fhour=max(min(fhour,23),0)
  248. mi=0
  249. end if
  250. ! extract first date
  251. mm=min(12,max(mod(fdate,10000)/100,1))
  252. dd=min(maxdpm(mm),max(mod(fdate,100),1))
  253. yyyy=max(1,min((fdate-100*mm-dd)/10000,9999)) !There is no year zero
  254. ! extract last time
  255. if (ih(4).gt.99) then
  256. mil=mod(ih(4),100)
  257. lhour=max(min(ih(4)/100,23),0)
  258. else
  259. lhour=max(min(ih(4),23),0)
  260. mil=0
  261. end if
  262. ! extract last date
  263. ddl=min(31,max(mod(ih(3),100),1))
  264. mml=min(12,max(mod(ih(3),10000)/100,1))
  265. yyyyl=max(1,min((ih(3)-100*mml-ddl)/10000,9999)) ! There is no year zero
  266. ! convert everything to minutes
  267. fdate=mi +60*(fhour+24*(dd +30*(mm +12*(yyyy )))) ! a modeler's month
  268. ldate=mil+60*(lhour+24*(ddl+30*(mml+12*(yyyyl)))) ! has 30 days :-)
  269. ! calculate time increment
  270. deltat=max(1,(ldate-fdate)/(max(tdef-1,1))) ! just let's be robust
  271. ! find appropriate unit for time increment
  272. ut='mn' ! fallback
  273. if (mod(deltat,60).eq.0) then
  274. deltat=deltat/60
  275. ut='hr'
  276. if (mod(deltat,24).eq.0) then
  277. deltat=deltat/24
  278. ut='dy'
  279. if (mod(deltat,30).eq.0) then
  280. deltat=deltat/30
  281. ut='mo'
  282. if (mod(deltat,12).eq.0) then
  283. deltat=deltat/12
  284. ut='yr'
  285. if (deltat.eq.0) then
  286. deltat=6
  287. ut='hr'
  288. print*,'Could not extract proper time increment.'
  289. print*,'Assuming 6-hourly data...'
  290. end if
  291. end if
  292. end if
  293. end if
  294. end if
  295. ! Was this complicated?
  296. ! We need a date string of the form hh:mmZddmmmyyyy
  297. write(3,'(a4,i6,a8,i2.2,a1,i2.2,a1,i2.2,a3,i4.4,i9,a2)') &
  298. & 'TDEF',tdef,' LINEAR ',fhour,':',mi,'Z',dd,month(mm), &
  299. & yyyy,deltat,ut
  300. ! write codelist
  301. write(3,'(a,i6)')'VARS ',nvar
  302. codelist=>cl_first
  303. do while(associated(codelist))
  304. write(vform(6:6),'(i1)') &
  305. & (min(9,1+int(log10(max(1.,real(codelist%code))))))!varying format
  306. if (l_vsect) codelist%nlev=nlat
  307. write(3,vform)'c',codelist%code, &
  308. & codelist%nlev,' 99 ',codelist%code,ih(7),ih(8)
  309. if (l_vsect) then
  310. print*,"level -1 detected, assuming vertical section with"
  311. print*,nlon,"latitudes and ",nlat," linear levels."
  312. else
  313. if (codelist%nlev.ne.0 .and. codelist%nlev.ne.nlevmax) then
  314. print*,'***CAUTION!*** code ',codelist%code, &
  315. & ' is not defined on all levels. '
  316. print*,'GrADS will assume that they are the first few', &
  317. & ' from the descriptor file: ',filedes
  318. end if
  319. end if
  320. codelist=>codelist%next
  321. end do
  322. write(3,'(a)')'ENDVARS'
  323. Write (*,*) 'Processed ', irec, ' record(s)'
  324. End
  325. subroutine usage
  326. implicit none
  327. print*,'Usage: srvctl <service file>'
  328. print*,'Example: srvctl z500.srv will create z500.ctl'
  329. stop
  330. end subroutine usage
  331. subroutine inigau(kl,pga)
  332. implicit none
  333. integer :: kl ! Number of Gaussian latitudes
  334. integer :: j0,j1 ! Loop index
  335. real :: pga(kl) ! Gaussian abscissas
  336. real (kind=8) :: pz0(kl) ! Gaussian abscissas
  337. real (kind=8), parameter :: pi = 3.14159265358979_8
  338. real (kind=8) :: z0,z1,z2,z3
  339. real (kind=8) :: ql,qld
  340. ! 1. Compute Gaussian abscissas
  341. z0 = pi / (2*kl+1)
  342. z1 = 1.0_8 / (kl*kl*8)
  343. do j0 = 1 , kl/2
  344. z2 = z0 * (2*j0 - 0.5_8)
  345. z2 = cos(z2 + z1 / tan(z2))
  346. do j1 = 1 , 50
  347. z3 = ql(kl,z2) / qld(kl,z2)
  348. z2 = z2 - z3
  349. if (abs(z3) < 1.0e-16) exit
  350. enddo ! j1
  351. ! print *,j1,' iter for lat= ',j0,' eps= ',z3
  352. pz0(j0) = z2
  353. pz0(kl-j0+1) = -z2
  354. enddo ! j0
  355. pga(:) = pz0(:) ! Double precision to native
  356. return
  357. end
  358. real (kind=8) function ql(k,p)
  359. implicit none
  360. integer :: k
  361. real (kind=8) :: p
  362. real (kind=8) :: z0,z1,z2,z3,z4
  363. integer :: j
  364. z0 = acos(p)
  365. z1 = 1.0
  366. z2 = 0.0
  367. do j = k , 0 , -2
  368. z3 = z1 * cos(z0 * j)
  369. z2 = z2 + z3
  370. z4 = (k-j+1) * (k+j) * 0.5
  371. z1 = z1 * z4 / (z4 + (j-1))
  372. enddo ! j
  373. if (mod(k,2) == 0) z2 = z2 - 0.5 * z3
  374. z0 = sqrt(2.0_8)
  375. do j = 1 ,k
  376. z0 = z0 * sqrt(1.0_8 - 0.25_8 / (j*j))
  377. enddo ! j
  378. ql = z0 * z2
  379. return
  380. end
  381. real (kind=8) function qld(k,p)
  382. implicit none
  383. integer :: k
  384. real (kind=8) :: p
  385. real (kind=8) :: z0,z1,z2,z3,z4
  386. real (kind=8) :: ql
  387. integer :: j
  388. if (k == 0) then
  389. qld = 0.0
  390. return
  391. endif
  392. z0 = 1.0 / (p*p - 1.0)
  393. z1 = k
  394. z2 = 2.0 * z1
  395. z3 = sqrt((z2 + 1.0) / (z2 - 1.0))
  396. z4 = p * ql(k,p) - z3 * ql(k-1,p)
  397. qld = z0 * z1 * z4
  398. return
  399. end