Line data Source code
1 : !-------------------------------------------------------------------
2 : ! manages reading and interpolation of prescribed ozone
3 : ! Created by: Francis Vitt
4 : !-------------------------------------------------------------------
5 : module prescribed_ozone
6 :
7 : use shr_kind_mod, only : r8 => shr_kind_r8
8 : use cam_abortutils, only : endrun
9 : use spmd_utils, only : masterproc
10 : use tracer_data, only : trfld, trfile
11 : use cam_logfile, only : iulog
12 :
13 : implicit none
14 : private
15 : save
16 :
17 : type(trfld), pointer :: fields(:)
18 : type(trfile) :: file
19 :
20 : public :: prescribed_ozone_init
21 : public :: prescribed_ozone_adv
22 : public :: write_prescribed_ozone_restart
23 : public :: read_prescribed_ozone_restart
24 : public :: has_prescribed_ozone
25 : public :: prescribed_ozone_register
26 : public :: init_prescribed_ozone_restart
27 : public :: prescribed_ozone_readnl
28 :
29 : logical :: has_prescribed_ozone = .false.
30 : character(len=8), parameter :: ozone_name = 'ozone'
31 :
32 : character(len=16) :: fld_name = 'ozone'
33 : character(len=256) :: filename = ' '
34 : character(len=256) :: filelist = ' '
35 : character(len=256) :: datapath = ' '
36 : character(len=32) :: data_type = 'SERIAL'
37 : logical :: rmv_file = .false.
38 : integer :: cycle_yr = 0
39 : integer :: fixed_ymd = 0
40 : integer :: fixed_tod = 0
41 :
42 : contains
43 :
44 : !-------------------------------------------------------------------
45 : !-------------------------------------------------------------------
46 2304 : subroutine prescribed_ozone_register()
47 : use ppgrid, only: pver, pcols
48 : use physics_buffer, only : pbuf_add_field, dtype_r8
49 :
50 : integer :: oz_idx
51 :
52 1536 : if (has_prescribed_ozone) then
53 1536 : call pbuf_add_field(ozone_name,'physpkg',dtype_r8,(/pcols,pver/),oz_idx)
54 :
55 : endif
56 :
57 1536 : endsubroutine prescribed_ozone_register
58 :
59 : !-------------------------------------------------------------------
60 : !-------------------------------------------------------------------
61 1536 : subroutine prescribed_ozone_init()
62 :
63 1536 : use tracer_data, only : trcdata_init
64 : use cam_history, only : addfld
65 :
66 : implicit none
67 :
68 : integer :: ndx, istat
69 : character(len=32) :: specifier(1)
70 :
71 1536 : if ( has_prescribed_ozone ) then
72 1536 : if ( masterproc ) then
73 2 : write(iulog,*) 'ozone is prescribed in :'//trim(filename)
74 : endif
75 : else
76 : return
77 : endif
78 :
79 1536 : specifier(1) = trim(ozone_name)//':'//trim(fld_name)
80 :
81 :
82 1536 : allocate(file%in_pbuf(size(specifier)))
83 3072 : file%in_pbuf(:) = .true.
84 : call trcdata_init( specifier, filename, filelist, datapath, fields, file, &
85 1536 : rmv_file, cycle_yr, fixed_ymd, fixed_tod, data_type)
86 :
87 : call addfld(ozone_name, (/ 'lev' /), &
88 3072 : 'I','mol/mol', 'prescribed ozone' )
89 :
90 1536 : end subroutine prescribed_ozone_init
91 :
92 : !-------------------------------------------------------------------
93 : !-------------------------------------------------------------------
94 1536 : subroutine prescribed_ozone_readnl(nlfile)
95 :
96 1536 : use namelist_utils, only: find_group_name
97 : use units, only: getunit, freeunit
98 : use mpishorthand
99 :
100 : character(len=*), intent(in) :: nlfile ! filepath for file containing namelist input
101 :
102 : ! Local variables
103 : integer :: unitn, ierr
104 : character(len=*), parameter :: subname = 'prescribed_ozone_readnl'
105 :
106 : character(len=16) :: prescribed_ozone_name
107 : character(len=256) :: prescribed_ozone_file
108 : character(len=256) :: prescribed_ozone_filelist
109 : character(len=256) :: prescribed_ozone_datapath
110 : character(len=32) :: prescribed_ozone_type
111 : logical :: prescribed_ozone_rmfile
112 : integer :: prescribed_ozone_cycle_yr
113 : integer :: prescribed_ozone_fixed_ymd
114 : integer :: prescribed_ozone_fixed_tod
115 :
116 : namelist /prescribed_ozone_nl/ &
117 : prescribed_ozone_name, &
118 : prescribed_ozone_file, &
119 : prescribed_ozone_filelist, &
120 : prescribed_ozone_datapath, &
121 : prescribed_ozone_type, &
122 : prescribed_ozone_rmfile, &
123 : prescribed_ozone_cycle_yr, &
124 : prescribed_ozone_fixed_ymd, &
125 : prescribed_ozone_fixed_tod
126 : !-----------------------------------------------------------------------------
127 :
128 : ! Initialize namelist variables from local module variables.
129 1536 : prescribed_ozone_name = fld_name
130 1536 : prescribed_ozone_file = filename
131 1536 : prescribed_ozone_filelist = filelist
132 1536 : prescribed_ozone_datapath = datapath
133 1536 : prescribed_ozone_type = data_type
134 1536 : prescribed_ozone_rmfile = rmv_file
135 1536 : prescribed_ozone_cycle_yr = cycle_yr
136 1536 : prescribed_ozone_fixed_ymd= fixed_ymd
137 1536 : prescribed_ozone_fixed_tod= fixed_tod
138 :
139 : ! Read namelist
140 1536 : if (masterproc) then
141 2 : unitn = getunit()
142 2 : open( unitn, file=trim(nlfile), status='old' )
143 2 : call find_group_name(unitn, 'prescribed_ozone_nl', status=ierr)
144 2 : if (ierr == 0) then
145 2 : read(unitn, prescribed_ozone_nl, iostat=ierr)
146 2 : if (ierr /= 0) then
147 0 : call endrun(subname // ':: ERROR reading namelist')
148 : end if
149 : end if
150 2 : close(unitn)
151 2 : call freeunit(unitn)
152 : end if
153 :
154 : #ifdef SPMD
155 : ! Broadcast namelist variables
156 1536 : call mpibcast(prescribed_ozone_name, len(prescribed_ozone_name), mpichar, 0, mpicom)
157 1536 : call mpibcast(prescribed_ozone_file, len(prescribed_ozone_file), mpichar, 0, mpicom)
158 1536 : call mpibcast(prescribed_ozone_filelist, len(prescribed_ozone_filelist), mpichar, 0, mpicom)
159 1536 : call mpibcast(prescribed_ozone_datapath, len(prescribed_ozone_datapath), mpichar, 0, mpicom)
160 1536 : call mpibcast(prescribed_ozone_type, len(prescribed_ozone_type), mpichar, 0, mpicom)
161 1536 : call mpibcast(prescribed_ozone_rmfile, 1, mpilog, 0, mpicom)
162 1536 : call mpibcast(prescribed_ozone_cycle_yr, 1, mpiint, 0, mpicom)
163 1536 : call mpibcast(prescribed_ozone_fixed_ymd,1, mpiint, 0, mpicom)
164 1536 : call mpibcast(prescribed_ozone_fixed_tod,1, mpiint, 0, mpicom)
165 : #endif
166 :
167 : ! Update module variables with user settings.
168 1536 : fld_name = prescribed_ozone_name
169 1536 : filename = prescribed_ozone_file
170 1536 : filelist = prescribed_ozone_filelist
171 1536 : datapath = prescribed_ozone_datapath
172 1536 : data_type = prescribed_ozone_type
173 1536 : rmv_file = prescribed_ozone_rmfile
174 1536 : cycle_yr = prescribed_ozone_cycle_yr
175 1536 : fixed_ymd = prescribed_ozone_fixed_ymd
176 1536 : fixed_tod = prescribed_ozone_fixed_tod
177 :
178 : ! Turn on prescribed volcanics if user has specified an input dataset.
179 1536 : if (len_trim(filename) > 0 .and. filename.ne.'NONE') has_prescribed_ozone = .true.
180 :
181 1536 : end subroutine prescribed_ozone_readnl
182 :
183 : !-------------------------------------------------------------------
184 : !-------------------------------------------------------------------
185 741888 : subroutine prescribed_ozone_adv( state, pbuf2d)
186 :
187 : use tracer_data, only : advance_trcdata
188 : use physics_types,only : physics_state
189 : use ppgrid, only : begchunk, endchunk
190 : use ppgrid, only : pcols, pver
191 : use string_utils, only : to_lower, GLC
192 : use cam_history, only : outfld
193 : use cam_control_mod, only: aqua_planet
194 : use phys_control, only : cam_physpkg_is
195 : use physconst, only : mwdry ! molecular weight dry air ~ kg/kmole
196 : use physconst, only : boltz ! J/K/molecule
197 :
198 : use physics_buffer, only : physics_buffer_desc, pbuf_get_chunk, pbuf_get_field, pbuf_set_field
199 :
200 : implicit none
201 :
202 : type(physics_state), intent(in) :: state(begchunk:endchunk)
203 :
204 : type(physics_buffer_desc), pointer :: pbuf2d(:,:)
205 :
206 370944 : type(physics_buffer_desc), pointer :: pbuf_chnk(:)
207 : integer :: c,ncol
208 : real(r8) :: to_mmr(pcols,pver)
209 : real(r8) :: molmass
210 : real(r8) :: amass
211 : real(r8) :: outdata(pcols,pver)
212 370944 : real(r8),pointer :: tmpptr(:,:)
213 :
214 : character(len=32) :: units_str
215 :
216 370944 : if( .not. has_prescribed_ozone ) return
217 :
218 370944 : molmass = 47.9981995_r8
219 370944 : amass = mwdry
220 :
221 370944 : call advance_trcdata( fields, file, state, pbuf2d )
222 :
223 370944 : units_str = trim(to_lower(trim(fields(1)%units(:GLC(fields(1)%units)))))
224 :
225 : ! set the correct units and invoke history outfld
226 : !$OMP PARALLEL DO PRIVATE (C, NCOL, OUTDATA, TO_MMR, TMPPTR, PBUF_CHNK)
227 1866312 : do c = begchunk,endchunk
228 1495368 : ncol = state(c)%ncol
229 :
230 : select case ( units_str )
231 : case ("molec/cm3","/cm3","molecules/cm3","cm^-3","cm**-3")
232 0 : to_mmr(:ncol,:) = (molmass*1.e6_r8*boltz*state(c)%t(:ncol,:))/(amass*state(c)%pmiddry(:ncol,:))
233 : case ('kg/kg','mmr')
234 0 : to_mmr(:ncol,:) = 1._r8
235 : case ('mol/mol','mole/mole','vmr','fraction')
236 2323627992 : to_mmr(:ncol,:) = molmass/amass
237 : case default
238 0 : write(iulog,*) 'prescribed_ozone_adv: units = ',trim(fields(1)%units) ,' are not recognized'
239 1495368 : call endrun('prescribed_ozone_adv: units are not recognized')
240 : end select
241 :
242 1495368 : pbuf_chnk => pbuf_get_chunk(pbuf2d, c)
243 1495368 : call pbuf_get_field(pbuf_chnk, fields(1)%pbuf_ndx, tmpptr )
244 :
245 2323627992 : tmpptr(:ncol,:) = tmpptr(:ncol,:)*to_mmr(:ncol,:)
246 :
247 2323627992 : outdata(:ncol,:) = (amass/molmass)* tmpptr(:ncol,:) ! vmr
248 547779960 : call outfld( fields(1)%fldnam, outdata(:ncol,:), ncol, state(c)%lchnk )
249 : enddo
250 :
251 741888 : end subroutine prescribed_ozone_adv
252 :
253 : !-------------------------------------------------------------------
254 :
255 1536 : subroutine init_prescribed_ozone_restart( piofile )
256 370944 : use pio, only : file_desc_t
257 : use tracer_data, only : init_trc_restart
258 : implicit none
259 : type(file_desc_t),intent(inout) :: pioFile ! pio File pointer
260 :
261 1536 : call init_trc_restart( 'prescribed_ozone', piofile, file )
262 :
263 1536 : end subroutine init_prescribed_ozone_restart
264 : !-------------------------------------------------------------------
265 1536 : subroutine write_prescribed_ozone_restart( piofile )
266 1536 : use tracer_data, only : write_trc_restart
267 : use pio, only : file_desc_t
268 : implicit none
269 :
270 : type(file_desc_t) :: piofile
271 :
272 1536 : call write_trc_restart( piofile, file )
273 :
274 1536 : end subroutine write_prescribed_ozone_restart
275 :
276 : !-------------------------------------------------------------------
277 768 : subroutine read_prescribed_ozone_restart( pioFile )
278 1536 : use tracer_data, only : read_trc_restart
279 : use pio, only : file_desc_t
280 : implicit none
281 :
282 : type(file_desc_t) :: piofile
283 :
284 768 : call read_trc_restart( 'prescribed_ozone', piofile, file )
285 :
286 768 : end subroutine read_prescribed_ozone_restart
287 :
288 : end module prescribed_ozone
|