Line data Source code
1 : module atm_stream_ndep
2 :
3 : !-----------------------------------------------------------------------
4 : ! Contains methods for reading in nitrogen deposition data file
5 : ! Also includes functions for dynamic ndep file handling and
6 : ! interpolation.
7 : !-----------------------------------------------------------------------
8 : !
9 : use ESMF , only : ESMF_Clock, ESMF_Mesh
10 : use ESMF , only : ESMF_SUCCESS, ESMF_LOGERR_PASSTHRU, ESMF_END_ABORT
11 : use ESMF , only : ESMF_Finalize, ESMF_LogFoundError
12 : use nuopc_shr_methods , only : chkerr
13 : use dshr_strdata_mod , only : shr_strdata_type
14 : use shr_kind_mod , only : r8 => shr_kind_r8, CL => shr_kind_cl, CS => shr_kind_cs
15 : use shr_log_mod , only : errMsg => shr_log_errMsg
16 : use spmd_utils , only : mpicom, masterproc, iam
17 : use spmd_utils , only : mpi_character, mpi_integer
18 : use cam_logfile , only : iulog
19 : use cam_abortutils , only : endrun
20 :
21 : implicit none
22 : private
23 :
24 : public :: stream_ndep_init ! position datasets for dynamic ndep
25 : public :: stream_ndep_interp ! interpolates between two years of ndep file data
26 :
27 : private :: stream_ndep_check_units ! Check the units and make sure they can be used
28 :
29 : type(shr_strdata_type) :: sdat_ndep ! input data stream
30 : logical, public :: stream_ndep_is_initialized = .false.
31 : character(len=CS) :: stream_varlist_ndep(2)
32 : type(ESMF_Clock) :: model_clock
33 :
34 : character(len=*), parameter :: sourcefile = &
35 : __FILE__
36 :
37 : !==============================================================================
38 : contains
39 : !==============================================================================
40 :
41 18432 : subroutine stream_ndep_init(model_mesh, model_clock, rc)
42 : !
43 : ! Initialize data stream information.
44 :
45 : ! Uses:
46 : use cam_instance , only: inst_suffix
47 : use shr_nl_mod , only: shr_nl_find_group_name
48 : use dshr_strdata_mod , only: shr_strdata_init_from_inline
49 :
50 : ! input/output variables
51 : type(ESMF_CLock), intent(in) :: model_clock
52 : type(ESMF_Mesh) , intent(in) :: model_mesh
53 : integer , intent(out) :: rc
54 :
55 : ! local variables
56 : integer :: nu_nml ! unit for namelist file
57 : integer :: nml_error ! namelist i/o error flag
58 : character(len=CL) :: stream_ndep_data_filename
59 : character(len=CL) :: stream_ndep_mesh_filename
60 : character(len=CL) :: filein ! atm namelist file
61 : integer :: stream_ndep_year_first ! first year in stream to use
62 : integer :: stream_ndep_year_last ! last year in stream to use
63 : integer :: stream_ndep_year_align ! align stream_year_firstndep with
64 : integer :: ierr
65 : character(*), parameter :: subName = "('stream_ndep_init')"
66 : !-----------------------------------------------------------------------
67 :
68 : namelist /ndep_stream_nl/ &
69 : stream_ndep_data_filename, &
70 : stream_ndep_mesh_filename, &
71 : stream_ndep_year_first, &
72 : stream_ndep_year_last, &
73 : stream_ndep_year_align
74 :
75 1536 : rc = ESMF_SUCCESS
76 :
77 : ! Default values for namelist
78 1536 : stream_ndep_data_filename = ' '
79 1536 : stream_ndep_mesh_filename = ' '
80 1536 : stream_ndep_year_first = 1 ! first year in stream to use
81 1536 : stream_ndep_year_last = 1 ! last year in stream to use
82 1536 : stream_ndep_year_align = 1 ! align stream_ndep_year_first with this model year
83 :
84 : ! For now variable list in stream data file is hard-wired
85 4608 : stream_varlist_ndep = (/'NDEP_NHx_month', 'NDEP_NOy_month'/)
86 :
87 : ! Read ndep_stream namelist
88 1536 : if (masterproc) then
89 2 : filein = "atm_in" // trim(inst_suffix)
90 2 : open( newunit=nu_nml, file=trim(filein), status='old', iostat=nml_error )
91 2 : if (nml_error /= 0) then
92 0 : call endrun(subName//': ERROR opening '//trim(filein)//errMsg(sourcefile, __LINE__))
93 : end if
94 2 : call shr_nl_find_group_name(nu_nml, 'ndep_stream_nl', status=nml_error)
95 2 : if (nml_error == 0) then
96 2 : read(nu_nml, nml=ndep_stream_nl, iostat=nml_error)
97 2 : if (nml_error /= 0) then
98 0 : call endrun(' ERROR reading ndep_stream_nl namelist'//errMsg(sourcefile, __LINE__))
99 : end if
100 : else
101 0 : call endrun(' ERROR finding ndep_stream_nl namelist'//errMsg(sourcefile, __LINE__))
102 : end if
103 2 : close(nu_nml)
104 : endif
105 1536 : call mpi_bcast(stream_ndep_mesh_filename, len(stream_ndep_mesh_filename), mpi_character, 0, mpicom, ierr)
106 1536 : if (ierr /= 0) call endrun(trim(subname)//": FATAL: mpi_bcast: stream_ndep_mesh_filename")
107 1536 : call mpi_bcast(stream_ndep_data_filename, len(stream_ndep_data_filename), mpi_character, 0, mpicom, ierr)
108 1536 : if (ierr /= 0) call endrun(trim(subname)//": FATAL: mpi_bcast: stream_ndep_data_filename")
109 1536 : call mpi_bcast(stream_ndep_year_first, 1, mpi_integer, 0, mpicom, ierr)
110 1536 : if (ierr /= 0) call endrun(trim(subname)//": FATAL: mpi_bcast: stream_ndep_year_first")
111 1536 : call mpi_bcast(stream_ndep_year_last, 1, mpi_integer, 0, mpicom, ierr)
112 1536 : if (ierr /= 0) call endrun(trim(subname)//": FATAL: mpi_bcast: stream_ndep_year_last")
113 1536 : call mpi_bcast(stream_ndep_year_align, 1, mpi_integer, 0, mpicom, ierr)
114 1536 : if (ierr /= 0) call endrun(trim(subname)//": FATAL: mpi_bcast: stream_ndep_year_align")
115 :
116 1536 : if (masterproc) then
117 2 : write(iulog,'(a)' ) ' '
118 2 : write(iulog,'(a,i8)') 'stream ndep settings:'
119 2 : write(iulog,'(a,a)' ) ' stream_ndep_data_filename = ',trim(stream_ndep_data_filename)
120 2 : write(iulog,'(a,a)' ) ' stream_ndep_mesh_filename = ',trim(stream_ndep_mesh_filename)
121 2 : write(iulog,'(a,a,a)') ' stream_varlist_ndep = ',trim(stream_varlist_ndep(1)), trim(stream_varlist_ndep(2))
122 2 : write(iulog,'(a,i8)') ' stream_ndep_year_first = ',stream_ndep_year_first
123 2 : write(iulog,'(a,i8)') ' stream_ndep_year_last = ',stream_ndep_year_last
124 2 : write(iulog,'(a,i8)') ' stream_ndep_year_align = ',stream_ndep_year_align
125 2 : write(iulog,'(a)' ) ' '
126 : endif
127 :
128 : ! Read in units
129 1536 : call stream_ndep_check_units(stream_ndep_data_filename)
130 :
131 : ! Initialize the cdeps data type sdat_ndep
132 : call shr_strdata_init_from_inline(sdat_ndep, &
133 : my_task = iam, &
134 : logunit = iulog, &
135 : compname = 'ATM', &
136 : model_clock = model_clock, &
137 : model_mesh = model_mesh, &
138 : stream_meshfile = trim(stream_ndep_mesh_filename), &
139 : stream_filenames = (/trim(stream_ndep_data_filename)/), &
140 : stream_yearFirst = stream_ndep_year_first, &
141 : stream_yearLast = stream_ndep_year_last, &
142 : stream_yearAlign = stream_ndep_year_align, &
143 : stream_fldlistFile = stream_varlist_ndep, &
144 : stream_fldListModel = stream_varlist_ndep, &
145 : stream_lev_dimname = 'null', &
146 : stream_mapalgo = 'bilinear', &
147 : stream_offset = 0, &
148 : stream_taxmode = 'cycle', &
149 : stream_dtlimit = 1.0e30_r8, &
150 : stream_tintalgo = 'linear', &
151 : stream_name = 'Nitrogen deposition data ', &
152 3072 : rc = rc)
153 1536 : if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) then
154 0 : call ESMF_Finalize(endflag=ESMF_END_ABORT)
155 : end if
156 :
157 1536 : end subroutine stream_ndep_init
158 :
159 : !================================================================
160 1536 : subroutine stream_ndep_check_units( stream_fldFileName_ndep)
161 :
162 : !--------------------------------------------------------
163 : ! Check that units are correct on the file and if need any conversion
164 : !--------------------------------------------------------
165 :
166 1536 : use cam_pio_utils , only : cam_pio_createfile, cam_pio_openfile, cam_pio_closefile, pio_subsystem
167 : use pio , only : file_desc_t, io_desc_t, var_desc_t, pio_double, pio_def_dim
168 : use pio , only : pio_bcast_error, pio_seterrorhandling, pio_inq_varid, pio_get_att
169 : use pio , only : PIO_NOERR, PIO_NOWRITE
170 :
171 : ! Arguments
172 : character(len=*), intent(in) :: stream_fldFileName_ndep ! ndep filename
173 : !
174 : ! Local variables
175 : type(file_desc_t) :: File ! NetCDF filehandle for ndep file
176 : type(var_desc_t) :: vardesc ! variable descriptor
177 : integer :: ierr ! error status
178 : integer :: err_handling ! temporary
179 : character(len=CS) :: ndepunits! ndep units
180 : !-----------------------------------------------------------------------
181 :
182 1536 : call cam_pio_openfile( File, trim(stream_fldFileName_ndep), PIO_NOWRITE)
183 1536 : call pio_seterrorhandling(File, PIO_BCAST_ERROR, err_handling)
184 1536 : ierr = pio_inq_varid(File, stream_varlist_ndep(1), vardesc)
185 1536 : if (ierr /= PIO_NOERR) then
186 : call endrun(' ERROR finding variable: '//trim(stream_varlist_ndep(1))//" in file: "// &
187 0 : trim(stream_fldFileName_ndep)//errMsg(sourcefile, __LINE__))
188 : else
189 1536 : ierr = PIO_get_att(File, vardesc, "units", ndepunits)
190 : end if
191 1536 : call pio_seterrorhandling(File, err_handling)
192 1536 : call cam_pio_closefile(File)
193 :
194 : ! Now check to make sure they are correct
195 1536 : if (.not. trim(ndepunits) == "g(N)/m2/s" )then
196 : call endrun(' ERROR in units for nitrogen deposition equal to: '//trim(ndepunits)//" not units expected"// &
197 0 : errMsg(sourcefile, __LINE__))
198 : end if
199 :
200 3072 : end subroutine stream_ndep_check_units
201 :
202 : !================================================================
203 16896 : subroutine stream_ndep_interp(cam_out, rc)
204 :
205 1536 : use dshr_methods_mod , only : dshr_fldbun_getfldptr
206 : use dshr_strdata_mod , only : shr_strdata_advance
207 : use camsrfexch , only : cam_out_t
208 : use ppgrid , only : begchunk, endchunk
209 : use time_manager , only : get_curr_date
210 : use phys_grid , only : get_ncols_p
211 :
212 : ! input/output variables
213 : type(cam_out_t) , intent(inout) :: cam_out(begchunk:endchunk)
214 : integer , intent(out) :: rc
215 :
216 : ! local variables
217 : integer :: i,c,g
218 : integer :: year ! year (0, ...) for nstep+1
219 : integer :: mon ! month (1, ..., 12) for nstep+1
220 : integer :: day ! day of month (1, ..., 31) for nstep+1
221 : integer :: sec ! seconds into current date for nstep+1
222 : integer :: mcdate ! Current model date (yyyymmdd)
223 16896 : real(r8), pointer :: dataptr1d_nhx(:)
224 16896 : real(r8), pointer :: dataptr1d_noy(:)
225 : !-----------------------------------------------------------------------
226 :
227 : ! Advance sdat stream
228 16896 : call get_curr_date(year, mon, day, sec)
229 16896 : mcdate = year*10000 + mon*100 + day
230 16896 : call shr_strdata_advance(sdat_ndep, ymd=mcdate, tod=sec, logunit=iulog, istr='ndepdyn', rc=rc)
231 16896 : if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) then
232 0 : call ESMF_Finalize(endflag=ESMF_END_ABORT)
233 : end if
234 :
235 : ! Get pointer for stream data that is time and spatially interpolated to model time and grid
236 16896 : call dshr_fldbun_getFldPtr(sdat_ndep%pstrm(1)%fldbun_model, stream_varlist_ndep(1), fldptr1=dataptr1d_nhx, rc=rc)
237 16896 : if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) then
238 0 : call ESMF_Finalize(endflag=ESMF_END_ABORT)
239 : end if
240 16896 : call dshr_fldbun_getFldPtr(sdat_ndep%pstrm(1)%fldbun_model, stream_varlist_ndep(2), fldptr1=dataptr1d_noy, rc=rc)
241 16896 : if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) then
242 0 : call ESMF_Finalize(endflag=ESMF_END_ABORT)
243 : end if
244 :
245 16896 : g = 1
246 85008 : do c = begchunk,endchunk
247 1154208 : do i = 1,get_ncols_p(c)
248 1069200 : cam_out(c)%nhx_nitrogen_flx(i) = dataptr1d_nhx(g)
249 1069200 : cam_out(c)%noy_nitrogen_flx(i) = dataptr1d_noy(g)
250 1137312 : g = g + 1
251 : end do
252 : end do
253 :
254 33792 : end subroutine stream_ndep_interp
255 :
256 : end module atm_stream_ndep
|