Subversion Repositories lagranto.um

Rev

Go to most recent revision | Details | Last modification | View Log | RSS feed

Rev Author Line No. Line
16 michaesp 1
      program pp2cdf
2
      implicit none
3
C
4
C     Purpose.
5
C     --------
6
C
7
C       Reads UKMO MM pressure data and writes the data to a NetCDF-file.
8
C       It works on 20 pressure levels, and uses stashcodes 90003 and 90004 
9
C       (u and v wrt model grid).
10
C
11
C     Interface.
12
C     ----------
13
C
14
C       File with MM data attached as unit 8.
15
C       File with NetCDF filename and missing data flag is unit 15.
16
C       Varfile (variable informations) attached as unit 12.
17
C
18
C     Reference.
19
C     ----------
20
C
21
C       None.
22
C
23
C     Author.
24
C     -------
25
C
26
C
27
C     Modifications.
28
C     --------------
29
C
30
C       None.
31
C
32
C     -----------------------------------------------------------------
33
C
34
 
35
CCC   Include your netcdf.inc
36
      include 'netcdf.inc'
37
CCC   Include UM dimensions(nxmax,nymax,nzmax,ntmax)
38
      include 'um_dims.inc'
39
C     ===  definitions of routinespecific variables  =======================
40
 
41
CCC   maximum array dimensions (change them for your purpose)
42
      integer   nxi,nyi,nlevmax,nwet
43
      real      pmin,pmax,pdiff
44
      parameter(nlevmax=nzmax)
45
      parameter(nxi=nxmax-2,nyi=nymax-2)
46
 
47
      real      fld(nxmax,nymax)
48
      real	field(nxi*nyi)
49
      real	pstar(nxmax,nymax)
50
      real	data(nxi,nyi)
51
      real      varmin(3), varmax(3), stag(3)
52
      integer   vardim(4)
53
      real      mdv
54
      integer	datar(14),idate(5),stdate(5),cstid
55
      integer	lev,cdfid
56
      real	tstep
57
      real	aklev(nlevmax),bklev(nlevmax),aklay(nlevmax),bklay(nlevmax)
58
      real	latn,lats,lonw,lone,dx,dy,pole_lon,pole_lat
59
      real      p1,p2,pex1,pex2,exner,pres,plevs(nlevmax)
60
      integer	nx,ny,nlev,nvars,ntimes,tcode,qcode,pcode
61
      integer	i,j,ierr,iform,ieee,stash_code,iend,ilev
62
      integer	dyear,dmonth,dday,dhour,dmins
63
      logical	opnfile
64
      integer	strend,saveplevs,tind,irec
65
      integer	done_u,done_v,done_t,done_q,done_o,done_p
66
      character*80 cfn,wrcstflag,cdfname,varname
67
      logical    NewDyn
68
 
69
c     include 'ABmeso31.f'     ! define Hybrid coord. coefficients
70
 
71
C R IS GAS CONSTANT FOR DRY AIR
72
C CP IS SPECIFIC HEAT OF DRY AIR AT CONSTANT PRESSURE
73
C PREF IS REFERENCE SURFACE PRESSURE
74
      REAL R,CP,KAPPA,PREF  ! PREFTOKI
75
      PARAMETER(R=287.05,CP=1005.0,KAPPA=R/CP,PREF=100000.0)
76
!     PARAMETER(pmin=1000.0,pmax=200.0,pdiff=25.0,pcode=409)
77
 
78
      character*200 infile
79
      character*60 cdf_file,ctime*2,char1*1,ext1*2,ext2*2,date_str*2
80
 
81
      write(*,*)'===  start of program pp2cdf_p20 ===  (+++)'
82
      write(*,*)'===  This Program works on UKMM pressure level data'
83
 
84
C     Read parameters from input-file fort.15
85
 
86
      read(15,'(a)') infile		! name of PP Format input file
87
      read(15,'(a)') cdfname	! name of NetCDF file
88
      read(15,'(a)') wrcstflag	! write-cst-file flag
89
      read(15,'(a)') cfn           ! name of constants file
90
      read(15,*) mdv			! missing data value
91
      read(15,*) tcode             ! stash code of T/Theta field
92
      read(15,*) qcode             ! stash code of Q field
93
      read(15,*) pcode             ! stash code of PS field
94
      read(15,*) pmin              ! min value of PS field
95
      read(15,*) pmax              ! max. value of PS field
96
      read(15,*) pdiff             ! level difference of PS field
