updated top-level README and version_decl for V4.5 (#1847)
[WRF.git] / var / gen_be / gen_be_read_regcoeffs.f90
blobf54c6c283e4787da742d93fe5cb4b9163a694a3a
1 program gen_be_read_regcoeffs
3 !-------------------------------------------------------------------------------------------
4 ! Purpose: Read regression coefficients from BE file and write out in format
5 ! required for input to gen_be_stage2 (used for ep calculation).
7 ! Owner: Dale Barker
9 !-------------------------------------------------------------------------------------------
11 usa da_control, only : filename_len
13 implicit none
15 integer, parameter :: unit = 10 ! I/O unit.
17 character(len=filename_len) :: filename ! Input filename.
18 character*3 :: be_method ! Be method ('NMC', or 'ENS')
19 integer :: ni, nj, nk ! Dimensions read in.
20 integer :: bin_type ! Type of bin to average over. !!!DALE ADD.
21 integer :: num_bins ! Number of 3D bins.
22 integer :: num_bins2d ! Number of 2D bins.
23 real :: lat_min, lat_max ! Used if bin_type = 2 (degrees).
24 real :: binwidth_lat ! Used if bin_type = 2 (degrees). !!!DALE ADD..
25 real :: binwidth_hgt ! Used if bin_type = 2 (m). !!!DALE ADD..
26 real :: hgt_min, hgt_max ! Used if bin_type = 2 (m).
28 integer, allocatable:: bin(:,:,:) ! Bin assigned to each 3D point.
29 integer, allocatable:: bin2d(:,:) ! Bin assigned to each 2D point.
30 real, allocatable :: regcoeff1(:) ! psi/chi regression cooefficient.
31 real, allocatable :: regcoeff2(:,:) ! psi/ps regression cooefficient.
32 real, allocatable :: regcoeff3(:,:,:) ! psi/T regression cooefficient.
34 stderr = 0
35 stdout = 6
37 be_method = "ENS" ! Hardwired for now!
39 !----------------------------------------------------------------------------
40 ! [1] Read regression coefficients.
41 !----------------------------------------------------------------------------
43 filename = 'gen_be.'//trim(be_method)//'.dat'
44 open (unit, file = filename, form='unformatted')
46 ! Read the dimensions:
47 read(unit)ni, nj, nk
49 allocate( bin(1:ni,1:nj,1:nk) )
50 allocate( bin2d(1:ni,1:nj) )
52 ! Read bin info:
53 read(unit)bin_type
54 read(unit)lat_min, lat_max, binwidth_lat
55 read(unit)hgt_min, hgt_max, binwidth_hgt
56 read(unit)num_bins, num_bins2d
57 read(unit)bin(1:ni,1:nj,1:nk)
58 read(unit)bin2d(1:ni,1:nj)
60 ! Read the regression coefficients:
61 allocate( regcoeff1(1:num_bins) )
62 allocate( regcoeff2(1:nk,1:num_bins2d) )
63 allocate( regcoeff3(1:nk,1:nk,1:num_bins2d) )
65 read(unit)regcoeff1
66 read(unit)regcoeff2
67 read(unit)regcoeff3
69 close(unit)
71 !----------------------------------------------------------------------------
72 ! [2] Write regression coefficients.
73 !----------------------------------------------------------------------------
75 filename = 'gen_be_stage2.'//trim(be_method)//'.dat'
76 open (unit, file = filename, form='unformatted')
77 write(unit)ni, nj, nk
78 write(unit)num_bins, num_bins2d
79 write(unit)regcoeff1
80 write(unit)regcoeff2
81 write(unit)regcoeff3
82 close(unit)
84 deallocate( bin )
85 deallocate( bin2d )
86 deallocate( regcoeff1 )
87 deallocate( regcoeff2 )
88 deallocate( regcoeff3 )
90 end program gen_be_read_regcoeffs