97
      read(15,*) NewDyn            ! New Dynamics (version 5 onwards)
98
C      write(*,*) NewDyn
99
C     write(*,*)pmin, pmax, pdiff39C     Define constants file name
100
 
101
      if (cfn.eq.'default') then
102
        cfn=trim(cdfname)//'_cst'
103
      endif
104
      opnfile=.false.
105
      nvars=0
106
      ntimes=1
107
 
108
C     ======================================================
109
C     Start of loop to write specified fields on NetCDF file
110
C     loop 30 --> goto 30
111
C     ======================================================
112
 
113
      iform=0
114
      ieee=1
115
      irec=0
116
      done_u=0
117
      done_v=0
118
      done_t=0
119
      done_q=0
120
      done_o=0
121
      done_p=0
122
      saveplevs=0
123
      nlev=pmax  !50.0
124
      call open_ppf(infile,iform,ieee)  ! open PP Format input file
125
 
126
   30 continue
127
 
128
CCC   call here a subroutine that reads 1 variable on 1 level from
129
CCC   a data file
130
CCC   call another subroutine or do everything in one, as you like,
131
CCC   that gets some general information about the data
132
CCC   anyhow, what you do here should define the following parameters:
133
 
134
C     dyear	integer		year of date valid for current field
135
C     dmonth	integer		month of date valid for current field
136
C     dday	integer		day of date valid for current field
137
C     dhour	integer		hour of date valid for current field
138
C     dmins	integer		minute of date valid for current field
139
 
140
C     lonw	real		coordinates of data domain (in deg):
141
C     lone	real		      latn
142
C     lats	real       	 lonw --|-- lone
143
C     late	real		      lats
144
C     dx	real		grid size in W-E direction (in deg)
145
C     dy	real		grid size in S-N direction (in deg)
146
C     nx	integer	number of data points in W-E direction
147
C     ny	integer	number of data points in S-N direction
148
C     nlev	integer	number of data levels
149
 
150
C     stash_code	integer	your field code
151
C     lev	integer	number of the level for the current field
152
C     fld 	real		2-dim array with dimensions (nx,ny),
153
C				contains the field values
154
 
155
CCC   ... call here your subroutine(s)...
156
      call read_field(iform,nx,ny,fld,stash_code,lev,
157
     &     dx,dy,dyear,dmonth,dday,dhour,dmins,iend,
158
     &     lonw,lone,latn,lats,pole_lon,pole_lat,pres,nxmax,nymax,
159
     &     NewDyn)
160
c      write(*,*)'stash and level',stash_code,lev,iend,pres
161
      if(iend.eq.1) goto 999
162
 
163
CCC   Determine the name of the variable from the field code 'num'
164
CCC   If a variable is not in the list, it is not written to the NetCDF file
165
      if (stash_code.eq.90003) then
166
        varname='U'			! zonal velocity
167
        if(lev.eq.nlev) done_u=1
168
c       if(saveplevs.lt.nlevmax+1) then
169
c         if(saveplevs.eq.0) tind=1
170
c         plevs(tind)=pres
171
c         tind=tind+1
172
c       endif
173
      else if (stash_code.eq.90004) then
174
        varname='V'			! meridional velocity
175
        if(lev.eq.nlev) done_v=1
176
      else if (stash_code.eq.90087) then
177
        varname='OMEGA'			! vertical velocity
178
        if(lev.eq.nlev) done_o=1
179
      else if (stash_code.eq.tcode) then
180
        varname='T'			! temperature
181
        if(lev.eq.nlev) done_t=1
182
c if Theta supplied then convert to Temp
183
        if(tcode.eq.90006) then
184
          do j = 1,ny
185
            do i = 1,nx
186
c     form Temp. at full levels from Theta
187
              exner=(pres/pref)**kappa
188
              fld(i,j)=fld(i,j)*exner
189
            enddo
190
          enddo
191
        endif
192
      else if (stash_code.eq.pcode ) then
193
        varname='PS'			! surface pressure
194
cwang   nlev=1
195
cwang   lev=1        ! reset lev to 1 from 9999
196
        done_p=1
197
        do j = 1,ny
198
          do i = 1,nx
199
            pstar(i,j)=fld(i,j)
200
            fld(i,j)=fld(i,j)/100.0    ! Pstar needed in hPa
201
          enddo
202
        enddo
203
      else if (stash_code.eq.qcode) then
204
        varname='Q'			! specific humidity
205
        if(lev.eq.nlev) done_q=1
206
      else
207
        goto 30				! don't put fld on NetCDF file
208
      endif
209
 
210
      irec=irec+1
211
c     N.B. U, V and Omega are all on P-Grid
212
        do i=1,nxi
213
          do j=1,nyi
214
            data(i,j)=fld(i+1,j+1)
215
          enddo
216
        enddo
217
 
218
C     Define staggering coefficients
219
CCC   change the ??? to your num-value for vertical velocity
220
 
221
      stag(1)=0.0
222
      stag(2)=0.0
223
      stag(3)=0.0
224
c     if (stash_code.eq.???) then	! no staggering for vertical velocity
225
c       stag(3)=0.0
226
c     else
227
c       stag(3)=-0.5		! vertical staggering for all other variables
228
c     endif
229
 
230
C     Define data region
231
 
232
      varmin(1)=lonw
233
      varmin(2)=lats
234
      varmax(1)=lone
235
      varmax(2)=latn
236
C     varmin/max(3) changed to take into account reverse order of data
237
      varmin(3)=pmin   ! Not used
238
      varmax(3)=pmax  !50.0
239
      write(*,*) 'lonw,lats,lone,latn',lonw,lats,lone,latn
240
      write(*,*) 'pmax, pmin',pmax, pmin 
241
 
242
C     Define dimensions
243
 
244
      vardim(1)=nxi
245
      vardim(2)=nyi
246
CCC   Distinction between 2dim and 3dim fields
247
CCC   Insert num-values for 2dim fields
248
      if (stash_code.eq.pcode) then
249
        vardim(3)=1
250
      else
251
        vardim(3)=nlevmax
252
      endif
253
      vardim(4)=1
254
 
255
C     Define the date array
256
 
257
      idate(1)=dyear
258
      idate(2)=dmonth
259
      idate(3)=dday
260
      idate(4)=dhour
261
      idate(5)=dmins
262
 
263
C     set stdate on first read of PP record from file
264
 
265
c     if (irec.eq.1) then
266
c     endif
267
      if (wrcstflag.eq.'yes') then
268
 
269
C       stdate is the simulation start time
270
        stdate(1)=dyear
271
        stdate(2)=dmonth
272
        stdate(3)=dday
273
        stdate(4)=dhour
274
        stdate(5)=dmins
275
C       Define the datar array (used to define constants file)
276
 
277
        datar(1)=nxi
278
        datar(2)=nyi
279
        datar(3)=nint(1000.0*latn) ! I agree this is not nice
280
        datar(4)=nint(1000.0*lonw) ! but for historical reasons
281
        datar(5)=nint(1000.0*lats) ! subroutine wricst contains
282
        datar(6)=nint(1000.0*lone) ! this factor 1000. things
283
        datar(7)=nint(1000.0*dx)
284
        datar(8)=nint(1000.0*dy)
285
        datar(9)=nlevmax  ! just in case Pstar first in file
286
        datar(10)=0         ! not used
287
        datar(11)=0         ! not used
288
        datar(12)=0         ! not used
289
        datar(13)=nint(1000.0*pole_lon)
290
        datar(14)=nint(1000.0*pole_lat)
291
 
292
C       Get the 4 levels/layers arrays
293
C NH: changed to modplevs from modlevs
294
 
295
        call modplevs(aklev,bklev,aklay,bklay,plevs,nlevmax,pmin,pdiff)
296
 
297
C       Write the constants file
298
 
299
        call wricst(cfn,datar,aklev,bklev,aklay,bklay,stdate)
300
        write(*,*)
301
        write(*,*)'*** constants-file ',trim(cfn),' created'
302
        wrcstflag='no'
303
      else           ! assume that the constants-file already exists
304
C       Inquire start time
305
        call cdfopn(cfn,cstid,ierr)              ! open constants file
306
        call getstart(cstid,stdate,ierr)
307
        call ncclos(cstid,ierr)                  ! close constants file
308
      endif
309
 
310
C     Create the NetCDF file (only once)
311
 
312
      if (.not.opnfile) then
313
c    Code to derive Index No. for filenames
314
c       if(ntimes.lt.10) then
315
c         write(char1,'(i1)') ntimes
316
c         ctime='0'//char1
317
c       else
318
c         write(ctime,'(i2)') ntimes
319
c       endif
320
c       cdf_file=trim(cdfname)//ctime
321
c    Code to derive timestamp for filenames
322
c       dhour=dhour-stdate(4)  ! subtract start time so always atart at 0
323
        if(dhour.eq.0) then
324
          ext1='00'
325
        elseif(dhour.lt.10) then
326
          write(char1,'(i1)') dhour
327
          ext1='0'//char1
328
        else
329
          write(ext1,'(i2)') dhour
330
        endif
331
        if(dmins.lt.10) then
332
          write(char1,'(i1)') dmins 
333
          ext2='0'//char1
334
        else
335
          write(ext2,'(i2)') dmins
336
        endif
337
c       n.b if data runs into next day then can't use root of first
338
c       filename for rest, so form filename manually
339
c       cdf_file=trim(cdfname)//ext1//ext2
340
c       below assumes year and month are constant
341
        if(dday.lt.10) then
342
          write(char1,'(i1)') dday
343
          date_str='0'//char1
344
        else
345
          write(date_str,'(i2)') dday
346
        endif
347
cSue modify to get expected structure for new trajectory code
348
        cdf_file=cdfname(1:7)//date_str//'_'//ext1//ext2
349
        call crecdf(cdf_file,cdfid,varmin,varmax,
350
     &              3,trim(cfn),ierr)
351
        if (ierr.ne.0) goto 996
352
        write(*,*)
353
c       write(*,*)'*** NetCDF file ',trim(cdfname),' create
354
        write(*,*)'*** NetCDF file ',cdf_file,' created'
355
        opnfile=.true.
356
      endif
357
 
358
C     Put 2dim array in 1dim array
359
 
360
      do i=1,nxi
361
        do j=1,nyi
362
          field(i+(j-1)*nxi)=data(i,j)
363
        enddo
364
      enddo
365
 
366
C     Calculate tstep for actual date (relative to first time of
367
c     simulation) and convert to minutes
368
 
369
      call timediff(idate,stdate,tstep)
370
c     tstep=tstep*100.0
371
c     tstep=float(nint(tstep*100.0))
372
      write(6,*)"idate,stdate,tstep:",idate,stdate,tstep
373
cSue - leave in hours for new traj code  
374
c         i=ifix(tstep)  ! round down to nearest hour
375
c         tstep=float(i*60+nint(100.0*tstep)-100*i)
376
cwang     ilev=1+((1000-lev)/50) this should be changed to /25     
377
cwang     change ilev=1+((1000-lev)/50) statement when pdiff read in
378
      write(6,*)"tstep:",tstep
379
      ilev=1+((pmin-lev)/pdiff)
380
      if(stash_code.eq.pcode) ilev=1
381
 
382
      if (ilev.eq.1) then
383
        call putdef(cdfid,trim(varname),4,mdv,vardim,
384
     &              varmin,varmax,stag,ierr)
385
        if (ierr.ne.0) goto 996
386
        write(*,*)
387
        write(*,*)'*** variable ',trim(varname),' created'
388
        nvars=nvars+1
389
      endif
390
 
391
C     Put data on file
392
 
393
c     Convert units of Temp to Degrees C
394
      if (stash_code.eq.90002.or.stash_code.eq.90006) then
395
        do i=1,nxi*nyi
396
          field(i)=field(i)-273.15
397
        enddo
398
      endif
399
 
400
      write(*,*)
401
      write(*,'(a,a,a,f7.1,a,i4,a)')'*** var ',
402
     &  trim(varname),' at time ',
403
     &  tstep,' on level ',lev,' written on cdffile'
404
      call putdat(cdfid,trim(varname),tstep,ilev,
405
     &  field,ierr)
406
      if (ierr.ne.0) goto 996
407
      write(*,*)'cdfid',cdfid
408
c     if(nvars.eq.6.and.lev.eq.nlev) then   ! required variables written
409
      write(*,*)done_u,done_v,done_t,done_q,done_o,done_p
410
      if(done_u+done_v+done_t+done_q+done_o+done_p.eq.6) then
411
        opnfile=.false.
412
        ntimes=ntimes+1
413
        nvars=0
414
C     Close NetCDF file
415
 
416
        call ncclos(cdfid,ierr)
417
        if (ierr.ne.0) stop 'error when closing NetCDF file'
418
c       if(ntimes.eq.2) stop
419
        done_u=0
420
        done_v=0
421
        done_t=0
422
        done_q=0
423
        done_o=0
424
        done_p=0
425
      endif
426
      goto 30
427
 
428
  996 stop 'error: could not create NetCDF file'
429
  999 continue
430
      write(*,*)lev,nlev,ierr
431
      if(lev.gt.nlev.or.ierr.ne.0) then
432
        write(*,*)'===  Error: NetCDF file: ',cdf_file,' incomplete'
433
        write(*,*)'See fort.12 for list of data processed'
434
        stop
435
      endif
436
 
437
      write(*,*)'===  end of program pp2cdf_p20: status normal  ==='
438
 
439
      stop
440
      end
441
 
442
      subroutine open_ppf(infile,iform,ieee)
443
C    I/O STREAMS ARE AS FOLLOWS
444
C     1) 6   STANDARD OUTPUT
445
C     2) 8   PPUNIT - READ UNIT FOR PP FILE
446
      IMPLICIT NONE
447
      INTEGER ierr,IFORM,IEEE
448
      CHARACTER INFILE*100
449
c
450
      IF(IFORM.EQ.1) THEN
451
        OPEN(UNIT=8,FILE=INFILE,FORM='FORMATTED')
452
      ELSE
453
        IF(IEEE.EQ.1) THEN
454
c     2 lines below are Cray specific calls to identify IEEE file
455
c     n.b 'newlocal' refers to assign environment, not file
456
c         call asnctl('newlocal',1,ierr)
457
c         write(*,*) 'ierr from asnctl ',ierr
458
c         call asnunit(8,'-F f77 -N ieee',ierr)
459
c         write(*,*) 'ierr from asnunit ',ierr
460
        ENDIF
461
        OPEN(UNIT=8,FILE=INFILE,FORM='UNFORMATTED')
462
      ENDIF
463
      return
464
      END
465
c********************************************************
466
      subroutine read_field(iform,nx,ny,data,stash_code,level,
467
     &     dxdeg,dydeg,dyear,dmonth,dday,dhour,dmins,iend,
468
     &     lonw,lone,latn,lats,pole_lon,pole_lat,pres,nxmax,nymax,
469
     &      NewDyn)
470
C    I/O STREAMS ARE AS FOLLOWS
471
C     1) 6   STANDARD OUTPUT
472
C     2) 8   PPUNIT - READ UNIT FOR PP FILE
473
C     3) 12  HEADER INFORMATION STREAM
474
      IMPLICIT NONE
475
c     
476
      REAL ROOK(19), FIELD(nxmax*nymax),data(nxmax,nymax)
477
      INTEGER LOOK(45),I,J,K,N,NUM_VALUES,NX,NY,IFORM,nxmax,nymax,
478
     &     nf,stash_code,level,dyear,dmonth,dday,dhour,dmins,iend
479
      real LONG1,LAT1,dxdeg,dydeg,long_nw,lat_nw,
480
     &     fac,lonw,lone,latn,lats,pole_lon,pole_lat,pres
481
      logical NewDyn
482
      data nf/0/
483
      save nf
484
      nf=nf+1
485
c
486
      IF(IFORM.EQ.1) THEN
487
        READ(8,12,END=99) LOOK
488
        READ(8,13) ROOK
489
      ELSE
490
        READ(8,END=99) LOOK,ROOK
491
      ENDIF
492
      NX=LOOK(19)
493
      NY=LOOK(18)
494
      NUM_VALUES=NX*NY
495
C     WRITE OUT CONTENTS OF INFILE FOR INFORMATION
496
      WRITE(12,106) LOOK(33),LOOK(14),nf,
497
     &      NUM_VALUES,LOOK(42),LOOK(18),LOOK(19)
498
      IF(IFORM.EQ.1) THEN
499
        READ(8,13) (FIELD(I),I=1,NUM_VALUES)
500
      ELSE
501
      write(*,*) '1'
502
        READ(8) (FIELD(I),I=1,NUM_VALUES)
503
      ENDIF
504
      write(*,*) '2'
505
      LEVEL=LOOK(33)
506
      stash_code=LOOK(42)
507
c     Assign exact time of field from "Validity time"
508
      dyear=look(1)
509
      if(dyear.gt.1900) dyear=dyear-1900   ! wants only year as 9?
510
      dmonth=look(2)
511
      dday=look(3)
512
      dhour=look(4)
513
      dmins=look(5)
514
      LONG1=ROOK(61-45)
515
      if(LONG1 .lt. 0.0 ) then 
516
        LONG1=LONG1+360.0
517
      endif
518
      LAT1=ROOK(59-45)
519
      dxdeg=abs(ROOK(62-45))
520
      dydeg=abs(ROOK(60-45))
521
cwang      write(*,*)'dxdy',ROOK(62-45),ROOK(60-45)
522
cwang      write(*,*)'LONG1Lat1',ROOK(61-45),ROOK(59-45)
523
      fac=0.0
524
c     if(stash_code.eq.2.or.stash_code.eq.3.or.stash_code.eq.12201)
525
c    &      fac=0.5
526
C PAC Verified 
527
      long_nw=LONG1+dxdeg-fac*dxdeg
528
cwang      lat_nw=Lat1-dydeg+fac*dydeg
529
c     define limits of inner 2:nxmax-1 X 2:nymax-1 grid
530
      lonw=long_nw+dxdeg
531
      lone=lonw+float(nxmax-3)*dxdeg
532
cwang change statements to calculate latn and lats
533
cwang to next if loop so that it counts for dy for positive condition
534
      if (.not. NewDyn) then 
535
        lat_nw=Lat1-dydeg+fac*dydeg
536
        latn=lat_nw-dydeg
537
        lats=latn-float(nymax-3)*dydeg
538
      else
539
C PAC Verified
540
        lat_nw=Lat1+dydeg-fac*dydeg
541
        lats=lat_nw+dydeg
542
        latn=lats+float(nymax-3)*dydeg
543
      endif
544
      pole_lon=ROOK(57-45)
545
      pole_lat=ROOK(56-45)
546
      pres=100.0*rook(52-45)  ! in Pa
547
C-------------------------------------------------------------------
548
 12   FORMAT(12I10)
549
 13   FORMAT(10E12.5)
550
  106 FORMAT(' LEVEL=',I5,' FCST=',I6,' FIELD NO',I4,' NVALS='
551
     &    ,I5,' STASH CODE=',I5,' NO.ROWS=',I3,' NO.COLUMNS=',I3)
552
  100 FORMAT('  THE NUMBER OF FIELDS IN THE INPUT FILE IS   ',I8)
553
C-----------------------Process Data--------------------------------
554
C     Data WRITTEN STARTING AT N-W CORNER, FOLLOWING LOOPS
555
C     ASSIGN DATA FROM S-W CORNER AND THEN WRITE OUT
556
      if (.not. NewDyn) then 
557
        write(*,*)'data read starting at N-W'
558
        DO J=NY-1,0,-1 !LOOP SOUTH-NORTH (ROWS)
559
          I=J*NX       !FIELD RUNS OPPOSITE
560
          DO N=1,NX
561
            DATA(N,NY-J)=FIELD(N+I)
562
          END DO
563
        END DO
564
      else
565
C PAC Verified
566
         write(*,*)'data read dstarting at S-W'
567
        DO J=1,NY
568
          DO N=1,NX
569
            DATA(N,J)=FIELD((J-1)*NX+N)
570
          END DO
571
        END DO
572
      endif
573
C     CODE TO PREVENT UNDERFLOWS ON CONVERSION TO IEEE
574
      DO J = 1,NY
575
        DO I = 1,NX
576
           IF(ABS(DATA(I,J)).LT.1.0E-30.AND.DATA(I,J).NE.0.0) THEN
577
c            WRITE(6,*) 'UNDERFLOW AT: ',I,J,DATA(I,J)
578
             DATA(I,J) = 0.0
579
           ENDIF
580
        END DO
581
      END DO
582
      iend=0
583
      return
584
 99   continue
585
      iend=1
586
      write(*,*) 'End of file reached'
587
      return
588
      END
589
      subroutine modplevs(aklev,bklev,aklay,bklay,plevs,nlevmax,pm,pd)
590
C NH: changed to modplevs from modlevs
591
C------------------------------------------------------------------------
592
C
593
C     Defines the level- and layer-arrays given the number of levels nlev.
594
C
595
C     nlev    int    input  number of levels/layers
596
C     aklev   real   output array contains ak values for levels
597
C     bklev     real    output  array contains bk values for levels
598
C     aklay     real    output  array contains ak values for layers
599
C     bklay     real    output  array contains bk values for layers
600
C------------------------------------------------------------------------
601
 
602
      integer   nlev,k
603
 
604
      real      aklev(nlevmax),bklev(nlevmax),    ! level coefficients
605
     &          aklay(nlevmax),bklay(nlevmax)     ! layer coefficients
606
     &         ,plevs(nlevmax)
607
 
608
      do k=1,nlevmax
609
        aklay(k)=0.0
610
        bklay(k)=0.0
611
c       aklev(k)=plevs(k)/100.0    ! P needed in hPa
612
        aklev(k)=(pm-(k-1)*pd)    ! P needed in hPa
613
        bklev(k)=0.0
614
      enddo
615
      return
616
      end