Merge remote-tracking branch 'origin/release-v4.6.1'
[WRF.git] / hydro / Routing / module_NWM_io.F90
blobefaa6c74a4ce7eed170af6aaea30a433a3250e9b
1 ! Module for handling National Water Model streamflow, land surface,
2 ! gridded routing, lake, and groundwater output.
4 ! Logan Karsten, NCAR, RAL
6 module module_NWM_io
8 use module_version, only: get_code_version, get_nwm_version
9 use orchestrator_base
10 use module_hydro_stop, only: HYDRO_stop
11 use iso_fortran_env, only: int64, compiler_version
13 implicit none
15 ! Module-wide variables
16 integer, private :: ftnNoahMP ! Private NetCDF file handle since output routine
17                               ! called multiple times for one file.
18 contains
20 !==============================================================================
21 ! Program Name: output_chrt_NWM
22 ! Author(s)/Contact(s): Logan R Karsten <karsten><ucar><edu>
23 ! Abstract: Output routine for channel points for the National Water Model.
24 ! History Log:
25 ! 3/6/17 -Created, LRK.
26 ! Usage:
27 ! Parameters: None.
28 ! Input Files: None.
29 ! Output Files: None.
30 ! Condition codes: None.
32 ! User controllable options: None.
34 ! To add some information as global attribute for the model configuration
35 ! here we get a character variable for the io_config_outputs
36 function GetModelConfigType (io_config_outputs) result(modelConfigType)
37    integer io_config_outputs
38    character (len=64) :: modelConfigType
39    if (io_config_outputs .eq. 0) then
40       ! All
41        modelConfigType = "default"
42    else if (io_config_outputs .eq. 1) then
43       ! Analysis and Assimilation
44       modelConfigType = "analysis_and_assimilation"
45    else if (io_config_outputs .eq. 2) then
46       ! Short Range
47       modelConfigType = "short_range"
48    else if (io_config_outputs .eq. 3) then
49       ! Medium Range
50       modelConfigType = "medium_range"
51    else if (io_config_outputs .eq. 4) then
52       ! Long Range
53       modelConfigType = "long_range"
54    else if (io_config_outputs .eq. 5) then
55       ! Retrospective
56       modelConfigType = "retrospective"
57    else if (io_config_outputs .eq. 6) then
58       ! Diagnostic
59       modelConfigType = "diagnostic"
60    else
61    !   call nwmCheck(diagFlag,1,'ERROR: Invalid IOC flag provided by namelist file.')
62    endif
63 end function GetModelConfigType
65 subroutine output_chrt_NWM(domainId)
66    use module_rt_data, only: rt_domain
67    use config_base, only: nlst
68    use Module_Date_utilities_rt, only: geth_newdate, geth_idts
69    use module_NWM_io_dict
70    use netcdf
71 #ifdef MPP_LAND
72    use module_mpp_land
73    use module_mpp_reachls,  only: ReachLS_write_io
74 #endif
75    implicit none
77    ! Pass in "did" value from hydro driving program.
78    integer, intent(in) :: domainId
80    ! Derived types.
81    type(chrtMeta) :: fileMeta
83    ! Local variables
84    integer :: nudgeFlag, mppFlag, diagFlag
85    integer :: minSinceSim ! Number of minutes since beginning of simulation.
86    integer :: minSinceEpoch1 ! Number of minutes from EPOCH to the beginning of the model simulation.
87    integer :: minSinceEpoch ! Number of minutes from EPOCH to the current model valid time.
88    character(len=16) :: epochDate ! EPOCH represented as a string.
89    character(len=16) :: startDate ! Start of model simulation, represented as a string.
90    character(len=256) :: output_flnm ! CHRTOUT_DOMAIN filename
91    integer :: iret ! NetCDF return statuses
92    integer :: ftn ! NetCDF file handle
93    character(len=256) :: validTime ! Global attribute time string
94    character(len=256) :: initTime ! Global attribute time string
95    integer :: dimId(3) ! Dimension ID values created during NetCDF created.
96    integer :: varId ! Variable ID value created as NetCDF variables are created and populated.
97    integer :: timeId ! Dimension ID for the time dimension.
98    integer :: refTimeId ! Dimension ID for the reference time dimension.
99    integer :: coordVarId ! Variable to hold crs
100    integer :: featureVarId, elevVarId, orderVarId ! Misc NetCDF variable id values
101    integer :: latVarId, lonVarId ! Lat/lon NetCDF variable id values.
102    integer :: varRange(2) ! Local storage of min/max valid range values.
103    real :: varRangeReal(2) ! Local storage of min/max valid range values.
104    integer :: gSize ! Global size of channel point array.
105    integer :: indVarId,ftnRt ! values related to extraction of ascending order index values from the RouteLink file.
106    integer :: iTmp, indTmp ! Misc integer values.
107    integer :: ierr, myId ! MPI return status, process ID
108    integer :: ascFlag ! Flag for if ascendingIndex is present
109    ! Establish local, allocatable arrays
110    ! These are used to hold global output arrays, and global output arrays after
111    ! sorting has taken place by ascending feature_id value.
112    real, allocatable, dimension(:) :: strFlowLocal,velocityLocal,qlossLocal
113    real, allocatable, dimension(:,:) :: g_qlink
114    integer, allocatable, dimension(:) :: g_order
115    integer(kind=int64), allocatable, dimension(:) :: g_linkid
116    real, allocatable, dimension(:) :: g_chlat,g_chlon,g_hlink,g_zelev
117    real, allocatable, dimension(:) :: g_QLateral,g_velocity,g_qloss
118    real, allocatable, dimension(:) :: g_nudge,g_qSfcLatRunoff
119    real, allocatable, dimension(:) :: g_qBucket,g_qBtmVertRunoff,g_accBucket
120    real*8, allocatable, dimension(:) :: g_accSfcLatRunoff
121    real, allocatable, dimension(:,:) :: g_qlinkOut
122    integer, allocatable, dimension(:) :: g_orderOut
123    integer(kind=int64), allocatable, dimension(:) :: g_linkidOut
124    real, allocatable, dimension(:) :: g_chlatOut,g_chlonOut,g_hlinkOut,g_zelevOut
125    real, allocatable, dimension(:) :: g_QLateralOut,g_velocityOut,g_qlossOut
126    real, allocatable, dimension(:) :: g_nudgeOut,g_qSfcLatRunoffOut
127    real, allocatable, dimension(:) :: g_qBucketOut,g_qBtmVertRunoffOut,g_accBucketOut
128    real*8, allocatable, dimension(:) :: g_accSfcLatRunoffOut
129    real, allocatable, dimension(:,:) :: varOutReal   ! Array holding output variables in real format
130    integer, allocatable, dimension(:) :: varOutInt ! Array holding output variables after
131                                                      ! scale_factor/add_offset have been applied.
132    integer, allocatable, dimension(:) :: chIndArray ! Array of index values for
133    !each channel point. feature_id will need to be sorted in ascending order once
134    !data is collected into the global array. From there, the index values are
135    !re-sorted, and used to re-sort output arrays.
136    integer, allocatable, dimension(:) :: g_outInd ! Array of index values for strahler order.
137    integer :: numPtsOut
138    real, allocatable, dimension(:,:) :: varMetaReal
139    integer, allocatable, dimension(:,:) :: varMetaInt
140    integer(kind=int64), allocatable, dimension(:,:) :: varMetaInt8
142    character (len=64) :: modelConfigType ! This is character verion (long name) for the io_config_outputs
144    ! Initialize the ascFlag to 1
145    ascFlag = 1
147    ! Establish macro variables to hlep guide this subroutine.
148 #ifdef WRF_HYDRO_NUDGING
149    nudgeFlag = 1
150 #else
151    nudgeFlag = 0
152 #endif
154 #ifdef MPP_LAND
155    mppFlag = 1
156 #else
157    mppFlag = 0
158 #endif
160 #ifdef HYDRO_D
161    diagFlag = 1
162 #else
163    diagFlag = 0
164 #endif
166    if(nlst(domainId)%CHRTOUT_DOMAIN .eq. 0) then
167       ! No output requested here, return to parent calling program/subroutine.
168       return
169    endif
171    ! If we are running over MPI, determine which processor number we are on.
172    ! If not MPI, then default to 0, which is the I/O ID.
173    if(mppFlag .eq. 1) then
174 #ifdef MPP_LAND
175       call MPI_COMM_RANK( HYDRO_COMM_WORLD, myId, ierr )
176       call nwmCheck(diagFlag,ierr,'ERROR: Unable to determine MPI process ID.')
177 #endif
178    else
179       myId = 0
180    endif
182    ! Initialize NWM dictionary derived type containing all the necessary metadat
183    ! for the output file.
184    call initChrtDict(fileMeta,diagFlag,myId)
186    ! Depending on the NWM forecast config, we will be outputting different
187    ! varibles. DO NOT MODIFY THESE ARRAYS WITHOUT CONSULTING NCAR OR
188    ! OWP!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
189    if (nlst(1)%io_config_outputs .eq. 0) then
190       ! All
191       fileMeta%outFlag(:) = [1,1,1,1,1,0,0,0,0,0,0]
192    else if (nlst(1)%io_config_outputs .eq. 1) then
193       ! Analysis and Assimilation
194       fileMeta%outFlag(:) = [1,0,0,1,0,0,0,0,0,0,0]
195    else if (nlst(1)%io_config_outputs .eq. 2) then
196       ! Short Range
197       fileMeta%outFlag(:) = [1,0,0,1,0,0,0,0,0,0,0]
198    else if (nlst(1)%io_config_outputs .eq. 3) then
199       ! Medium Range
200       fileMeta%outFlag(:) = [1,0,0,1,0,0,0,0,0,0,0]
201    else if (nlst(1)%io_config_outputs .eq. 4) then
202       ! Long Range
203       fileMeta%outFlag(:) = [1,0,0,1,0,0,0,0,0,0,0]
204    else if (nlst(1)%io_config_outputs .eq. 5) then
205       ! Retrospective
206       fileMeta%outFlag(:) = [1,0,1,1,0,0,0,0,0,0,0]
207    else if (nlst(1)%io_config_outputs .eq. 6) then
208       ! Diagnostics
209       fileMeta%outFlag(:) = [1,0,1,1,0,0,0,0,0,0,0]
210    else
211       call nwmCheck(diagFlag,1,'ERROR: Invalid IOC flag provided by namelist file.')
212    endif
214    ! Turn off streamflow, velocity, head for special external channel routing config
215    if (nlst(domainId)%channel_bypass) then
216       fileMeta%outFlag(1) = 0
217       fileMeta%outFlag(2) = 0
218       fileMeta%outFlag(4) = 0
219       fileMeta%outFlag(5) = 0
220    endif
222    ! call the GetModelConfigType function
223    modelConfigType = GetModelConfigType(nlst(1)%io_config_outputs)
225    ! First step is to collect and assemble all data that will be written to the
226    ! NetCDF file. If we are not using MPI, we bypass the collection step through
227    ! MPI.
228    if(mppFlag .eq. 1) then
229       if(nlst(domainId)%channel_option .ne. 3) then
230          gsize = rt_domain(domainId)%gnlinksl
231       else
232          gsize = rt_domain(domainId)%gnlinks
233       endif
235       if(myId .eq. 0) then
236          ! Allocate memory for output.
237          allocate(g_chlon(gsize))
238          allocate(g_chlat(gsize))
239          allocate(g_hlink(gsize))
240          allocate(g_zelev(gsize))
241          allocate(g_qlink(gsize,2))
242          allocate(g_order(gsize))
243          allocate(g_linkid(gsize))
244          allocate(g_QLateral(gsize))
245          allocate(g_velocity(gsize))
246          allocate(g_nudge(gsize))
247          allocate(g_qSfcLatRunoff(gsize))
248          allocate(g_qBucket(gsize))
249          allocate(g_qBtmVertRunoff(gsize))
250          allocate(g_accSfcLatRunoff(gsize))
251          allocate(g_accBucket(gsize))
252          allocate(g_chlonOut(gsize))
253          allocate(g_chlatOut(gsize))
254          allocate(g_hlinkOut(gsize))
255          allocate(g_zelevOut(gsize))
256          allocate(g_qlinkOut(gsize,2))
257          allocate(g_orderOut(gsize))
258          allocate(g_QLateralOut(gsize))
259          allocate(g_velocityOut(gsize))
260          allocate(g_nudgeOut(gsize))
261          allocate(g_qSfcLatRunoffOut(gsize))
262          allocate(g_qBucketOut(gsize))
263          allocate(g_qBtmVertRunoffOut(gsize))
264          allocate(g_accSfcLatRunoffOut(gsize))
265          allocate(g_accBucketOut(gsize))
266          allocate(chIndArray(gsize))
267          allocate(g_linkidOut(gsize))
268          allocate(g_outInd(gsize))
269          if (nlst(domainId)%channel_loss_option > 0) then
270             allocate(g_qloss(gsize))
271             allocate(g_qlossOut(gsize))
272          end if
273       else
274          allocate(g_chlon(1))
275          allocate(g_chlat(1))
276          allocate(g_hlink(1))
277          allocate(g_zelev(1))
278          allocate(g_qlink(1,2))
279          allocate(g_order(1))
280          allocate(g_linkid(1))
281          allocate(g_QLateral(1))
282          allocate(g_velocity(1))
283          allocate(g_nudge(1))
284          allocate(g_qSfcLatRunoff(1))
285          allocate(g_qBucket(1))
286          allocate(g_qBtmVertRunoff(1))
287          allocate(g_accSfcLatRunoff(1))
288          allocate(g_accBucket(1))
289          allocate(g_chlonOut(1))
290          allocate(g_chlatOut(1))
291          allocate(g_hlinkOut(1))
292          allocate(g_zelevOut(1))
293          allocate(g_qlinkOut(1,2))
294          allocate(g_orderOut(1))
295          allocate(g_QLateralOut(1))
296          allocate(g_velocityOut(1))
297          allocate(g_nudgeOut(1))
298          allocate(g_qSfcLatRunoffOut(1))
299          allocate(g_qBucketOut(1))
300          allocate(g_qBtmVertRunoffOut(1))
301          allocate(g_accSfcLatRunoffOut(1))
302          allocate(g_accBucketOut(1))
303          allocate(chIndArray(1))
304          allocate(g_linkidOut(1))
305          allocate(g_outInd(1))
306          if (nlst(domainId)%channel_option == 2 .and. nlst(domainId)%channel_loss_option > 0) then
307             allocate(g_qloss(1))
308             allocate(g_qlossOut(1))
309          end if
310       endif
312       ! Allocate local streamflow and velocity arrays. We need to do a check to
313       ! for lake_type 2. However, we cannot set the values in the global array
314       ! to missing as this causes the model to crash.
315       allocate(strFlowLocal(RT_DOMAIN(domainId)%NLINKS))
316       allocate(velocityLocal(RT_DOMAIN(domainId)%NLINKS))
317       strFlowLocal = RT_DOMAIN(domainId)%QLINK(:,1)
318       velocityLocal = RT_DOMAIN(domainId)%velocity
319       ! TML: Add qloss allocation and compute variable, only for channel
320       ! option #2, where qloss is active (muskingum-cunge).
321       if(nlst(domainId)%channel_option == 2 .and. nlst(domainId)%channel_loss_option > 0) then
322          allocate(qlossLocal(RT_DOMAIN(domainId)%NLINKS))
323          qlossLocal = RT_DOMAIN(domainId)%qloss !TML temp fix to test code
324       endif
326       ! Loop through all the local links on this processor. For lake_type
327       ! of 2, we need to manually set the streamflow and velocity values
328       ! to the model NDV value.
329       if (RT_DOMAIN(domainId)%NLAKES .gt. 0) then
330          do iTmp=1,RT_DOMAIN(domainId)%NLINKS
331             if (RT_DOMAIN(domainId)%TYPEL(iTmp) .eq. 2) then
332                strFlowLocal(iTmp) = fileMeta%modelNdv
333                velocityLocal(iTmp) = fileMeta%modelNdv
334                if(nlst(domainId)%channel_option == 2 .and. nlst(domainId)%channel_loss_option > 0) then
335                   qlossLocal(iTmp) = fileMeta%modelNdv
336                endif
337             endif
338          end do
339       endif
341       ! Collect arrays from various processors through MPI, and
342       ! assemble into global arrays previously allocated.
343       if(nlst(domainId)%channel_option .ne. 3) then
344          ! Reach-based routing collection
345 #ifdef MPP_LAND
346          call ReachLS_write_io(strFlowLocal,g_qlink(:,1))
347          call ReachLS_write_io(RT_DOMAIN(domainId)%QLINK(:,2),g_qlink(:,2))
348          call ReachLS_write_io(RT_DOMAIN(domainId)%ORDER,g_order)
349          call ReachLS_write_io(RT_DOMAIN(domainId)%linkid,g_linkid)
350          call ReachLS_write_io(RT_DOMAIN(domainId)%CHLAT,g_chlat)
351          call ReachLS_write_io(RT_DOMAIN(domainId)%CHLON,g_chlon)
352          call ReachLS_write_io(RT_DOMAIN(domainId)%ZELEV,g_zelev)
353          call ReachLS_write_io(RT_DOMAIN(domainId)%QLateral,g_QLateral)
354          call ReachLS_write_io(velocityLocal,g_velocity)
355          call ReachLS_write_io(RT_DOMAIN(domainId)%HLINK,g_hlink)
356          ! Optional outputs
357          if(nudgeFlag .eq. 1)then
358 #ifdef WRF_HYDRO_NUDGING
359             fileMeta%outFlag(2) = 1 ! Set output flag to on.
360             call ReachLS_write_io(RT_DOMAIN(domainID)%nudge,g_nudge)
361 #endif
362          else
363             fileMeta%outFlag(2) = 0 ! Set output flag to off.
364          endif
365          ! TML: Only produce qloss output if routing option 2 is selected
366          if(nlst(domainId)%channel_option .eq. 2 .and. nlst(domainId)%channel_loss_option > 0) then
367             fileMeta%outFlag(11) = 1
368             call ReachLS_write_io(qlossLocal,g_qloss)
369          endif
370          if(nlst(domainId)%UDMP_OPT .eq. 1) then
371             ! Currently, we only allow channel-only outputs to be produced for
372             ! NWM configurations.
373             if(nlst(domainId)%output_channelBucket_influx .eq. 1 .or. &
374                nlst(domainId)%output_channelBucket_influx .eq. 2) then
375                fileMeta%outFlag(6) = 1
376                fileMeta%outFlag(7) = 1
377                call ReachLS_write_io(RT_DOMAIN(domainId)%qSfcLatRunoff,g_qSfcLatRunoff)
378                call ReachLS_write_io(RT_DOMAIN(domainId)%qBucket,g_qBucket)
379             endif
380             if(nlst(domainId)%output_channelBucket_influx .eq. 2 .and. &
381                nlst(domainId)%channel_only                .eq. 0         ) then
382                fileMeta%outFlag(8) = 1
383                call ReachLS_write_io(RT_DOMAIN(domainId)%qin_gwsubbas,g_qBtmVertRunoff)
384             endif
385             if(nlst(domainId)%output_channelBucket_influx .eq. 3) then
386                !! JLM: unsure the following will work... but this is caveated in namelist.
387                fileMeta%outFlag(9) = 1
388                fileMeta%outFlag(10) = 1
389                call ReachLS_write_io(RT_DOMAIN(domainId)%accSfcLatRunoff,g_accSfcLatRunoff)
390                call ReachLS_write_io(RT_DOMAIN(domainId)%qBucket,g_accBucket)
391             endif
392          else
393             if(nlst(domainId)%output_channelBucket_influx .ne. 0) then
394                ! For reach-based routing (non-NWM), we currently do not support
395                ! these outputs. Politely alert the user.....
396                call postDiagMsg(diagFlag,'WARNING: Channel-only outputs not available for UDMPT = 0 on reach-based routing.')
397             endif
398          endif
399 #endif
400       else
401          ! Gridded routing collection
402          call write_chanel_real(strFlowLocal,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_qlink(:,1))
403          call write_chanel_real(RT_DOMAIN(domainId)%QLINK(:,2),rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_qlink(:,2))
404          call write_chanel_real(RT_DOMAIN(domainId)%CHLAT,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_chlat)
405          call write_chanel_real(RT_DOMAIN(domainId)%CHLON,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_chlon)
406          call write_chanel_real(RT_DOMAIN(domainId)%HLINK,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_hlink)
407          call write_chanel_int(RT_DOMAIN(domainId)%ORDER,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_order)
408          call write_chanel_int8(RT_DOMAIN(domainId)%linkid,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_linkid)
409          call write_chanel_real(RT_DOMAIN(domainId)%ZELEV,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_zelev)
410          call write_chanel_real(RT_DOMAIN(domainId)%QLateral,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_QLateral)
411          call write_chanel_real(velocityLocal,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_velocity)
412          if(nlst(domainId)%output_channelBucket_influx .ne. 0) then
413             call postDiagMsg(diagFlag,'WARNING: This channelBucket_influx only available for reach-based routing.')
414          endif
415          if(nudgeFlag .eq. 1)then
416 #ifdef WRF_HYDRO_NUDGING
417             fileMeta%outFlag(2) = 1 ! Set output flag to on.
418             call write_chanel_real(RT_DOMAIN(domainID)%nudge,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_nudge)
419 #endif
420          else
421             fileMeta%outFlag(2) = 0 ! Set output flag to off.
422          endif
423       endif
425    else
426       gSize = rt_domain(domainId)%nlinksl
427       ! No MPI - We are running on a single processor
428       allocate(g_chlon(gsize))
429       allocate(g_chlat(gsize))
430       allocate(g_hlink(gsize))
431       allocate(g_zelev(gsize))
432       allocate(g_qlink(gsize,2))
433       allocate(g_order(gsize))
434       allocate(g_linkid(gsize))
435       allocate(g_QLateral(gsize))
436       allocate(g_velocity(gsize))
437       allocate(g_nudge(gsize))
438       allocate(g_qSfcLatRunoff(gsize))
439       allocate(g_qBucket(gsize))
440       allocate(g_qBtmVertRunoff(gsize))
441       allocate(g_accSfcLatRunoff(gsize))
442       allocate(g_accBucket(gsize))
443       allocate(g_chlonOut(gsize))
444       allocate(g_chlatOut(gsize))
445       allocate(g_hlinkOut(gsize))
446       allocate(g_zelevOut(gsize))
447       allocate(g_qlinkOut(gsize,2))
448       allocate(g_orderOut(gsize))
449       allocate(g_QLateralOut(gsize))
450       allocate(g_velocityOut(gsize))
451       allocate(g_nudgeOut(gsize))
452       allocate(g_qSfcLatRunoffOut(gsize))
453       allocate(g_qBucketOut(gsize))
454       allocate(g_qBtmVertRunoffOut(gsize))
455       allocate(g_accSfcLatRunoffOut(gsize))
456       allocate(g_accBucketOut(gsize))
457       allocate(chIndArray(gsize))
458       allocate(g_linkidOut(gsize))
459       allocate(g_outInd(gsize))
460       g_chlon = RT_DOMAIN(domainId)%CHLON
461       g_chlat = RT_DOMAIN(domainId)%CHLAT
462       g_zelev = RT_DOMAIN(domainId)%ZELEV
463       g_order = RT_DOMAIN(domainId)%ORDER
464       g_linkid = RT_DOMAIN(domainId)%linkid
465       g_hlink = RT_DOMAIN(domainId)%HLINK
466       g_qlink = RT_DOMAIN(domainId)%QLINK
467       g_QLateral = RT_DOMAIN(domainId)%QLateral
468       g_velocity = RT_DOMAIN(domainId)%velocity
469       ! Optional outputs
470       if(nudgeFlag .eq. 1)then
471 #ifdef WRF_HYDRO_NUDGING
472          fileMeta%outFlag(2) = 1 ! Set output flag to on.
473          g_nudge = RT_DOMAIN(domainID)%nudge
474 #endif
475       endif
476       ! TML: Only produce qloss output if routing option 2 is selected
477       if(nlst(domainId)%channel_option == 2 .and. nlst(domainId)%channel_loss_option > 0) then
478          allocate(g_qloss(gsize))
479          allocate(g_qlossOut(gsize))
480          fileMeta%outFlag(11) = 1
481          g_qloss = RT_DOMAIN(domainId)%qloss
482       endif
483       if(nlst(domainId)%UDMP_OPT .eq. 1) then
484          ! Currently, we only allow channel-only outputs to be produced for
485          ! NWM configurations.
486          if(nlst(domainId)%output_channelBucket_influx .eq. 1 .or. &
487             nlst(domainId)%output_channelBucket_influx .eq. 2) then
488             fileMeta%outFlag(6) = 1
489             fileMeta%outFlag(7) = 1
490             g_qSfcLatRunoff = RT_DOMAIN(domainId)%qSfcLatRunoff
491             g_qBucket = RT_DOMAIN(domainId)%qBucket
492          endif
493          if(nlst(domainId)%output_channelBucket_influx .eq. 2) then
494             fileMeta%outFlag(8) = 1
495             g_qBtmVertRunoff = RT_DOMAIN(domainId)%qin_gwsubbas
496          endif
497          if(nlst(domainId)%output_channelBucket_influx .eq. 3) then
498             fileMeta%outFlag(9) = 1
499             fileMeta%outFlag(10) = 1
500             g_accSfcLatRunoff = RT_DOMAIN(domainId)%accSfcLatRunoff
501             g_accBucket = RT_DOMAIN(domainId)%qBucket
502          endif
503       else
504          if(nlst(domainId)%output_channelBucket_influx .ne. 0) then
505             ! For reach-based routing (non-NWM), we currently do not support
506             ! these outputs. Politely alert the user.....
507             call postDiagMsg(diagFlag,'WARNING: Channel-only outputs not available for UDMPT = 0 on reach-based routing.')
508          endif
509       endif
510    endif
512    ! Calculate datetime information.
513    ! First compose strings of EPOCH and simulation start date.
514    epochDate = trim("1970-01-01 00:00")
515    startDate = trim(nlst(domainId)%startdate(1:4)//"-"//&
516                     nlst(domainId)%startdate(6:7)//&
517                     &"-"//nlst(domainId)%startdate(9:10)//" "//&
518                     nlst(domainId)%startdate(12:13)//":"//&
519                     nlst(domainId)%startdate(15:16))
520    ! Second, utilize NoahMP date utilities to calculate the number of minutes
521    ! from EPOCH to the beginning of the model simulation.
522    call geth_idts(startDate,epochDate,minSinceEpoch1)
523    ! Third, calculate the number of minutes since the beginning of the
524    ! simulation.
525    minSinceSim = int(nlst(1)%out_dt*(rt_domain(1)%out_counts-1))
526    ! Fourth, calculate the total number of minutes from EPOCH to the current
527    ! model time step.
528    minSinceEpoch = minSinceEpoch1 + minSinceSim
529    ! Fifth, compose global attribute time strings that will be used.
530    validTime = trim(nlst(domainId)%olddate(1:4)//'-'//&
531                     nlst(domainId)%olddate(6:7)//'-'//&
532                     nlst(domainId)%olddate(9:10)//'_'//&
533                     nlst(domainId)%olddate(12:13)//':'//&
534                     nlst(domainId)%olddate(15:16)//&
535                     &':00')
536    initTime = trim(nlst(domainId)%startdate(1:4)//'-'//&
537                   nlst(domainId)%startdate(6:7)//'-'//&
538                   nlst(domainId)%startdate(9:10)//'_'//&
539                   nlst(domainId)%startdate(12:13)//':'//&
540                   nlst(domainId)%startdate(15:16)//&
541                   &':00')
542    ! Replace default values in the dictionary.
543    fileMeta%initTime = trim(initTime)
544    fileMeta%validTime = trim(validTime)
546    ! calculate the minimum and maximum time
547    fileMeta%timeValidMin = minSinceEpoch1 + nlst(1)%out_dt
548    fileMeta%timeValidMax = minSinceEpoch1 + int(nlst(1)%khour * 60/nlst(1)%out_dt) * nlst(1)%out_dt
550    ! calculate total_valid_time
551    fileMeta%totalValidTime = int(nlst(1)%khour * 60 / nlst(1)%out_dt)  ! # number of valid time (#of output files)
553    ! Compose output file name.
554    write(output_flnm, '(A12,".CHRTOUT_DOMAIN",I1)')nlst(domainId)%olddate(1:4)//&
555          nlst(domainId)%olddate(6:7)//nlst(domainId)%olddate(9:10)//&
556          nlst(domainId)%olddate(12:13)//nlst(domainId)%olddate(15:16), nlst(domainId)%igrid
558    ! Only run NetCDF library calls to output data if we are on the master
559    ! processor.
560    if(myId .eq. 0) then
561       if(nlst(domainId)%channel_option .ne. 3) then
562          ! Read in index values from Routelink that will be used to sort output
563          ! variables by ascending feature_id.
564          iret = orchestrator%IO_Manager%netcdf_layer%open_file(trim(nlst(1)%route_link_f),NF90_NOWRITE,ncid=ftnRt)
565          !iret = nf90_open(trim(nlst(1)%route_link_f),NF90_NOWRITE,ncid=ftnRt)
566          call nwmCheck(diagFlag,iret,'ERROR: Unable to open RouteLink file for index extraction')
567          iret = nf90_inq_varid(ftnRt,'ascendingIndex',indVarId)
568          if(iret .ne. 0) then
569             call postDiagMsg(diagFlag,'WARNING: ascendingIndex not found in RouteLink file. No resorting will take place.')
570             ascFlag = 0
571          endif
572          if(ascFlag .eq. 1) then
573             iret = nf90_get_var(ftnRt,indVarId,chIndArray)
574             call nwmCheck(diagFlag,iret,'ERROR: Unable to extract ascendingIndex from RouteLink file.')
575          endif
576          iret = nf90_close(ftnRt)
577          call nwmCheck(diagFlag,iret,'ERROR: Unable to close RouteLink file.')
578       else
579          ascFlag = 0
580       endif
581       ! Place all output arrays into one real array that will be looped over
582       ! during conversion to compressed integer format.
583       if(ascFlag .eq. 1) then
584          ! Sort feature_id values by ascending values using the index array
585          ! extracted from the RouteLink file.
586          do iTmp=1,gSize
587             indTmp = chIndArray(iTmp)
588             indTmp = indTmp + 1 ! Python starts index values at 0, so we need to add one.
589             g_linkidOut(iTmp) = g_linkid(indTmp)
590             g_qlinkOut(iTmp,1) = g_qlink(indTmp,1)
591             g_nudgeOut(iTmp) = g_nudge(indTmp)
592             g_QLateralOut(iTmp) = g_QLateral(indTmp)
593             g_velocityOut(iTmp) = g_velocity(indTmp)
594             g_hlinkOut(iTmp) = g_hlink(indTmp)
595             g_qSfcLatRunoffOut(iTmp) = g_qSfcLatRunoff(indTmp)
596             g_qBucketOut(iTmp) = g_qBucket(indTmp)
597             g_qBtmVertRunoffOut(iTmp) = g_qBtmVertRunoff(indTmp)
598             g_accSfcLatRunoffOut(iTmp) = g_accSfcLatRunoff(indTmp)
599             g_accBucketOut(iTmp) = g_accBucket(indTmp)
600             g_chlatOut(iTmp) = g_chlat(indTmp)
601             g_chlonOut(iTmp) = g_chlon(indTmp)
602             g_orderOut(iTmp) = g_order(indTmp)
603             g_zelevOut(iTmp) = g_zelev(indTmp)
604             if(nlst(domainId)%channel_option == 2 .and. nlst(domainId)%channel_loss_option > 0) then
605                g_qlossOut(iTmp) = g_qloss(indTmp)
606             end if
607          end do
608       else
609          g_linkidOut = g_linkid
610          g_qlinkOut(:,1) = g_qlink(:,1)
611          g_nudgeOut = g_nudge
612          g_QLateralOut = g_QLateral
613          g_velocityOut = g_velocity
614          g_hlinkOut = g_hlink
615          g_qSfcLatRunoffOut = g_qSfcLatRunoff
616          g_qBucketOut = g_qBucket
617          g_qBtmVertRunoffOut = g_qBtmVertRunoff
618          g_accSfcLatRunoffOut = g_accSfcLatRunoff
619          g_accBucketOut = g_accBucket
620          g_chlatOut = g_chlat
621          g_chlonOut = g_chlon
622          g_orderOut = g_order
623          g_zelevOut = g_zelev
624          if(nlst(domainId)%channel_option == 2 .and. nlst(domainId)%channel_loss_option > 0) then
625             g_qlossOut = g_qloss
626          end if
627       endif
629       ! Calculate index values based on minimum strahler order to write.
630       ! Initialize the index array to 0
631       g_outInd = 0
633       where(g_orderOut .ge. nlst(domainId)%order_to_write) g_outInd = 1
634       numPtsOut = sum(g_outInd)
636       if(numPtsOut .eq. 0) then
637          ! Write warning message to user showing there are NO channel points to
638          ! write. Simply return to the main calling function.
639          call postDiagMsg(diagFlag,"WARNING: No channel points found for CHRTOUT.")
640          return
641       endif
643       ! Loop through all channel points if we are running gridded routing.
644       ! Assign an arbitrary index value as the linkid field is read in as 0 from
645       ! the Fulldom file.
646       if(nlst(domainId)%channel_option .eq. 3) then
647          do iTmp=1,gSize
648             g_linkidOut(iTmp) = iTmp
649          end do
650       endif
652       allocate(varOutReal(fileMeta%numVars,numPtsOut))
653       allocate(varOutInt(numPtsOut))
654       allocate(varMetaReal(3,numPtsOut))
655       allocate(varMetaInt(1,numPtsOut))
656       allocate(varMetaInt8(1,numPtsOut))
658       varOutReal(1,:) = PACK(g_qlinkOut(:,1),g_outInd == 1)
659       varOutReal(2,:) = PACK(g_nudgeOut,g_outInd == 1)
660       varOutReal(3,:) = PACK(g_QLateralOut,g_outInd == 1)
661       varOutReal(4,:) = PACK(g_velocityOut,g_outInd == 1)
662       varOutReal(5,:) = PACK(g_hlinkOut,g_outInd == 1)
663       varOutReal(6,:) = PACK(g_qSfcLatRunoffOut,g_outInd == 1)
664       varOutReal(7,:) = PACK(g_qBucketOut,g_outInd == 1)
665       varOutReal(8,:) = PACK(g_qBtmVertRunoffOut,g_outInd == 1)
666       varOutReal(9,:) = PACK(g_accSfcLatRunoffOut,g_outInd == 1)
667       varOutReal(10,:) = PACK(g_accBucketOut,g_outInd == 1)
668       if(nlst(domainId)%channel_option == 2 .and. nlst(domainId)%channel_loss_option > 0) then
669          varOutReal(11,:) = PACK(g_qlossOut,g_outInd == 1)
670       end if
672       varMetaReal(1,:) = PACK(g_chlatOut,g_outInd == 1)
673       varMetaReal(2,:) = PACK(g_chlonOut,g_outInd == 1)
674       varMetaReal(3,:) = PACK(g_zelevOut,g_outInd == 1)
675       varMetaInt(1,:) = PACK(g_orderOut,g_outInd == 1)
676       varMetaInt8(1,:) = PACK(g_linkidOut,g_outInd == 1)
678       ! Mask out missing values
679       where ( varOutReal == fileMeta%modelNdv ) varOutReal = -9999.0
681       ! Open output NetCDF file for writing.
682       iret = nf90_create(trim(output_flnm),cmode=NF90_NETCDF4,ncid = ftn)
683       call nwmCheck(diagFlag,iret,'ERROR: Unable to create CHRTOUT NetCDF file.')
685       ! Write global attributes.
686       iret = nf90_put_att(ftn,NF90_GLOBAL,"TITLE",trim(fileMeta%title))
687       call nwmCheck(diagFlag,iret,'ERROR: Unable to create TITLE attribute')
688       iret = nf90_put_att(ftn,NF90_GLOBAL,"compiler_version",compiler_version())
689       call nwmCheck(diagFlag,iret,'ERROR: Unable to create compiler_version attribute')
690       iret = nf90_put_att(ftn,NF90_GLOBAL,"featureType",trim(fileMeta%fType))
691       call nwmCheck(diagFlag,iret,'ERROR: Unable to create featureType attribute')
692       iret = nf90_put_att(ftn,NF90_GLOBAL,"proj4",trim(fileMeta%proj4))
693       call nwmCheck(diagFlag,iret,'ERROR: Unable to create proj4 attribute')
694       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_initialization_time",trim(fileMeta%initTime))
695       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model init attribute')
696       iret = nf90_put_att(ftn,NF90_GLOBAL,"station_dimension",trim(fileMeta%stDim))
697       call nwmCheck(diagFlag,iret,'ERROR: Unable to create st. dimension attribute')
698       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_output_valid_time",trim(fileMeta%validTime))
699       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model valid attribute')
700       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_total_valid_times",fileMeta%totalValidTime)
701       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model total valid time attribute')
702       iret = nf90_put_att(ftn,NF90_GLOBAL,"stream_order_output",fileMeta%stOrder)
703       call nwmCheck(diagFlag,iret,'ERROR: Unable to create order attribute')
704       iret = nf90_put_att(ftn,NF90_GLOBAL,"cdm_datatype",trim(fileMeta%cdm))
705       call nwmCheck(diagFlag,iret,'ERROR: Unable to create CDM attribute')
706       !iret = nf90_put_att(ftn,NF90_GLOBAL,"esri_pe_string",trim(fileMeta%esri))
707       !call nwmCheck(diagFlag,iret,'ERROR: Unable to create ESRI attribute')
708       iret = nf90_put_att(ftn,NF90_GLOBAL,"Conventions",trim(fileMeta%conventions))
709       call nwmCheck(diagFlag,iret,'ERROR: Unable to create conventions attribute')
710       iret = nf90_put_att(ftn,NF90_GLOBAL,"code_version",trim(get_code_version()))
711       call nwmCheck(diagFlag,iret,'ERROR: Unable to create code_version attribute')
712 #ifdef NWM_META
713       iret = nf90_put_att(ftn,NF90_GLOBAL,"NWM_version_number",trim(get_nwm_version()))
714       call nwmCheck(diagFlag,iret,'ERROR: Unable to create NWM_version_number attribute')
715 #endif
716       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_output_type",trim(fileMeta%modelOutputType))
717       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_output_type attribute')
718       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_configuration",modelConfigType)
719       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_configuration attribute')
721       ! Create global attributes specific to running output through the
722       ! channel-only configuration of the model.
723       iret = nf90_put_att(ftn,NF90_GLOBAL,"dev_OVRTSWCRT",nlst(domainId)%OVRTSWCRT)
724       call nwmCheck(diagFlag,iret,'ERROR: Unable to create dev_OVRTSWCRT attribute')
725       iret = nf90_put_att(ftn,NF90_GLOBAL,"dev_NOAH_TIMESTEP",int(nlst(domainId)%dt))
726       call nwmCheck(diagFlag,iret,'ERROR: Unable to create dev_NOAH_TIMESTEP attribute')
727       iret = nf90_put_att(ftn,NF90_GLOBAL,"dev_channel_only",nlst(domainId)%channel_only)
728       call nwmCheck(diagFlag,iret,'ERROR: Unable to create dev_channel_only attribute')
729       iret = nf90_put_att(ftn,NF90_GLOBAL,"dev_channelBucket_only",nlst(domainId)%channelBucket_only)
730       call nwmCheck(diagFlag,iret,'ERROR: Unable to create dev_channelBucket_only attribute')
731       iret = nf90_put_att(ftn,NF90_GLOBAL,'dev','dev_ prefix indicates development/internal meta data')
732       call nwmCheck(diagFlag,iret,'ERROR: Unable to create dev attribute')
734       ! Create dimensions
735       !iret = nf90_def_dim(ftn,"feature_id",gSize,dimId(1))
736       iret = nf90_def_dim(ftn,"feature_id",numPtsOut,dimId(1))
737       call nwmCheck(diagFlag,iret,'ERROR: Unable to create feature_id dimension')
738       iret = nf90_def_dim(ftn,"time",NF90_UNLIMITED,dimId(2))
739       call nwmCheck(diagFlag,iret,'ERROR: Unable to create time dimension')
740       iret = nf90_def_dim(ftn,"reference_time",1,dimId(3))
741       call nwmCheck(diagFlag,iret,'ERROR: Unable to create reference_time dimension')
743       ! Create and populate reference_time and time variables.
744       iret = nf90_def_var(ftn,"time",nf90_int,dimId(2),timeId)
745       call nwmCheck(diagFlag,iret,'ERROR: Unable to create time variable')
746       iret = nf90_put_att(ftn,timeId,'long_name',trim(fileMeta%timeLName))
747       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into time variable')
748       iret = nf90_put_att(ftn,timeId,'standard_name',trim(fileMeta%timeStName))
749       call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into time variable')
750       iret = nf90_put_att(ftn,timeId,'units',trim(fileMeta%timeUnits))
751       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into time variable')
752       iret = nf90_put_att(ftn,timeId,'valid_min',fileMeta%timeValidMin)
753       call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_min attribute into time variable')
754       iret = nf90_put_att(ftn,timeId,'valid_max',fileMeta%timeValidMax)
755       call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_max attribute into time variable')
756       iret = nf90_def_var(ftn,"reference_time",nf90_int,dimId(3),refTimeId)
757       call nwmCheck(diagFlag,iret,'ERROR: Unable to create reference_time variable')
758       iret = nf90_put_att(ftn,refTimeId,'long_name',trim(fileMeta%rTimeLName))
759       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into reference_time variable')
760       iret = nf90_put_att(ftn,refTimeId,'standard_name',trim(fileMeta%rTimeStName))
761       call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into reference_time variable')
762       iret = nf90_put_att(ftn,refTimeId,'units',trim(fileMeta%rTimeUnits))
763       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into reference_time variable')
765       ! Create a crs variable.
766       ! NOTE - For now, we are hard-coding in for lat/lon points. However, this
767       ! may be more flexible in future iterations.
768       iret = nf90_def_var(ftn,'crs',nf90_char,varid=coordVarId)
769       call nwmCheck(diagFlag,iret,'ERROR: Unable to create crs variable.')
770       iret = nf90_put_att(ftn,coordVarId,'transform_name','latitude longitude')
771       call nwmCheck(diagFlag,iret,'ERROR: Unable to place transform_name attribute into crs variable.')
772       iret = nf90_put_att(ftn,coordVarId,'grid_mapping_name','latitude longitude')
773       call nwmCheck(diagFlag,iret,'ERROR: Unable to place grid_mapping_name attribute into crs variable.')
774       iret = nf90_put_att(ftn,coordVarId,'esri_pe_string','GEOGCS["GCS_WGS_1984",DATUM["D_WGS_1984",&
775                                           &SPHEROID["WGS_1984",6378137.0,298.257223563]],PRIMEM["Greenwich",0.0],UNIT["Degree",&
776                                           &0.0174532925199433]];-400 -400 1000000000;&
777                                           &-100000 10000;-100000 10000;8.98315284119521E-09;0.001;0.001;IsHighPrecision')
778       call nwmCheck(diagFlag,iret,'ERROR: Unable to place esri_pe_string into crs variable.')
779       iret = nf90_put_att(ftn,coordVarId,'spatial_ref','GEOGCS["GCS_WGS_1984",DATUM["D_WGS_1984",&
780                                           &SPHEROID["WGS_1984",6378137.0,298.257223563]],PRIMEM["Greenwich",0.0],UNIT["Degree",&
781                                           &0.0174532925199433]];-400 -400 1000000000;&
782                                           &-100000 10000;-100000 10000;8.98315284119521E-09;0.001;0.001;IsHighPrecision')
783       call nwmCheck(diagFlag,iret,'ERROR: Unable to place spatial_ref into crs variable.')
784       iret = nf90_put_att(ftn,coordVarId,'long_name','CRS definition')
785       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name into crs variable.')
786       iret = nf90_put_att(ftn,coordVarId,'longitude_of_prime_meridian',0.0)
787       call nwmCheck(diagFlag,iret,'ERROR: Unable to place longitude_of_prime_meridian into crs variable.')
788       iret = nf90_put_att(ftn,coordVarId,'_CoordinateAxes','latitude longitude')
789       call nwmCheck(diagFlag,iret,'ERROR: Unable to place _CoordinateAxes into crs variable.')
790       iret = nf90_put_att(ftn,coordVarId,'semi_major_axis',6378137.0)
791       call nwmCheck(diagFlag,iret,'ERROR: Unable to place semi_major_axis into crs variable.')
792       iret = nf90_put_att(ftn,coordVarId,'semi_minor_axis',6356752.31424518)
793       call nwmCheck(diagFlag,iret,'ERROR: Unable to place semi_minor_axis into crs variable.')
794       iret = nf90_put_att(ftn,coordVarId,'inverse_flattening',298.257223563)
795       call nwmCheck(diagFlag,iret,'ERROR: Unable to place inverse_flattening into crs variable.')
797       ! Create feature_id variable
798       iret = nf90_def_var(ftn,"feature_id",nf90_int64,dimId(1),featureVarId)
799       call nwmCheck(diagFlag,iret,'ERROR: Unable to create feature_id variable.')
800       iret = nf90_put_att(ftn,featureVarId,'long_name',trim(fileMeta%featureIdLName))
801       call nwmCheck(diagFlag,iret,'ERROR: Uanble to place long_name attribute into feature_id variable')
802       iret = nf90_put_att(ftn,featureVarId,'comment',trim(fileMeta%featureIdComment))
803       call nwmCheck(diagFlag,iret,'ERROR: Unable to place comment attribute into feature_id variable')
804       iret = nf90_put_att(ftn,featureVarId,'cf_role',trim(fileMeta%cfRole))
805       call nwmCheck(diagFlag,iret,'ERROR: Unable to place cf_role attribute into feature_id variable')
807 #ifndef NWM_META
808       ! Create channel lat/lon variables
809       ! NOTE: NWM current operations do not permit the output of latitude and longitude for streamflow.
810       iret = nf90_def_var(ftn,"latitude",nf90_float,dimId(1),latVarId)
811       call nwmCheck(diagFlag,iret,'ERROR: Unable to create latitude variable.')
812       iret = nf90_put_att(ftn,latVarId,'long_name',trim(fileMeta%latLName))
813       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into latitude variable')
814       iret = nf90_put_att(ftn,latVarId,'standard_name',trim(fileMeta%latStName))
815       call nwmCheck(diagFlag,iret,'ERROR: Unable to place stndard_name attribute into latitude variable')
816       iret = nf90_put_att(ftn,latVarId,'units',trim(fileMeta%latUnits))
817       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into latitude variable')
818       iret = nf90_def_var(ftn,"longitude",nf90_float,dimId(1),lonVarId)
819       call nwmCheck(diagFlag,iret,'ERROR: Unable to create longitude variable.')
820       iret = nf90_put_att(ftn,lonVarId,'long_name',trim(fileMeta%lonLName))
821       call nwmCheck(diagFlag,iret,'ERROR: Uanble to place long_name attribute into longitude variable')
822       iret = nf90_put_att(ftn,lonVarId,'standard_name',trim(fileMeta%lonStName))
823       call nwmCheck(diagFlag,iret,'ERROR: Unable to place stndard_name attribute into longitude variable')
824       iret = nf90_put_att(ftn,lonVarId,'units',trim(fileMeta%lonUnits))
825       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into longitude variable')
827       ! Create channel order variable
828       iret = nf90_def_var(ftn,"order",nf90_int,dimId(1),orderVarId)
829       call nwmCheck(diagFlag,iret,'ERROR: Unable to create order variable.')
830       iret = nf90_put_att(ftn,orderVarId,'long_name',trim(fileMeta%orderLName))
831       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into order variable')
832       iret = nf90_put_att(ftn,orderVarId,'standard_name',trim(fileMeta%orderStName))
833       call nwmCheck(diagFlag,iret,'ERROR: Unable to place stndard_name attribute into order variable')
835       ! Create channel elevation variable
836       iret = nf90_def_var(ftn,"elevation",nf90_float,dimId(1),elevVarId)
837       call nwmCheck(diagFlag,iret,'ERROR: Unable to create elevation variable.')
838       iret = nf90_put_att(ftn,elevVarId,'long_name',trim(fileMeta%elevLName))
839       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into elevation variable')
840       iret = nf90_put_att(ftn,elevVarId,'standard_name',trim(fileMeta%elevStName))
841       call nwmCheck(diagFlag,iret,'ERROR: Unable to place stndard_name attribute into elevation variable')
842       iret = nf90_put_att(ftn,elevVarId,'units',trim(fileMeta%elevUnits))
843       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into elevation variable')
844 #endif
846       ! Define deflation levels for these meta-variables. For now, we are going to
847       ! default to a compression level of 2. Only compress if io_form_outputs is set to 1.
848       if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
849          iret = nf90_def_var_deflate(ftn,timeId,0,1,2)
850          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for time.')
851          iret = nf90_def_var_deflate(ftn,featureVarId,0,1,2)
852          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for feature_id.')
853          iret = nf90_def_var_deflate(ftn,refTimeId,0,1,2)
854          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for reference_time.')
855 #ifndef NWM_META
856          iret = nf90_def_var_deflate(ftn,latVarId,0,1,2)
857          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for latitude.')
858          iret = nf90_def_var_deflate(ftn,lonVarId,0,1,2)
859          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for longitude.')
860          iret = nf90_def_var_deflate(ftn,orderVarId,0,1,2)
861          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for order.')
862          iret = nf90_def_var_deflate(ftn,elevVarId,0,1,2)
863          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for elevation.')
864 #endif
865       endif
867       ! Allocate memory for the output variables, then place the real output
868       ! variables into a single array. This array will be accessed throughout the
869       ! output looping below for conversion to compressed integer values.
870       ! Loop through and create each output variable, create variable attributes,
871       ! and insert data.
872       do iTmp=1,fileMeta%numVars
873          if(fileMeta%outFlag(iTmp) .eq. 1) then
874             ! First create variable
875             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
876                iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_int,dimId(1),varId)
877             else
878                iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_float,dimId(1),varId)
879             endif
880             call nwmCheck(diagFlag,iret,'ERROR: Unable to create variable:'//trim(fileMeta%varNames(iTmp)))
882             ! Extract valid range into a 1D array for placement.
883             varRange(1) = fileMeta%validMinComp(iTmp)
884             varRange(2) = fileMeta%validMaxComp(iTmp)
885             varRangeReal(1) = real(fileMeta%validMinDbl(iTmp))
886             varRangeReal(2) = real(fileMeta%validMaxDbl(iTmp))
888             ! Establish a compression level for the variables. For now we are using a
889             ! compression level of 2. In addition, we are choosing to turn the shuffle
890             ! filter off for now. Kelley Eicher did some testing with this and
891             ! determined that the benefit wasn't worth the extra time spent writing
892             ! output. Only compress if io_form_outputs is set to 1.
893             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
894                iret = nf90_def_var_deflate(ftn,varId,0,1,2)
895                call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression for: '//trim(fileMeta%varNames(iTmp)))
896             endif
898             ! Create variable attributes
899             iret = nf90_put_att(ftn,varId,'long_name',trim(fileMeta%longName(iTmp)))
900             call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into variable '//trim(fileMeta%varNames(iTmp)))
901             iret = nf90_put_att(ftn,varId,'units',trim(fileMeta%units(iTmp)))
902             call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into variable '//trim(fileMeta%varNames(iTmp)))
903             iret = nf90_put_att(ftn,varId,'coordinates',trim(fileMeta%coordNames(iTmp)))
904             call nwmCheck(diagFlag,iret,'ERROR: Unable to place coordinates attribute into variable '//trim(fileMeta%varNames(iTmp)))
905             iret = nf90_put_att(ftn,varId,'grid_mapping','crs')
906             call nwmCheck(diagFlag,iret,'ERROR: Unable to place grid_mapping attribute into variable '//trim(fileMeta%varNames(iTmp)))
907             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
908                iret = nf90_put_att(ftn,varId,'_FillValue',fileMeta%fillComp(iTmp))
909                call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
910                iret = nf90_put_att(ftn,varId,'missing_value',fileMeta%missingComp(iTmp))
911                call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
912                iret = nf90_put_att(ftn,varId,'scale_factor',fileMeta%scaleFactor(iTmp))
913                call nwmCheck(diagFlag,iret,'ERROR: Unable to place scale_factor attribute into variable '//trim(fileMeta%varNames(iTmp)))
914                iret = nf90_put_att(ftn,varId,'add_offset',fileMeta%addOffset(iTmp))
915                call nwmCheck(diagFlag,iret,'ERROR: Unable to place add_offset attribute into variable '//trim(fileMeta%varNames(iTmp)))
916                iret = nf90_put_att(ftn,varId,'valid_range',varRange)
917                call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
918             else
919                iret = nf90_put_att(ftn,varId,'_FillValue',fileMeta%fillReal(iTmp))
920                call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
921                iret = nf90_put_att(ftn,varId,'missing_value',fileMeta%missingReal(iTmp))
922                call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
923                iret = nf90_put_att(ftn,varId,'valid_range',varRangeReal)
924                call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
925             endif
926          endif
927       end do
929       ! Remove NetCDF file from definition mode.
930       iret = nf90_enddef(ftn)
931       call nwmCheck(diagFlag,iret,'ERROR: Unable to take CHRTOUT file out of definition mode')
933       ! Loop through all possible output variables, and convert floating points
934       ! to integers via prescribed scale_factor/add_offset, then write to the
935       ! NetCDF variable.
936       do iTmp=1,fileMeta%numVars
937          if(fileMeta%outFlag(iTmp) .eq. 1) then
938             ! We are outputing this variable.
939             ! Convert reals to integer. If this is time zero, check to see if we
940             ! need to convert all data to NDV
941             if(minSinceSim .eq. 0 .and. fileMeta%timeZeroFlag(iTmp) .eq. 0) then
942                varOutInt(:) = fileMeta%fillComp(iTmp)
943                varOutReal(iTmp,:) = fileMeta%fillReal(iTmp)
944             else
945                varOutInt(:) = NINT((varOutReal(iTmp,:)-fileMeta%addOffset(iTmp))/fileMeta%scaleFactor(iTmp))
946             endif
947             ! Get NetCDF variable id.
948             iret = nf90_inq_varid(ftn,trim(fileMeta%varNames(iTmp)),varId)
949             call nwmCheck(diagFlag,iret,'ERROR: Unable to find variable ID for var: '//trim(fileMeta%varNames(iTmp)))
950             ! Put data into NetCDF file
951             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
952                iret = nf90_put_var(ftn,varId,varOutInt)
953             else
954                iret = nf90_put_var(ftn,varId,varOutReal(iTmp,:))
955             endif
956             call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into output variable: '//trim(fileMeta%varNames(iTmp)))
957          endif
958       end do
960       ! Place link ID values into the NetCDF file
961       iret = nf90_inq_varid(ftn,'feature_id',varId)
962       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate feature_id in NetCDF file.')
963       iret = nf90_put_var(ftn,varId,varMetaInt8(1,:))
964       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into feature_id output variable.')
966 #ifndef NWM_META
967       iret = nf90_inq_varid(ftn,'latitude',varId)
968       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate latitude in NetCDF file.')
969       iret = nf90_put_var(ftn,varId,varMetaReal(1,:))
970       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into latitude output variable.')
972       iret = nf90_inq_varid(ftn,'longitude',varId)
973       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate longitude in NetCDF file.')
974       iret = nf90_put_var(ftn,varId,varMetaReal(2,:))
975       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into longitude output variable.')
977       iret = nf90_inq_varid(ftn,'order',varId)
978       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate order in NetCDF file.')
979       iret = nf90_put_var(ftn,varId,varMetaInt(1,:))
980       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into order output variable.')
982       iret = nf90_inq_varid(ftn,'elevation',varId)
983       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate elevation in NetCDF file.')
984       iret = nf90_put_var(ftn,varId,varMetaReal(3,:))
985       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into elevation output variable.')
986 #endif
988       ! Place time values into time variables.
989       iret = nf90_inq_varid(ftn,'time',varId)
990       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate time variable')
991       iret = nf90_put_var(ftn,varId,minSinceEpoch)
992       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into time variable')
993       iret = nf90_inq_varid(ftn,'reference_time',varId)
994       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate reference_time variable')
995       iret = nf90_put_var(ftn,varId,minSinceEpoch1)
996       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into reference_time variable')
998       ! Close the output file
999       iret = nf90_close(ftn)
1000       call nwmCheck(diagFlag,iret,'ERROR: Unable to close CHRTOUT file.')
1002    endif ! End if we are on master processor.
1004    ! Deallocate all memory.
1005    if(myId .eq. 0) then
1006       deallocate(varOutReal)
1007       deallocate(varOutInt)
1008       deallocate(varMetaReal)
1009       deallocate(varMetaInt)
1010       deallocate(varMetaInt8)
1011    endif
1012    deallocate(g_chlonOut)
1013    deallocate(g_chlatOut)
1014    deallocate(g_hlinkOut)
1015    deallocate(g_zelevOut)
1016    deallocate(g_qlinkOut)
1017    deallocate(g_orderOut)
1018    deallocate(g_QLateralOut)
1019    deallocate(g_velocityOut)
1020    deallocate(g_nudgeOut)
1021    deallocate(g_qSfcLatRunoffOut)
1022    deallocate(g_qBucketOut)
1023    deallocate(g_qBtmVertRunoffOut)
1024    deallocate(g_accSfcLatRunoffOut)
1025    deallocate(g_accBucketOut)
1026    deallocate(chIndArray)
1027    deallocate(g_linkidOut)
1028    deallocate(g_chlon)
1029    deallocate(g_chlat)
1030    deallocate(g_hlink)
1031    deallocate(g_zelev)
1032    deallocate(g_qlink)
1033    deallocate(g_order)
1034    deallocate(g_linkid)
1035    deallocate(g_QLateral)
1036    deallocate(g_nudge)
1037    deallocate(g_qSfcLatRunoff)
1038    deallocate(g_qBucket)
1039    deallocate(g_qBtmVertRunoff)
1040    deallocate(g_accSfcLatRunoff)
1041    deallocate(g_accBucket)
1042    deallocate(strFlowLocal)
1043    deallocate(velocityLocal)
1044    if (allocated(qlossLocal)) then
1045       deallocate(qlossLocal)
1046    end if
1047    if (allocated(g_qlossOut)) then
1048       deallocate(g_qlossOut)
1049    end if
1051    deallocate(g_outInd)
1053 end subroutine output_chrt_NWM
1055 !==============================================================================
1056 ! Program Name: output_NoahMP_NWM
1057 ! Author(s)/Contact(s): Logan R Karsten <karsten><ucar><edu>
1058 ! Abstract: Output routine for NoahMP grids for the National Water Model.
1059 ! History Log:
1060 ! 3/6/17 -Created, LRK.
1061 ! Usage:
1062 ! Parameters: None.
1063 ! Input Files: None.
1064 ! Output Files: None.
1065 ! Condition codes: None.
1067 ! User controllable options: None.
1069 subroutine output_NoahMP_NWM(outDir,iGrid,output_timestep,itime,startdate,date,ixPar,jxPar,zNum,varReal,vegTyp,varInd)
1070    use module_rt_data, only: rt_domain
1071    use config_base, only: nlst, noah_lsm
1072    use Module_Date_utilities_rt, only: geth_newdate, geth_idts
1073    use module_NWM_io_dict
1074    use netcdf
1075 #ifdef MPP_LAND
1076      use module_mpp_land
1077 #endif
1078    implicit none
1080    ! Subroutine arguments
1081    character(len=*), intent(in) :: outDir ! Output directory to place output.
1082    integer, intent(in) :: iGrid ! Grid number
1083    integer, intent(in) :: output_timestep ! Output timestep we are on.
1084    integer, intent(in) :: itime ! the noalMP time step we are in
1085    character(len=19),intent(in) :: startdate ! Model simulation start date
1086    character(len=19),intent(in) :: date ! Current model date
1087    integer, intent(in) :: ixPar,jxPar ! I/J dimensions of local grid.
1088    integer, intent(in) :: zNum ! Number of vertical layers (most of the time 1)
1089    real, intent(in) :: varReal(ixPar,zNum,jxPar) ! Variable data to be written.
1090    integer, intent(inout) :: vegTyp(ixPar,jxPar) ! Vegetation type grid used to mask out variables.
1091    integer, intent(in) :: varInd ! Variable index used to extact meta-data from.
1093    ! Derived types.
1094    type(ldasMeta) :: fileMeta
1096    ! Local variables
1097    integer :: minSinceSim ! Number of minutes since beginning of simulation.
1098    integer :: minSinceEpoch1 ! Number of minutes from EPOCH to the beginning of the model simulation.
1099    integer :: minSinceEpoch ! Number of minutes from EPOCH to the current model valid time.
1100    character(len=16) :: epochDate ! EPOCH represented as a string.
1101    character(len=16) :: startDateTmp ! Start of model simulation, represented as a string.
1102    character(len=256) :: validTime ! Global attribute time string
1103    character(len=256) :: initTime ! Global attribute time string
1104    integer :: mppFlag, diagFlag
1105    character(len=1024) :: output_flnm ! Output file name
1106    integer :: iret ! NetCDF return status
1107    integer :: ftn  ! NetCDF file handle
1108    integer :: dimId(8) ! NetCDF dimension ID values
1109    integer :: varId ! NetCDF variable ID value
1110    integer :: timeId ! NetCDF time variable ID
1111    integer :: refTimeId ! NetCDF reference_time variable ID
1112    integer :: coordVarId ! NetCDF coordinate variable ID
1113    integer :: xVarId,yVarId ! NetCDF x/y variable ID
1114    integer :: ierr, myId ! MPI related values
1115    integer :: varRange(2) ! Local storage of valid min/max values
1116    real :: varRangeReal(2) ! Local storage of valid min/max values
1117    integer :: iTmp,jTmp,zTmp,jTmp2,iTmp2
1118    integer :: ftnGeo,geoXVarId,geoYVarId
1119    integer :: waterVal ! Value in HRLDAS in WRFINPUT file used to define water bodies for masking
1120    integer :: sfcflag
1121    ! Allocatable arrays to hold global output arrays, and local arrays for
1122    ! conversion to integers.
1123    integer, allocatable, dimension(:,:) :: localCompTmp, globalCompTmp
1124    integer, allocatable, dimension(:,:,:) :: globalOutComp
1125    real, allocatable, dimension(:,:,:) :: globalOutReal
1126    real, allocatable, dimension(:,:) :: globalRealTmp
1127    real*8, allocatable, dimension(:) :: yCoord,xCoord,yCoord2
1128    real, allocatable, dimension(:,:,:) :: varRealTmp
1129    character (len=64) :: modelConfigType ! This is character verion (long name) for the io_config_outputs
1131 #ifdef MPP_LAND
1132    mppFlag = 1
1133 #else
1134    mppFlag = 0
1135 #endif
1137 #ifdef HYDRO_D
1138    diagFlag = 1
1139 #else
1140    diagFlag = 0
1141 #endif
1143    ! If we are running over MPI, determine which processor number we are on.
1144    ! If not MPI, then default to 0, which is the I/O ID.
1145    if(mppFlag .eq. 1) then
1146 #ifdef MPP_LAND
1147       call MPI_COMM_RANK( HYDRO_COMM_WORLD, myId, ierr )
1148       call nwmCheck(diagFlag,ierr,'ERROR: Unable to determine MPI process ID.')
1149 #endif
1150    else
1151       myId = 0
1152    endif
1154    ! Initialize water type to 16.
1155    ! NOTE THIS MAY CHANGE IN THE FUTURE!!!!!
1156    waterVal = rt_domain(1)%iswater
1158    ! Initialize overland routing flag for SFCRNOFF outputs
1159    sfcflag = 1
1160    if (nlst(1)%OVRTSWCRT > 0) then
1161      sfcflag = 0
1162    endif
1164    ! Initialize NWM dictionary derived type containing all the necessary
1165    ! metadata for the output file.
1166    call initLdasDict(fileMeta,myId,diagFlag)
1168    ! Calculate necessary datetime information that will go into the output file.
1169    ! First compose strings of EPOCH and simulation start date.
1170    epochDate = trim("1970-01-01 00:00")
1171    startDateTmp = trim(nlst(1)%startdate(1:4)//"-"//&
1172                        nlst(1)%startdate(6:7)//&
1173                        &"-"//nlst(1)%startdate(9:10)//" "//&
1174                        nlst(1)%startdate(12:13)//":"//&
1175                        nlst(1)%startdate(15:16))
1176    ! Second, utilize NoahMP date utilities to calculate the number of minutes
1177    ! from EPOCH to the beginning of the model simulation.
1178    call geth_idts(startDateTmp,epochDate,minSinceEpoch1)
1179    ! Third, calculate the number of minutes since the beginning of the
1180    ! simulation.
1181    minSinceSim = int(itime * nlst(1)%dt / 60)
1182    ! Fourth, calculate the total number of minutes from EPOCH to the current
1183    ! model time step.
1184    minSinceEpoch = minSinceEpoch1 + minSinceSim
1185    ! Fifth, compose global attribute time strings that will be used.
1186    validTime = trim(nlst(1)%olddate(1:4)//'-'//&
1187                     nlst(1)%olddate(6:7)//'-'//&
1188                     nlst(1)%olddate(9:10)//'_'//&
1189                     nlst(1)%olddate(12:13)//':'//&
1190                     nlst(1)%olddate(15:16)//&
1191                     &':00')
1192    initTime = trim(nlst(1)%startdate(1:4)//'-'//&
1193                   nlst(1)%startdate(6:7)//'-'//&
1194                   nlst(1)%startdate(9:10)//'_'//&
1195                   nlst(1)%startdate(12:13)//':'//&
1196                   nlst(1)%startdate(15:16)//&
1197                   &':00')
1199    ! Replace default values in the dictionary.
1200    fileMeta%initTime = trim(initTime)
1201    fileMeta%validTime = trim(validTime)
1203    ! calculate the minimum and maximum time
1204    fileMeta%timeValidMin = minSinceEpoch1 + output_timestep / 60  !  output_timestep is in seconds
1205    fileMeta%timeValidMax = minSinceEpoch1 + int(nlst(1)%khour * 3600 / output_timestep ) * output_timestep / 60
1207    ! calculate total_valid_time
1208    fileMeta%totalValidTime = int(nlst(1)%khour * 3600 / output_timestep )  ! # number of valid time (#of output files)
1210    ! Depending on the NWM forecast config, we will be outputting different
1211    ! varibles. DO NOT MODIFY THESE ARRAYS WITHOUT CONSULTING NCAR OR
1212    ! OWP!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1213    if(nlst(1)%io_config_outputs .eq. 0) then
1214       ! All
1215       fileMeta%outFlag(:) = [1,1,1,1,1,1,1,1,1,1,& !1-10
1216                              1,1,1,1,1,1,1,1,1,1,& !11-20
1217                              sfcflag,1,1,1,1,1,1,1,1,1,& !21-30
1218                              1,1,1,1,1,1,1,1,1,1,& !31-40
1219                              1,1,1,1,1,1,1,1,1,1,& !41-50
1220                              1,1,1,1,1,1,1,1,1,1,& !51-60
1221                              1,1,1,1,1,1,1,1,1,1,& !61-70
1222                              1,1,1,1,1,1,1,1,1,1,& !71-80
1223                              1,1,1,1,1,1,1,1,1,1,& !81-90
1224                              1,1,1,1,1,1,1,1,&     !91-98
1225                              1,1,1,&               !99-101
1226                              1,1,1,&               !102-104
1227                              1,1,1,&               !105-107
1228                              1,1,1,&               !108-110
1229                              1,1,1,&               !111-113
1230                              1,1,1]                !114
1232   else if(nlst(1)%io_config_outputs .eq. 1) then
1233       ! Analysis and Assimilation
1234       fileMeta%outFlag(:) = [0,0,0,0,0,0,0,0,0,0,& !1-10
1235                              0,0,0,0,0,0,1,0,0,0,& !11-20
1236                              0,0,0,0,0,0,0,0,0,0,& !21-30
1237                              0,0,0,0,0,0,0,0,0,0,& !31-40
1238                              0,0,0,0,0,0,0,0,0,0,& !41-50
1239                              0,0,0,0,0,0,0,0,1,1,& !51-60
1240                              0,0,1,1,1,1,1,1,0,1,& !61-70
1241                              0,0,0,0,0,0,0,0,0,0,& !71-80
1242                              0,0,0,0,0,0,0,0,0,1,& !81-90
1243                              0,1,1,0,1,0,0,1,&     !91-98
1244                              0,0,0,&               !99-101
1245                              0,0,0,&               !102-104
1246                              0,0,0,&               !105-107
1247                              0,0,0,&               !108-110
1248                              0,0,0,&               !111-113
1249                              0,0,0]                !114
1251    else if(nlst(1)%io_config_outputs .eq. 2) then
1252       ! Short Range
1253       fileMeta%outFlag(:) = [0,0,0,0,0,0,0,0,0,0,& !1-10
1254                              0,0,0,0,0,0,0,0,0,0,& !11-20
1255                              0,0,0,0,0,0,0,0,0,0,& !21-30
1256                              0,0,0,0,0,0,0,0,0,0,& !31-40
1257                              0,0,0,0,0,0,0,0,0,0,& !41-50
1258                              0,0,0,0,0,0,0,0,0,0,& !51-60
1259                              0,0,0,1,1,0,0,1,0,0,& !61-70
1260                              0,0,0,0,0,0,0,0,0,0,& !71-80
1261                              0,0,0,0,0,0,0,0,0,1,& !81-90
1262                              0,0,1,0,1,0,0,0,&     !91-98
1263                              0,0,0,&               !99-101
1264                              0,0,0,&               !102-104
1265                              0,0,0,&               !105-107
1266                              0,0,0,&               !108-110
1267                              0,0,0,&               !111-113
1268                              0,0,0]                !114
1270    else if(nlst(1)%io_config_outputs .eq. 3) then
1271       ! Medium Range
1272       fileMeta%outFlag(:) = [0,0,0,0,0,0,0,0,0,0,& !1-10
1273                              1,1,1,1,1,0,0,0,0,1,& !11-20
1274                              0,0,0,0,0,0,0,1,1,1,& !21-30
1275                              0,0,0,0,0,0,0,0,0,0,& !31-40
1276                              0,0,0,0,1,0,0,0,0,0,& !41-50
1277                              0,0,0,0,0,0,0,0,1,1,& !51-60
1278                              0,0,1,1,1,0,1,1,0,1,& !61-70
1279                              0,0,0,0,0,0,0,0,0,0,& !71-80
1280                              0,0,0,0,0,0,0,0,0,1,& !81-90
1281                              1,1,1,0,1,0,0,0,&     !91-98
1282                              0,0,0,&               !99-101
1283                              0,0,0,&               !102-104
1284                              0,0,0,&               !105-107
1285                              0,0,0,&               !108-110
1286                              0,0,0,&               !111-113
1287                              0,0,0]                !114
1289    else if(nlst(1)%io_config_outputs .eq. 4) then
1290       ! Long Range
1291       fileMeta%outFlag(:) = [0,0,0,0,0,0,0,0,0,0,& !1-10
1292                              0,0,0,0,0,0,0,0,0,1,& !11-20
1293                              sfcflag,0,0,0,0,0,0,0,0,0,& !21-30
1294                              0,0,0,0,0,0,0,0,0,0,& !31-40
1295                              0,0,0,0,0,0,0,0,0,0,& !41-50
1296                              0,0,0,0,0,0,0,0,0,0,& !51-60
1297                              0,0,0,0,1,0,0,0,0,1,& !61-70
1298                              0,0,0,0,0,0,0,0,0,0,& !71-80
1299                              0,0,0,0,0,0,0,0,0,1,& !81-90
1300                              1,0,1,1,0,0,0,0,&     !91-98
1301                              0,0,0,&               !99-101
1302                              0,0,0,&               !102-104
1303                              0,0,0,&               !105-107
1304                              0,0,0,&               !108-110
1305                              0,0,0,&               !111-113
1306                              0,0,0]                !114
1308    else if(nlst(1)%io_config_outputs .eq. 5) then
1309       ! Retrospective
1310       fileMeta%outFlag(:) = [0,0,0,0,0,0,1,0,0,0,& !1-10
1311                              1,1,0,1,1,0,1,1,0,1,& !11-20
1312                              sfcflag,0,0,0,0,0,0,0,0,0,& !21-30
1313                              0,0,0,0,0,0,0,0,0,0,& !31-40
1314                              0,0,0,0,1,0,0,0,0,0,& !41-50
1315                              0,0,0,0,0,0,0,0,0,0,& !51-60
1316                              1,0,1,1,1,1,0,1,1,1,& !61-70
1317                              0,0,0,0,0,0,0,0,0,0,& !71-80
1318                              0,0,0,0,0,0,0,0,0,1,& !81-90
1319                              0,0,0,0,0,1,1,1,&     !91-98
1320                              0,0,0,&               !99-101
1321                              0,0,0,&               !102-104
1322                              0,0,0,&               !105-107
1323                              1,1,0,&               !108-110
1324                              1,0,0,&               !111-113
1325                              1,1,1]                !114
1327    else if(nlst(1)%io_config_outputs .eq. 6) then
1328       ! Diagnostics
1329       fileMeta%outFlag(:) = [0,0,0,0,0,0,1,0,0,0,& !1-10
1330                              1,1,1,1,1,0,1,1,0,1,& !11-20
1331                              sfcflag,0,0,0,0,0,0,1,1,1,& !21-30
1332                              0,0,0,0,0,0,0,0,0,0,& !31-40
1333                              0,0,0,0,1,0,0,0,0,0,& !41-50
1334                              0,0,0,0,0,0,0,0,1,1,& !51-60
1335                              1,0,1,1,1,1,1,1,1,1,& !61-70
1336                              0,0,0,0,0,0,0,0,0,0,& !71-80
1337                              0,0,0,0,0,0,0,0,0,1,& !81-90
1338                              1,1,1,1,1,1,1,1,&     !91-98
1339                              0,0,0,&               !99-101
1340                              0,0,0,&               !102-104
1341                              0,0,0,&               !105-107
1342                              1,1,0,&               !108-110
1343                              1,0,0,&               !111-113
1344                              1,1,1]                !114
1345    else
1346       call nwmCheck(diagFlag,1,'ERROR: Invalid IOC flag provided by namelist file.')
1347    endif
1349    ! ! If crocus is off, these should not be outputted
1350    if (noah_lsm%crocus_opt == 0) then
1351       fileMeta%outFlag(101) = 0
1352       fileMeta%outFlag(102) = 0
1353       fileMeta%outFlag(103) = 0
1354       fileMeta%outFlag(104) = 0
1355       fileMeta%outFlag(108) = 0
1356       fileMeta%outFlag(109) = 0
1357       fileMeta%outFlag(111) = 0
1358       fileMeta%outFlag(114) = 0
1359       fileMeta%outFlag(115) = 0
1360       fileMeta%outFlag(116) = 0
1361       fileMeta%numVars = numLdasVars_crocus_off ! 98
1362    end if
1364    ! call the GetModelConfigType function
1365    modelConfigType = GetModelConfigType(nlst(1)%io_config_outputs)
1367    if(varInd .eq. 1) then
1368       ! We are on the first variable, we need to create the output file with
1369       ! attributes first.
1370       if(myId .eq. 0) then
1371          ! We are on the I/O node. Create output file.
1372          if (mod(output_timestep,3600) == 0) then
1373             write(output_flnm, '(A,"/",A12,".LDASOUT_DOMAIN",I1)') outdir,date(1:4)//&
1374                   date(6:7)//date(9:10)//date(12:13)//date(15:16), igrid
1375          elseif (mod(output_timestep,60) == 0) then
1376             write(output_flnm, '(A,"/",A12,".LDASOUT_DOMAIN",I1)') outdir,date(1:4)//&
1377                   date(6:7)//date(9:10)//date(12:13)//date(15:16), igrid
1378          else
1379             write(output_flnm, '(A,"/",A14,".LDASOUT_DOMAIN",I1)') outdir,date(1:4)//&
1380                   date(6:7)//date(9:10)//date(12:13)//date(15:16)//date(18:19), igrid
1381          endif
1383          iret = nf90_create(trim(output_flnm),cmode=NF90_NETCDF4,ncid = ftn)
1384          call nwmCheck(diagFlag,iret,'ERROR: Unable to create LDASOUT NetCDF file.')
1385          ftnNoahMP = ftn
1387          ! Write global attributes
1388          iret = nf90_put_att(ftnNoahMP,NF90_GLOBAL,'TITLE',trim(fileMeta%title))
1389          call nwmCheck(diagFlag,iret,'ERROR: Unable to place TITLE attribute into LDASOUT file.')
1390          iret = nf90_put_att(ftnNoahMP,NF90_GLOBAL,"compiler_version",compiler_version())
1391          call nwmCheck(diagFlag,iret,'ERROR: Unable to create compiler_version attribute')
1392          iret = nf90_put_att(ftnNoahMP,NF90_GLOBAL,'model_initialization_time',trim(fileMeta%initTime))
1393          call nwmCheck(diagFlag,iret,'ERROR: Unable to place model init time attribute into LDASOUT file.')
1394          iret = nf90_put_att(ftnNoahMP,NF90_GLOBAL,'model_output_valid_time',trim(fileMeta%validTime))
1395          call nwmCheck(diagFlag,iret,'ERROR: Unable to place model output time attribute into LDASOUT file.')
1396          iret = nf90_put_att(ftnNoahMP,NF90_GLOBAL,'model_total_valid_times',fileMeta%totalValidTime)
1397          call nwmCheck(diagFlag,iret,'ERROR: Unable to place model total_valid_times attribute into LDASOUT file.')
1398          iret = nf90_put_att(ftnNoahMP,NF90_GLOBAL,'Conventions',trim(fileMeta%conventions))
1399          call nwmCheck(diagFlag,iret,'ERROR: Unable to place CF conventions attribute into LDASOUT file.')
1400          iret = nf90_put_att(ftnNoahMP,NF90_GLOBAL,"code_version",trim(get_code_version()))
1401          call nwmCheck(diagFlag,iret,'ERROR: Unable to create code_version attribute')
1402 #ifdef NWM_META
1403          iret = nf90_put_att(ftnNoahMP,NF90_GLOBAL,"NWM_version_number",trim(get_nwm_version()))
1404          call nwmCheck(diagFlag,iret,'ERROR: Unable to create NWM_version_number attribute')
1405 #endif
1406          iret = nf90_put_att(ftn,NF90_GLOBAL,"model_output_type",trim(fileMeta%modelOutputType))
1407          call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_output_type attribute')
1408          iret = nf90_put_att(ftn,NF90_GLOBAL,"model_configuration",modelConfigType)
1409          call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_configuration attribute')
1410          iret = nf90_put_att(ftnNoahMP,NF90_GLOBAL,"proj4",trim(fileMeta%proj4))
1411          call nwmCheck(diagFlag,iret,'ERROR: Unable to create proj4 attribute')
1412          iret = nf90_put_att(ftnNoahMP,NF90_GLOBAL,"GDAL_DataType","Generic")
1413          call nwmCheck(diagFlag,iret,'ERROR: Unable to create GDAL_DataType attribute')
1415          ! Create dimensions
1416          iret = nf90_def_dim(ftnNoahMP,'time',NF90_UNLIMITED,dimId(1))
1417          call nwmCheck(diagFlag,iret,'ERROR: Unable to define time dimension')
1418          iret = nf90_def_dim(ftnNoahMP,'x',global_nx,dimId(2))
1419          call nwmCheck(diagFlag,iret,'ERROR: Unable to define x dimension')
1420          iret = nf90_def_dim(ftnNoahMP,'y',global_ny,dimId(3))
1421          call nwmCheck(diagFlag,iret,'ERROR: Unable to define y dimension')
1422          iret = nf90_def_dim(ftnNoahMP,'soil_layers_stag',fileMeta%numSoilLayers,dimId(4))
1423          call nwmCheck(diagFlag,iret,'ERROR: Unable to define soil_layers_stag dimension')
1424          iret = nf90_def_dim(ftnNoahMP,'snow_layers',fileMeta%numSnowLayers,dimId(5))
1425          call nwmCheck(diagFlag,iret,'ERROR: Unable to define snow_layers dimension')
1426          iret = nf90_def_dim(ftnNoahMP,'reference_time',1,dimId(6))
1427          call nwmCheck(diagFlag,iret,'ERROR: Unable to define reference_time dimension')
1428          if (noah_lsm%crocus_opt == 1) &
1429               iret = nf90_def_dim(ftnNoahMP,'glacier_levels',fileMeta%act_lev,dimId(8))
1430          call nwmCheck(diagFlag,iret,'ERROR: Unable to define act_layers dimension')
1431          ! Only create vis_nir if we are outputting the two snow albedo variables.
1432          ! Otherwise these are unecessary dimensions.
1433          if ((fileMeta%outFlag(96) .eq. 1) .or. (fileMeta%outFlag(96) .eq. 1)) then
1434          iret = nf90_def_dim(ftnNoahMP,'vis_nir',fileMeta%numSpectrumBands,dimId(7))
1435          call nwmCheck(diagFlag,iret,'ERROR: Unable to define vis_nir dimension')
1436          endif
1438          ! Create and populate reference_time and time variables.
1439          iret = nf90_def_var(ftnNoahMP,"time",nf90_int,dimId(1),timeId)
1440          call nwmCheck(diagFlag,iret,'ERROR: Unable to create time variable')
1441          iret = nf90_put_att(ftnNoahMP,timeId,'long_name',trim(fileMeta%timeLName))
1442          call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into time variable')
1443          iret = nf90_put_att(ftnNoahMP,timeId,'standard_name',trim(fileMeta%timeStName))
1444          call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into time variable')
1445          iret = nf90_put_att(ftnNoahMP,timeId,'units',trim(fileMeta%timeUnits))
1446          call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into time variable')
1447          iret = nf90_put_att(ftn,timeId,'valid_min',fileMeta%timeValidMin)
1448          call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_min attribute into time variable')
1449          iret = nf90_put_att(ftn,timeId,'valid_max',fileMeta%timeValidMax)
1450          call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_max attribute into time variable')
1451          iret = nf90_def_var(ftnNoahMP,"reference_time",nf90_int,dimId(6),refTimeId)
1452          call nwmCheck(diagFlag,iret,'ERROR: Unable to create reference_time variable')
1453          iret = nf90_put_att(ftnNoahMP,refTimeId,'long_name',trim(fileMeta%rTimeLName))
1454          call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into reference_time variable')
1455          iret = nf90_put_att(ftnNoahMP,refTimeId,'standard_name',trim(fileMeta%rTimeStName))
1456          call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into reference_time variable')
1457          iret = nf90_put_att(ftnNoahMP,refTimeId,'units',trim(fileMeta%rTimeUnits))
1458          call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into reference_time variable')
1460          ! Create x/y coordinate variables
1461          iret = nf90_def_var(ftnNoahMP,'x',nf90_double,dimId(2),xVarId)
1462          call nwmCheck(diagFlag,iret,'ERROR: Unable to create x coordinate variable')
1463          do iTmp=1,fileMeta%nxRealAtts
1464             iret = nf90_put_att(ftnNoahMP,xVarId,trim(fileMeta%xFloatAttNames(iTmp)),&
1465                                 fileMeta%xRealAttVals(iTmp,1:fileMeta%xRealAttLen(iTmp)))
1466             call nwmCheck(diagFlag,iret,'ERROR: Unable to place x floating point attributes into LDASOUT file.')
1467          end do
1468          do iTmp=1,fileMeta%nxCharAtts
1469             iret = nf90_put_att(ftnNoahMP,xVarId,trim(fileMeta%xCharAttNames(iTmp)),trim(fileMeta%xCharAttVals(iTmp)))
1470             call nwmCheck(diagFlag,iret,'ERROR: Unable to place x string point attributes into LDASOUT file.')
1471          end do
1472          iret = nf90_def_var(ftnNoahMP,'y',nf90_double,dimId(3),yVarId)
1473          call nwmCheck(diagFlag,iret,'ERROR: Unable to create y coordinate variable')
1474          do iTmp=1,fileMeta%nyRealAtts
1475             iret = nf90_put_att(ftnNoahMP,yVarId,trim(fileMeta%yFloatAttNames(iTmp)),&
1476                                 fileMeta%yRealAttVals(iTmp,1:fileMeta%yRealAttLen(iTmp)))
1477             call nwmCheck(diagFlag,iret,'ERROR: Unable to place y floating point attributes into LDASOUT file.')
1478          end do
1479          do iTmp=1,fileMeta%nyCharAtts
1480             iret = nf90_put_att(ftnNoahMP,yVarId,trim(fileMeta%yCharAttNames(iTmp)),trim(fileMeta%yCharAttVals(iTmp)))
1481             call nwmCheck(diagFlag,iret,'ERROR: Unable to place y string point attributes into LDASOUT file.')
1482          end do
1484          ! Define compression if chosen.
1485          if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
1486             iret = nf90_def_var_deflate(ftn,timeId,0,1,2)
1487             call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for time.')
1488             iret = nf90_def_var_deflate(ftn,refTimeId,0,1,2)
1489             call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for reference_time.')
1490             iret = nf90_def_var_deflate(ftn,xVarId,0,1,2)
1491             call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for x.')
1492             iret = nf90_def_var_deflate(ftn,yVarId,0,1,2)
1493             call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for y.')
1494          endif
1496          ! Translate crs variable info from land spatial metadata file to output
1497          ! file.
1498          iret = nf90_def_var(ftnNoahMP,'crs',nf90_char,varid=coordVarId)
1499          call nwmCheck(diagFlag,iret,'ERROR: Unable to create crs variable in LDASOUT file.')
1500          do iTmp=1,fileMeta%nCrsRealAtts
1501             iret = nf90_put_att(ftnNoahMP,coordVarId,trim(fileMeta%crsFloatAttNames(iTmp)),&
1502                                 fileMeta%crsRealAttVals(iTmp,1:fileMeta%crsRealAttLen(iTmp)))
1503             call nwmCheck(diagFlag,iret,'ERROR: Unable to place crs floating point attributes into LDASOUT file.')
1504          end do
1505          do iTmp=1,fileMeta%nCrsCharAtts
1506             iret = nf90_put_att(ftnNoahMP,coordVarId,trim(fileMeta%crsCharAttNames(iTmp)),trim(fileMeta%crsCharAttVals(iTmp)))
1507             call nwmCheck(diagFlag,iret,'ERROR: Unable to place crs string point attributes into LDASOUT file.')
1508          end do
1510          ! Loop through all possible variables and create them, along with their
1511          ! metadata attributes.
1512          do iTmp=1,fileMeta%numVars
1513             if(fileMeta%outFlag(iTmp) .eq. 1) then
1514                if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
1515                   if(fileMeta%numLev(iTmp) .eq. fileMeta%numSoilLayers) then
1516                      iret = nf90_def_var(ftnNoahMP,trim(fileMeta%varNames(iTmp)),nf90_int,(/dimId(2),dimId(4),dimId(3),dimId(1)/),varId)
1517                   else if(fileMeta%numLev(iTmp) .eq. fileMeta%numSnowLayers) then
1518                      iret = nf90_def_var(ftnNoahMP,trim(fileMeta%varNames(iTmp)),nf90_int,(/dimId(2),dimId(5),dimId(3),dimId(1)/),varId)
1519                   else if(noah_lsm%crocus_opt == 1 .and. fileMeta%numLev(iTmp) .eq. fileMeta%act_lev) then
1520                      iret = nf90_def_var(ftnNoahMP,trim(fileMeta%varNames(iTmp)),nf90_int,(/dimId(2),dimId(8),dimId(3),dimId(1)/),varId)
1521                   else if(fileMeta%numLev(iTmp) .eq. fileMeta%numSpectrumBands) then
1522                      iret = nf90_def_var(ftnNoahMP,trim(fileMeta%varNames(iTmp)),nf90_int,(/dimId(2),dimId(7),dimId(3),dimId(1)/),varId)
1523                   else if(fileMeta%numLev(iTmp) .eq. 1) then
1524                      iret = nf90_def_var(ftnNoahMP,trim(fileMeta%varNames(iTmp)),nf90_int,(/dimId(2),dimId(3),dimId(1)/),varId)
1525                   endif
1526                else
1527                   if(fileMeta%numLev(iTmp) .eq. fileMeta%numSoilLayers) then
1528                      iret = nf90_def_var(ftnNoahMP,trim(fileMeta%varNames(iTmp)),nf90_float,(/dimId(2),dimId(4),dimId(3),dimId(1)/),varId)
1529                   else if(fileMeta%numLev(iTmp) .eq. fileMeta%numSnowLayers) then
1530                      iret = nf90_def_var(ftnNoahMP,trim(fileMeta%varNames(iTmp)),nf90_float,(/dimId(2),dimId(5),dimId(3),dimId(1)/),varId)
1531                   else if(noah_lsm%crocus_opt == 1 .and. fileMeta%numLev(iTmp) .eq. fileMeta%act_lev) then
1532                      iret = nf90_def_var(ftnNoahMP,trim(fileMeta%varNames(iTmp)),nf90_float,(/dimId(2),dimId(8),dimId(3),dimId(1)/),varId)
1533                   else if(fileMeta%numLev(iTmp) .eq. fileMeta%numSpectrumBands) then
1534                      iret = nf90_def_var(ftnNoahMP,trim(fileMeta%varNames(iTmp)),nf90_float,(/dimId(2),dimId(7),dimId(3),dimId(1)/),varId)
1535                   else if(fileMeta%numLev(iTmp) .eq. 1) then
1536                      iret = nf90_def_var(ftnNoahMP,trim(fileMeta%varNames(iTmp)),nf90_float,(/dimId(2),dimId(3),dimId(1)/),varId)
1537                   endif
1538                endif
1539                call nwmCheck(diagFlag,iret,"ERROR: Unable to create variable: "//trim(fileMeta%varNames(iTmp)))
1541                ! Extract valid range into a 1D array for placement.
1542                varRange(1) = fileMeta%validMinComp(iTmp)
1543                varRange(2) = fileMeta%validMaxComp(iTmp)
1544                varRangeReal(1) = real(fileMeta%validMinDbl(iTmp))
1545                varRangeReal(2) = real(fileMeta%validMaxDbl(iTmp))
1547                ! Establish a compression level for the variables. For now we are using a
1548                ! compression level of 2. In addition, we are choosing to turn the shuffle
1549                ! filter off for now. Kelley Eicher did some testing with this and
1550                ! determined that the benefit wasn't worth the extra time spent writing output.
1551                ! Only compress if io_form_outputs is set to 1.
1552                if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
1553                   iret = nf90_def_var_deflate(ftnNoahMP,varId,0,1,2)
1554                   call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression for: '//trim(fileMeta%varNames(iTmp)))
1555                endif
1557                ! Create variable attributes
1558                iret = nf90_put_att(ftnNoahMP,varId,'long_name',trim(fileMeta%longName(iTmp)))
1559                call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into variable '//trim(fileMeta%varNames(iTmp)))
1560                iret = nf90_put_att(ftnNoahMP,varId,'units',trim(fileMeta%units(iTmp)))
1561                call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into variable '//trim(fileMeta%varNames(iTmp)))
1562                iret = nf90_put_att(ftnNoahMP,varId,'grid_mapping','crs')
1563                call nwmCheck(diagFlag,iret,'ERROR: Unable to place grid_mapping attribute into variable: '//trim(fileMeta%varNames(iTmp)))
1564                if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
1565                   iret = nf90_put_att(ftnNoahMP,varId,'_FillValue',fileMeta%fillComp(iTmp))
1566                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
1567                   iret = nf90_put_att(ftnNoahMP,varId,'missing_value',fileMeta%missingComp(iTmp))
1568                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
1569                   iret = nf90_put_att(ftnNoahMP,varId,'scale_factor',fileMeta%scaleFactor(iTmp))
1570                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place scale_factor attribute into variable '//trim(fileMeta%varNames(iTmp)))
1571                   iret = nf90_put_att(ftnNoahMP,varId,'add_offset',fileMeta%addOffset(iTmp))
1572                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place add_offset attribute into variable '//trim(fileMeta%varNames(iTmp)))
1573                   iret = nf90_put_att(ftnNoahMP,varId,'valid_range',varRange)
1574                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
1575                else
1576                   iret = nf90_put_att(ftnNoahMP,varId,'_FillValue',fileMeta%fillReal(iTmp))
1577                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
1578                   iret = nf90_put_att(ftnNoahMP,varId,'missing_value',fileMeta%missingReal(iTmp))
1579                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
1580                   iret = nf90_put_att(ftnNoahMP,varId,'valid_range',varRangeReal)
1581                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
1582                endif
1583                ! Place necessary geospatial attributes into the variable.
1584                do iTmp2=1,fileMeta%nCrsCharAtts
1585                   if(trim(fileMeta%crsCharAttNames(iTmp2)) .eq. 'esri_pe_string') then
1586                      iret = nf90_put_att(ftnNoahMP,varId,trim(fileMeta%crsCharAttNames(iTmp2)),trim(fileMeta%crsCharAttVals(iTmp2)))
1587                      call nwmCheck(diagFlag,iret,'ERROR: Unable to place esri_pe_string attribute into '//trim(fileMeta%varNames(iTmp)))
1588                   endif
1589                end do
1590             endif ! End if output flag is on
1591          end do ! end looping through variable output list.
1593          ! Remove NetCDF file from definition mode.
1594          iret = nf90_enddef(ftnNoahMP)
1595          call nwmCheck(diagFlag,iret,'ERROR: Unable to take LDASOUT file out of definition mode')
1597          ! Read in coordinates from GeoGrid file. These will be placed into the
1598          ! output file coordinate variables.
1599          allocate(xCoord(global_nx))
1600          allocate(yCoord(global_ny))
1601          allocate(yCoord2(global_ny))
1602          iret = nf90_open(trim(nlst(1)%land_spatial_meta_flnm),NF90_NOWRITE,ncid=ftnGeo)
1603          if(iret .ne. 0) then
1604             ! Spatial metadata file not found for land grid. Warn the user no
1605             ! file was found, and set x/y coordinates to -9999.0
1606             call postDiagMsg(diagFlag,'WARNING: Unable to find LAND spatial metadata file')
1607             xCoord = -9999.0
1608             yCoord = -9999.0
1609             yCoord2 = -9999.0
1610          else
1611             iret = nf90_inq_varid(ftnGeo,'x',geoXVarId)
1612             call nwmCheck(diagFlag,iret,'ERROR: Unable to find x coordinate in geoGrid file')
1613             iret = nf90_get_var(ftnGeo,geoXVarId,xCoord)
1614             call nwmCheck(diagFlag,iret,'ERROR: Unable to extract x coordinate from geoGrid file')
1615             iret = nf90_inq_varid(ftnGeo,'y',geoYVarId)
1616             call nwmCheck(diagFlag,iret,'ERROR: Unable to find y coordinate in geoGrid file')
1617             iret = nf90_get_var(ftnGeo,geoYVarId,yCoord)
1618             call nwmCheck(diagFlag,iret,'ERROR: Unable to extract y coordinate from geoGrid file')
1620             iret = nf90_close(ftnGeo)
1621             call nwmCheck(diagFlag,iret,'ERROR: Unable to close geoGrid file.')
1622             ! Reverse Y coordinates. They are read in reverse.
1623             jTmp2 = 0
1624             do jTmp = global_ny,1,-1
1625                jTmp2 = jTmp2 + 1
1626                yCoord2(jTmp2) = yCoord(jTmp)
1627             end do
1628          endif
1630          ! Place coordinate values into output file
1631          iret = nf90_inq_varid(ftnNoahMP,'x',varId)
1632          call nwmCheck(diagFlag,iret,'ERROR: Unable to locate x coordinate variable.')
1633          iret = nf90_put_var(ftnNoahMP,varId,xCoord)
1634          call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into x coordinate variable')
1635          iret = nf90_inq_varid(ftnNoahMP,'y',varId)
1636          call nwmCheck(diagFlag,iret,'ERROR: Unable to locate y coordinate variable')
1637          iret = nf90_put_var(ftnNoahMP,varId,yCoord2)
1638          call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into y coordinate variable')
1639          deallocate(xCoord)
1640          deallocate(yCoord)
1641          deallocate(yCoord2)
1643          ! Place time values into time variables.
1644          iret = nf90_inq_varid(ftnNoahMP,'time',varId)
1645          call nwmCheck(diagFlag,iret,'ERROR: Unable to locate time variable')
1646          iret = nf90_put_var(ftnNoahMP,varId,minSinceEpoch)
1647          call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into time variable')
1648          iret = nf90_inq_varid(ftnNoahMP,'reference_time',varId)
1649          call nwmCheck(diagFlag,iret,'ERROR: Unable to locate reference_time variable')
1650          iret = nf90_put_var(ftnNoahMP,varId,minSinceEpoch1)
1651          call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into reference_time variable')
1653       end if ! End if we are on the I/O processor.
1654    endif ! End if we are on the first variable
1656    ! Place data into NetCDF file. This involves a few steps:
1657    ! 1.) Allocate an integer array of local grid size.
1658    ! 2.) Allocate an integer array of global grid size.
1659    ! 3.) Make a copy of the floating point grid so it can be
1660    !     masked out where water bodies exist, or missing NoahMP values
1661    !     exist.
1662    ! 4.) Loop through real local grid, convert floating point
1663    !     values to integer via scale_factor/add_offset. If
1664    !     missing value found, assign FillValue caluclated
1665    !     in the dictionary.
1666    ! 5.) Use MPP utilities to collect local integer arrays
1667    !     into global integer array.
1668    ! 6.) Write global integer array into output file.
1669    if(fileMeta%outFlag(varInd) .eq. 1) then
1670       ! Output flag on for this variable.
1671       ! Allocate memory
1672       if(myId .eq. 0) then
1673          allocate(globalOutComp(global_nx,fileMeta%numLev(varInd),global_ny))
1674          allocate(globalCompTmp(global_nx,global_ny))
1675          allocate(globalOutReal(global_nx,fileMeta%numLev(varInd),global_ny))
1676          allocate(globalRealTmp(global_nx,global_ny))
1677       else
1678          allocate(globalOutComp(1,1,1))
1679          allocate(globalCompTmp(1,1))
1680          allocate(globalOutReal(1,1,1))
1681          allocate(globalRealTmp(1,1))
1682       endif
1683       allocate(localCompTmp(ixPar,jxPar))
1684       allocate(varRealTmp(ixPar,fileMeta%numLev(varInd),jxPar))
1685       globalOutComp = fileMeta%fillComp(varInd)
1686       globalOutReal = fileMeta%fillReal(varInd)
1688       varRealTmp = varReal
1689       ! Reset any missing values that may exist.
1690       where ( varRealTmp .eq. fileMeta%modelNdv ) varRealTmp = fileMeta%fillReal(varInd)
1691       where ( varRealTmp .eq. fileMeta%modelNdvInt ) varRealTmp = fileMeta%fillReal(varInd)
1692       where ( varRealTmp .eq. fileMeta%modelNdv2 ) varRealTmp = fileMeta%fillReal(varInd)
1693       where ( varRealTmp .eq. fileMeta%modelNdv3 ) varRealTmp = fileMeta%fillReal(varInd)
1694       where (varRealTmp .ne. varRealTmp) varRealTmp = fileMeta%fillReal(varInd)
1695       do zTmp = 1,fileMeta%numLev(varInd)
1696          localCompTmp = fileMeta%fillComp(varInd)
1697          globalCompTmp = fileMeta%fillComp(varInd)
1698          globalRealTmp = fileMeta%fillReal(varInd)
1699          where ( vegTyp .eq. waterVal) varRealTmp(:,zTmp,:) = fileMeta%fillReal(varInd)
1700          ! Check to see if we are on time 0. If the flag is set to 0 for time 0
1701          ! outputs, convert all data to a fill. If we are time 0, make sure we
1702          ! don't need to fill the grid in with NDV values.
1703          if(minSinceSim .eq. 0 .and. fileMeta%timeZeroFlag(varInd) .eq. 0) then
1704             localCompTmp = fileMeta%fillComp(varInd)
1705             varRealTmp = fileMeta%fillReal(varInd)
1706          else
1707             localCompTmp = NINT((varRealTmp(:,zTmp,:)-fileMeta%addOffset(varInd))/fileMeta%scaleFactor(varInd))
1708          endif
1710          if(mppFlag .eq. 1) then
1711 #ifdef MPP_LAND
1712             call write_IO_int(localCompTmp,globalCompTmp)
1713             call write_IO_real(varRealTmp(:,zTmp,:),globalRealTmp)
1714 #endif
1715          else
1716             globalCompTmp = localCompTmp
1717             globalRealTmp = varRealTmp(:,zTmp,:)
1718          endif
1720          ! Place output into global array to be written to NetCDF file.
1721          if(myId .eq. 0) then
1722             globalOutComp(:,zTmp,:) = globalCompTmp
1723             globalOutReal(:,zTmp,:) = globalRealTmp
1724          endif
1725       end do
1727       ! Write array out to NetCDF file.
1728       if(myId .eq. 0) then
1729       !   write(*,*) 'trude foo1'
1730       !   write(*,*) 'variable name : ', fileMeta%varNames(varInd)
1731       !   write(*,*) 'varind :', varind
1732       !   write(*,*) 'varid :', varid
1733       !   write(*,*) 'ftnNoahMP :', ftnNoahMP
1734       !   write(*,*) 'num lev :', fileMeta%numLev(varInd)
1735          iret = nf90_inq_varid(ftnNoahMP,trim(fileMeta%varNames(varInd)),varId)
1736          call nwmCheck(diagFlag,iret,'ERROR: Unable to find variable ID for var: '//trim(fileMeta%varNames(varInd)))
1737 !         write(*,*) 'trude foo2'
1738          if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
1739             if(fileMeta%numLev(varInd) .eq. 1) then
1740                iret = nf90_put_var(ftnNoahMP,varId,globalOutComp,(/1,1,1/),(/global_nx,global_ny,1/))
1741             else
1742                iret = nf90_put_var(ftnNoahMP,varId,globalOutComp,(/1,1,1,1/),(/global_nx,fileMeta%numLev(varInd),global_ny,1/))
1743             endif
1744          else
1745             if(fileMeta%numLev(varInd) .eq. 1) then
1746                iret = nf90_put_var(ftnNoahMP,varId,globalOutReal,(/1,1,1/),(/global_nx,global_ny,1/))
1747             else
1748                iret = nf90_put_var(ftnNoahMP,varId,globalOutReal,(/1,1,1,1/),(/global_nx,fileMeta%numLev(varInd),global_ny,1/))
1749             endif
1750          endif
1751          call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into output variable: '//trim(fileMeta%varNames(varInd)))
1752       endif
1754       ! Deallocate memory for this variable.
1755       deallocate(globalOutComp)
1756       deallocate(globalCompTmp)
1757       deallocate(globalOutReal)
1758       deallocate(globalRealTmp)
1759       deallocate(localCompTmp)
1760       deallocate(varRealTmp)
1762    endif
1764    if(myId .eq. 0) then
1765       ! Only close the file if we are finished with the very last variable.
1766       if(varInd .eq. fileMeta%numVars) then
1767          ! Close the output file
1768          iret = nf90_close(ftnNoahMP)
1769          call nwmCheck(diagFlag,iret,'ERROR: Unable to close LDASOUT file.')
1770       endif
1771    endif
1774 end subroutine output_NoahMP_NWM
1776 !==============================================================================
1777 ! Program Name: output_rt_NWM
1778 ! Author(s)/Contact(s): Logan R Karsten <karsten><ucar><edu>
1779 ! Abstract: Output routine for terrain routing variables
1780 !           for the National Water Model.
1781 ! History Log:
1782 ! 3/6/17 -Created, LRK.
1783 ! Usage:
1784 ! Parameters: None.
1785 ! Input Files: None.
1786 ! Output Files: None.
1787 ! Condition codes: None.
1789 ! User controllable options: None.
1791 subroutine output_rt_NWM(domainId,iGrid)
1792    use module_rt_data, only: rt_domain
1793    use config_base, only: nlst
1794    use Module_Date_utilities_rt, only: geth_newdate, geth_idts
1795    use module_NWM_io_dict
1796    use netcdf
1797 #ifdef MPP_LAND
1798      use module_mpp_land
1799 #endif
1800    implicit none
1802    ! subroutine arguments
1803    integer, intent(in) :: domainId
1804    integer, intent(in) :: iGrid
1806    ! Derived types.
1807    type(rtDomainMeta) :: fileMeta
1809    ! Local variables
1810    integer :: mppFlag, diagFlag
1811    integer :: minSinceSim ! Number of minutes since beginning of simulation.
1812    integer :: minSinceEpoch1 ! Number of minutes from EPOCH to the beginning of the model simulation.
1813    integer :: minSinceEpoch ! Number of minutes from EPOCH to the current model valid time.
1814    character(len=16) :: epochDate ! EPOCH represented as a string.
1815    character(len=16) :: startDate ! Start of model simulation, represented as a string.
1816    character(len=256) :: output_flnm ! CHRTOUT_DOMAIN filename
1817    integer :: iret ! NetCDF return statuses
1818    integer :: ftn ! NetCDF file handle
1819    character(len=256) :: validTime ! Global attribute time string
1820    character(len=256) :: initTime ! Global attribute time string
1821    integer :: dimId(5) ! Dimension ID values created during NetCDF created.
1822    integer :: varId ! Variable ID value created as NetCDF variables are created and populated.
1823    integer :: timeId ! Dimension ID for the time dimension.
1824    integer :: refTimeId ! Dimension ID for the reference time dimension.
1825    integer :: xVarId,yVarId,coordVarId ! Coordinate variable NC ID values
1826    integer :: varRange(2) ! Local storage for valid min/max ranges
1827    real :: varRangeReal(2) ! Local storage for valid min/max ranges
1828    integer :: ierr, myId ! MPI return status, process ID
1829    integer :: iTmp,jTmp,jTmp2,iTmp2,zTmp
1830    real :: varRealTmp ! Local copy of floating point lake value
1831    integer :: ftnGeo,geoXVarId,geoYVarId
1832    ! Allocatable arrays to hold either x/y coordinate information,
1833    ! or the grid of output values to be converted to integer via scale_factor
1834    ! and add_offset.
1835    integer, allocatable, dimension(:,:) :: localCompTmp
1836    integer, allocatable, dimension(:,:,:) :: globalOutComp
1837    real, allocatable, dimension(:,:) :: localRealTmp
1838    real, allocatable, dimension(:,:,:) :: globalOutReal
1839    real*8, allocatable, dimension(:) :: yCoord,xCoord,yCoord2
1840    integer :: numLev ! This will be 4 for soil moisture, and 1 for all other variables.
1841    character (len=64) :: modelConfigType ! This is character verion (long name) for the io_config_outputs
1842    real :: scaleFactorReciprocal
1843 ! Establish macro variables to hlep guide this subroutine.
1844 #ifdef MPP_LAND
1845    mppFlag = 1
1846 #else
1847    mppFlag = 0
1848 #endif
1850 #ifdef HYDRO_D
1851    diagFlag = 1
1852 #else
1853    diagFlag = 0
1854 #endif
1856    ! If we are running over MPI, determine which processor number we are on.
1857    ! If not MPI, then default to 0, which is the I/O ID.
1858    if(mppFlag .eq. 1) then
1859 #ifdef MPP_LAND
1860       call MPI_COMM_RANK( HYDRO_COMM_WORLD, myId, ierr )
1861       call nwmCheck(diagFlag,ierr,'ERROR: Unable to determine MPI process ID.')
1862 #endif
1863    else
1864       myId = 0
1865    endif
1867    ! Some sanity checking here.
1868    if(nlst(domainId)%RTOUT_DOMAIN .eq. 0) then
1869       ! No output requested here. Return to the parent calling program.
1870       return
1871    endif
1873    ! Initialize NWM dictionary derived type containing all the necessary metadat
1874    ! for the output file.
1875    call initRtDomainDict(fileMeta,myId,diagFlag)
1877    if(nlst(domainId)%io_config_outputs .eq. 0) then
1878       ! All
1879       fileMeta%outFlag(:) = [1,1,1,1,1]
1880    else if(nlst(domainId)%io_config_outputs .eq. 1) then
1881       ! Analysis and Assimilation
1882       fileMeta%outFlag(:) = [1,1,0,0,0]
1883    else if(nlst(domainId)%io_config_outputs .eq. 2) then
1884       ! Short Range
1885       fileMeta%outFlag(:) = [1,1,0,0,0]
1886    else if(nlst(domainId)%io_config_outputs .eq. 3) then
1887       ! Medium Range
1888       fileMeta%outFlag(:) = [1,1,0,0,0]
1889    else if(nlst(domainId)%io_config_outputs .eq. 4) then
1890       ! Long Range
1891       fileMeta%outFlag(:) = [1,1,0,0,0]
1892    else if(nlst(domainId)%io_config_outputs .eq. 5) then
1893       ! Retrospective
1894       fileMeta%outFlag(:) = [1,1,0,0,0]
1895    else if(nlst(domainId)%io_config_outputs .eq. 6) then
1896       ! Diagnostics
1897       fileMeta%outFlag(:) = [1,1,0,0,0]
1898    else
1899       call nwmCheck(diagFlag,1,'ERROR: Invalid IOC flag provided by namelist file.')
1900    endif
1902    ! call the GetModelConfigType function
1903    modelConfigType = GetModelConfigType(nlst(1)%io_config_outputs)
1905    ! Calculate datetime information.
1906    ! First compose strings of EPOCH and simulation start date.
1907    epochDate = trim("1970-01-01 00:00")
1908    startDate = trim(nlst(domainId)%startdate(1:4)//"-"//&
1909                     nlst(domainId)%startdate(6:7)//&
1910                     &"-"//nlst(domainId)%startdate(9:10)//" "//&
1911                     nlst(domainId)%startdate(12:13)//":"//&
1912                     nlst(domainId)%startdate(15:16))
1913    ! Second, utilize NoahMP date utilities to calculate the number of minutes
1914    ! from EPOCH to the beginning of the model simulation.
1915    call geth_idts(startDate,epochDate,minSinceEpoch1)
1916    ! Third, calculate the number of minutes since the beginning of the
1917    ! simulation.
1918    minSinceSim = int(nlst(1)%out_dt*(rt_domain(1)%out_counts-1))
1919    ! Fourth, calculate the total number of minutes from EPOCH to the current
1920    ! model time step.
1921    minSinceEpoch = minSinceEpoch1 + minSinceSim
1922    ! Fifth, compose global attribute time strings that will be used.
1923    validTime = trim(nlst(domainId)%olddate(1:4)//'-'//&
1924                     nlst(domainId)%olddate(6:7)//'-'//&
1925                     nlst(domainId)%olddate(9:10)//'_'//&
1926                     nlst(domainId)%olddate(12:13)//':'//&
1927                     nlst(domainId)%olddate(15:16)//&
1928                     &':00')
1929    initTime = trim(nlst(domainId)%startdate(1:4)//'-'//&
1930                   nlst(domainId)%startdate(6:7)//'-'//&
1931                   nlst(domainId)%startdate(9:10)//'_'//&
1932                   nlst(domainId)%startdate(12:13)//':'//&
1933                   nlst(domainId)%startdate(15:16)//&
1934                   &':00')
1935    ! Replace default values in the dictionary.
1936    fileMeta%initTime = trim(initTime)
1937    fileMeta%validTime = trim(validTime)
1939    ! calculate the minimum and maximum time
1940    fileMeta%timeValidMin = minSinceEpoch1 + nlst(1)%out_dt
1941    fileMeta%timeValidMax = minSinceEpoch1 + int(nlst(1)%khour * 60/nlst(1)%out_dt) * nlst(1)%out_dt
1943    ! calculate total_valid_time
1944    if(nlst(domainId)%io_config_outputs .ne. 3 .and. nlst(domainId)%io_config_outputs .ne. 5) then
1945        fileMeta%totalValidTime = int(nlst(1)%khour * 60 / nlst(1)%out_dt)  ! # number of valid time (#of output files)
1946    else
1947        fileMeta%totalValidTime = int(nlst(1)%khour * 60 / nlst(1)%out_dt / 3)  ! # number of valid time (#of output files)
1948    endif
1950    ! Create output filename
1951    write(output_flnm, '(A12,".RTOUT_DOMAIN",I1)') nlst(domainId)%olddate(1:4)//&
1952                        nlst(domainId)%olddate(6:7)//&
1953                        nlst(domainId)%olddate(9:10)//&
1954                        nlst(domainId)%olddate(12:13)//&
1955                        nlst(domainId)%olddate(15:16), igrid
1957    if(myId .eq. 0) then
1958       ! Create output NetCDF file for writing.
1959       iret = nf90_create(trim(output_flnm),cmode=NF90_NETCDF4,ncid = ftn)
1960       call nwmCheck(diagFlag,iret,'ERROR: Unable to create RT_DOMAIN NetCDF file.')
1962       ! Write global attributes
1963       iret = nf90_put_att(ftn,NF90_GLOBAL,'TITLE',trim(fileMeta%title))
1964       call nwmCheck(diagFlag,iret,'ERROR: Unable to create TITLE attribute')
1965       iret = nf90_put_att(ftn,NF90_GLOBAL,"compiler_version",compiler_version())
1966       call nwmCheck(diagFlag,iret,'ERROR: Unable to create compiler_version attribute')
1967       iret = nf90_put_att(ftn,NF90_GLOBAL,'model_initialization_time',trim(fileMeta%initTime))
1968       call nwmCheck(diagFlag,iret,'ERROR: Unable to place model init time attribute into RT_DOMAIN file.')
1969       iret = nf90_put_att(ftn,NF90_GLOBAL,'model_output_valid_time',trim(fileMeta%validTime))
1970       call nwmCheck(diagFlag,iret,'ERROR: Unable to place model output time attribute into RT_DOMAIN file.')
1971       iret = nf90_put_att(ftn,NF90_GLOBAL,'model_total_valid_times',fileMeta%totalValidTime)
1972       call nwmCheck(diagFlag,iret,'ERROR: Unable to place model total valid times attribute into RT_DOMAIN file.')
1973       iret = nf90_put_att(ftn,NF90_GLOBAL,'Conventions',trim(fileMeta%conventions))
1974       call nwmCheck(diagFlag,iret,'ERROR: Unable to place CF conventions attribute into RT_DOMAIN file.')
1975       iret = nf90_put_att(ftn,NF90_GLOBAL,"code_version",trim(get_code_version()))
1976       call nwmCheck(diagFlag,iret,'ERROR: Unable to create code_version attribute')
1977 #ifdef NWM_META
1978       iret = nf90_put_att(ftn,NF90_GLOBAL,"NWM_version_number",trim(get_nwm_version()))
1979       call nwmCheck(diagFlag,iret,'ERROR: Unable to create NWM_version_number attribute')
1980 #endif
1981       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_output_type",trim(fileMeta%modelOutputType))
1982       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_output_type attribute')
1983       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_configuration",modelConfigType)
1984       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_configuration attribute')
1985       iret = nf90_put_att(ftn,NF90_GLOBAL,"proj4",trim(fileMeta%proj4))
1986       call nwmCheck(diagFlag,iret,'ERROR: Unable to create proj4 attribute')
1987       iret = nf90_put_att(ftn,NF90_GLOBAL,"GDAL_DataType","Generic")
1988       call nwmCheck(diagFlag,iret,'ERROR: Unable to create GDAL_DataType attribute')
1990       ! Create dimensions
1991       iret = nf90_def_dim(ftn,'time',NF90_UNLIMITED,dimId(1))
1992       call nwmCheck(diagFlag,iret,'ERROR: Unable to define time dimension')
1993       iret = nf90_def_dim(ftn,'x',RT_DOMAIN(domainId)%g_ixrt,dimId(2))
1994       call nwmCheck(diagFlag,iret,'ERROR: Unable to define x dimension')
1995       iret = nf90_def_dim(ftn,'y',RT_DOMAIN(domainId)%g_jxrt,dimId(3))
1996       call nwmCheck(diagFlag,iret,'ERROR: Unable to define y dimension')
1997       iret = nf90_def_dim(ftn,'reference_time',1,dimId(4))
1998       call nwmCheck(diagFlag,iret,'ERROR: Unable to define reference_time dimension')
1999       ! Only create soil layers stag dimension if we are outputting to the soil moisture grid.
2000       ! Otherwise this creates unused dimensions.
2001       if (fileMeta%outFlag(5) .eq. 1) then
2002       iret = nf90_def_dim(ftn,'soil_layers_stag',fileMeta%numSoilLayers,dimId(5))
2003       call nwmCheck(diagFlag,iret,'ERROR: Unable to define soil_layers_stag dimension')
2004       endif
2006       ! Create and populate reference_time and time variables.
2007       iret = nf90_def_var(ftn,"time",nf90_int,dimId(1),timeId)
2008       call nwmCheck(diagFlag,iret,'ERROR: Unable to create time variable')
2009       iret = nf90_put_att(ftn,timeId,'long_name',trim(fileMeta%timeLName))
2010       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into time variable')
2011       iret = nf90_put_att(ftn,timeId,'standard_name',trim(fileMeta%timeStName))
2012       call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into time variable')
2013       iret = nf90_put_att(ftn,timeId,'units',trim(fileMeta%timeUnits))
2014       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into time variable')
2015       iret = nf90_put_att(ftn,timeId,'valid_min',fileMeta%timeValidMin)
2016       call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_min attribute into time variable')
2017       iret = nf90_put_att(ftn,timeId,'valid_max',fileMeta%timeValidMax)
2018       call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_max attribute into time variable')
2019       iret = nf90_def_var(ftn,"reference_time",nf90_int,dimId(4),refTimeId)
2020       call nwmCheck(diagFlag,iret,'ERROR: Unable to create reference_time variable')
2021       iret = nf90_put_att(ftn,refTimeId,'long_name',trim(fileMeta%rTimeLName))
2022       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into reference_time variable')
2023       iret = nf90_put_att(ftn,refTimeId,'standard_name',trim(fileMeta%rTimeStName))
2024       call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into reference_time variable')
2025       iret = nf90_put_att(ftn,refTimeId,'units',trim(fileMeta%rTimeUnits))
2026       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into reference_time variable')
2028       ! Create x/y coordinate variables
2029       iret = nf90_def_var(ftn,'x',nf90_double,dimId(2),xVarId)
2030       call nwmCheck(diagFlag,iret,'ERROR: Unable to create x coordinate variable')
2031       do iTmp=1,fileMeta%nxRealAtts
2032          iret = nf90_put_att(ftn,xVarId,trim(fileMeta%xFloatAttNames(iTmp)),&
2033                              fileMeta%xRealAttVals(iTmp,1:fileMeta%xRealAttLen(iTmp)))
2034          call nwmCheck(diagFlag,iret,'ERROR: Unable to place x floating point attributes into RTDOMAIN file.')
2035       end do
2036       do iTmp=1,fileMeta%nxCharAtts
2037          iret = nf90_put_att(ftn,xVarId,trim(fileMeta%xCharAttNames(iTmp)),trim(fileMeta%xCharAttVals(iTmp)))
2038          call nwmCheck(diagFlag,iret,'ERROR: Unable to place x string point attributes into RTDOMAIN file.')
2039       end do
2040       iret = nf90_def_var(ftn,'y',nf90_double,dimId(3),yVarId)
2041       call nwmCheck(diagFlag,iret,'ERROR: Unable to create y coordinate variable')
2042       do iTmp=1,fileMeta%nyRealAtts
2043          iret = nf90_put_att(ftn,yVarId,trim(fileMeta%yFloatAttNames(iTmp)),&
2044                              fileMeta%yRealAttVals(iTmp,1:fileMeta%yRealAttLen(iTmp)))
2045          call nwmCheck(diagFlag,iret,'ERROR: Unable to place y floating point attributes into RTDOMAIN file.')
2046       end do
2047       do iTmp=1,fileMeta%nyCharAtts
2048          iret = nf90_put_att(ftn,yVarId,trim(fileMeta%yCharAttNames(iTmp)),trim(fileMeta%yCharAttVals(iTmp)))
2049          call nwmCheck(diagFlag,iret,'ERROR: Unable to place y string point attributes into RTDOMAIN file.')
2050       end do
2052       ! Define compression for meta-variables only if io_form_outputs is set to 1.
2053       if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
2054          iret = nf90_def_var_deflate(ftn,timeId,0,1,2)
2055          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for time.')
2056          iret = nf90_def_var_deflate(ftn,refTimeId,0,1,2)
2057          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for reference_time.')
2058          iret = nf90_def_var_deflate(ftn,xVarId,0,1,2)
2059          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for x.')
2060          iret = nf90_def_var_deflate(ftn,yVarId,0,1,2)
2061          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for y.')
2062       endif
2064       ! Translate crs variable info from land spatial metadata file to output
2065       ! file.
2066       iret = nf90_def_var(ftn,'crs',nf90_char,varid=coordVarId)
2067       call nwmCheck(diagFlag,iret,'ERROR: Unable to create crs variable in RT_DOMAIN file.')
2068       do iTmp=1,fileMeta%nCrsRealAtts
2069          iret = nf90_put_att(ftn,coordVarId,trim(fileMeta%crsFloatAttNames(iTmp)),&
2070                              fileMeta%crsRealAttVals(iTmp,1:fileMeta%crsRealAttLen(iTmp)))
2071          call nwmCheck(diagFlag,iret,'ERROR: Unable to place crs floating point attributes into RT_DOMAIN file.')
2072       end do
2073       do iTmp=1,fileMeta%nCrsCharAtts
2074          iret = nf90_put_att(ftn,coordVarId,trim(fileMeta%crsCharAttNames(iTmp)),trim(fileMeta%crsCharAttVals(iTmp)))
2075          call nwmCheck(diagFlag,iret,'ERROR: Unable to place crs string point attributes into RT_DOMAIN file.')
2076       end do
2078       ! Loop through all possible variables and create them, along with their
2079       ! metadata attributes.
2080       do iTmp=1,fileMeta%numVars
2081          if(fileMeta%outFlag(iTmp) .eq. 1) then
2082             if(iTmp .eq. 5) then
2083                ! Soil Moisture
2084                if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
2085                   iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_int,(/dimId(2),dimId(5),dimId(3),dimId(1)/),varId)
2086                else
2087                   iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_float,(/dimId(2),dimId(5),dimId(3),dimId(1)/),varId)
2088                endif
2089             else
2090                ! All other variables
2091                if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
2092                   iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_int,(/dimId(2),dimId(3),dimId(1)/),varId)
2093                else
2094                   iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_float,(/dimId(2),dimId(3),dimId(1)/),varId)
2095                endif
2096             endif
2097             call nwmCheck(diagFlag,iret,"ERROR: Unable to create variable: "//trim(fileMeta%varNames(iTmp)))
2099             ! Extract valid range into a 1D array for placement.
2100             varRange(1) = fileMeta%validMinComp(iTmp)
2101             varRange(2) = fileMeta%validMaxComp(iTmp)
2102             varRangeReal(1) = real(fileMeta%validMinDbl(iTmp))
2103             varRangeReal(2) = real(fileMeta%validMaxDbl(iTmp))
2105             ! Establish a compression level for the variables. For now we are using a
2106             ! compression level of 2. In addition, we are choosing to turn the shuffle
2107             ! filter off for now. Kelley Eicher did some testing with this and
2108             ! determined that the benefit wasn't worth the extra time spent writing output.
2109             ! Only compress if io_form_outputs is set to 1.
2110             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
2111                iret = nf90_def_var_deflate(ftn,varId,0,1,2)
2112                call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression for: '//trim(fileMeta%varNames(iTmp)))
2113             endif
2115             ! Create variable attributes
2116             iret = nf90_put_att(ftn,varId,'long_name',trim(fileMeta%longName(iTmp)))
2117             call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into variable '//trim(fileMeta%varNames(iTmp)))
2118             iret = nf90_put_att(ftn,varId,'units',trim(fileMeta%units(iTmp)))
2119             call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into variable '//trim(fileMeta%varNames(iTmp)))
2120             iret = nf90_put_att(ftn,varId,'grid_mapping','crs')
2121             call nwmCheck(diagFlag,iret,'ERROR: Unable to place grid_mapping attribute into variable: '//trim(fileMeta%varNames(iTmp)))
2122             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
2123                iret = nf90_put_att(ftn,varId,'_FillValue',fileMeta%fillComp(iTmp))
2124                call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
2125                iret = nf90_put_att(ftn,varId,'missing_value',fileMeta%missingComp(iTmp))
2126                call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
2127                iret = nf90_put_att(ftn,varId,'scale_factor',fileMeta%scaleFactor(iTmp))
2128                call nwmCheck(diagFlag,iret,'ERROR: Unable to place scale_factor attribute into variable '//trim(fileMeta%varNames(iTmp)))
2129                iret = nf90_put_att(ftn,varId,'add_offset',fileMeta%addOffset(iTmp))
2130                call nwmCheck(diagFlag,iret,'ERROR: Unable to place add_offset attribute into variable '//trim(fileMeta%varNames(iTmp)))
2131                iret = nf90_put_att(ftn,varId,'valid_range',varRange)
2132                call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
2133             else
2134                iret = nf90_put_att(ftn,varId,'_FillValue',fileMeta%fillReal(iTmp))
2135                call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
2136                iret = nf90_put_att(ftn,varId,'missing_value',fileMeta%missingReal(iTmp))
2137                call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
2138                iret = nf90_put_att(ftn,varId,'valid_range',varRangeReal)
2139                call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
2140             endif
2141             ! Place necessary geospatial attributes into the variable.
2142             do iTmp2=1,fileMeta%nCrsCharAtts
2143                if(trim(fileMeta%crsCharAttNames(iTmp2)) .eq. 'esri_pe_string') then
2144                   iret = nf90_put_att(ftn,varId,trim(fileMeta%crsCharAttNames(iTmp2)),trim(fileMeta%crsCharAttVals(iTmp2)))
2145                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place esri_pe_string attribute into '//trim(fileMeta%varNames(iTmp)))
2146                endif
2147             end do
2148          endif
2149       end do ! end looping through variable output list.
2151       ! Remove NetCDF file from definition mode.
2152       iret = nf90_enddef(ftn)
2153       call nwmCheck(diagFlag,iret,'ERROR: Unable to take RT_DOMAIN file out of definition mode')
2155       ! Read in coordinates from FullDom file. These will be placed into the
2156       ! output file coordinate variables.
2157       allocate(xCoord(RT_DOMAIN(domainId)%g_ixrt))
2158       allocate(yCoord(RT_DOMAIN(domainId)%g_jxrt))
2159       allocate(yCoord2(RT_DOMAIN(domainId)%g_jxrt))
2160       iret = nf90_open(trim(nlst(domainId)%geo_finegrid_flnm),NF90_NOWRITE,ncid=ftnGeo)
2161       call nwmCheck(diagFlag,iret,'ERROR: Unable to open FullDom file')
2162       iret = nf90_inq_varid(ftnGeo,'x',geoXVarId)
2163       call nwmCheck(diagFlag,iret,'ERROR: Unable to find x coordinate in FullDom file')
2164       iret = nf90_get_var(ftnGeo,geoXVarId,xCoord)
2165       call nwmCheck(diagFlag,iret,'ERROR: Unable to extract x coordinate from FullDom file')
2166       iret = nf90_inq_varid(ftnGeo,'y',geoYVarId)
2167       call nwmCheck(diagFlag,iret,'ERROR: Unable to find y coordinate in FullDom file')
2168       iret = nf90_get_var(ftnGeo,geoYVarId,yCoord)
2169       call nwmCheck(diagFlag,iret,'ERROR: Unable to extract y coordinate from FullDom file')
2170       iret = nf90_close(ftnGeo)
2171       call nwmCheck(diagFlag,iret,'ERROR: Unable to close geoGrid file.')
2173       ! Reverse Y coordinates. They are read in reverse.
2174       jTmp2 = 0
2175       do jTmp = RT_DOMAIN(domainId)%g_jxrt,1,-1
2176          jTmp2 = jTmp2 + 1
2177          yCoord2(jTmp2) = yCoord(jTmp)
2178       end do
2179       ! Place coordinate values into output file
2180       iret = nf90_inq_varid(ftn,'x',varId)
2181       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate x coordinate variable.')
2182       iret = nf90_put_var(ftn,varId,xCoord)
2183       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into x coordinate variable')
2184       iret = nf90_inq_varid(ftn,'y',varId)
2185       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate y coordinate variable')
2186       iret = nf90_put_var(ftn,varId,yCoord2)
2187       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into y coordinate variable')
2188       deallocate(xCoord)
2189       deallocate(yCoord)
2190       deallocate(yCoord2)
2192       ! Place time values into time variables.
2193       iret = nf90_inq_varid(ftn,'time',varId)
2194       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate time variable')
2195       iret = nf90_put_var(ftn,varId,minSinceEpoch)
2196       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into time variable')
2197       iret = nf90_inq_varid(ftn,'reference_time',varId)
2198       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate reference_time variable')
2199       iret = nf90_put_var(ftn,varId,minSinceEpoch1)
2200       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into reference_time variable')
2202    endif ! End if statement if on I/O ID
2204    ! Loop through each variable, collect local routing grid variables into a
2205    ! global routing grid and output through the master I/O process.
2206    do iTmp2=1,fileMeta%numVars
2208       ! Specify the number of vertical levels we are dealing with
2209       if(iTmp2 .eq. 5) then
2210          numLev = 4
2211       else
2212          numLev = 1
2213       endif
2215       scaleFactorReciprocal = 1/fileMeta%scaleFactor(iTmp2)
2217       if(fileMeta%outFlag(iTmp2) .eq. 1) then
2218          !Allocate memory necessary
2219          if(myId .eq. 0) then
2220             allocate(globalOutComp(RT_DOMAIN(domainId)%g_ixrt,numLev,RT_DOMAIN(domainId)%g_jxrt))
2221             allocate(globalOutReal(RT_DOMAIN(domainId)%g_ixrt,numLev,RT_DOMAIN(domainId)%g_jxrt))
2222          else
2223             allocate(globalOutComp(1,1,1))
2224             allocate(globalOutReal(1,1,1))
2225          endif
2226          ! Allocate local memory
2227          allocate(localCompTmp(RT_DOMAIN(domainId)%ixrt,RT_DOMAIN(domainId)%jxrt))
2228          allocate(localRealTmp(RT_DOMAIN(domainId)%ixrt,RT_DOMAIN(domainId)%jxrt))
2229          ! Initialize arrays to prescribed NDV value.
2230          globalOutComp = fileMeta%fillComp(iTmp2)
2231          globalOutReal = fileMeta%fillReal(iTmp2)
2233          ! Loop through the number of levels.
2234          do zTmp=1,numLev
2235             ! Initialize arrays to prescribed NDV value.
2236             localCompTmp = fileMeta%fillComp(iTmp2)
2237             localRealTmp = fileMeta%fillReal(iTmp2)
2239             ! Loop through output array and convert floating point values to
2240             ! integers via scale_factor/add_offset.
2241             do iTmp = 1,RT_DOMAIN(domainId)%ixrt
2242                do jTmp = 1,RT_DOMAIN(domainId)%jxrt
2243                   if(iTmp2 .eq. 1) then
2244                      varRealTmp = rt_domain(domainId)%subsurface%properties%zwattablrt(iTmp,jTmp)
2245                   else if(iTmp2 .eq. 2) then
2246                      varRealTmp = RT_DOMAIN(domainId)%overland%control%surface_water_head_routing(iTmp,jTmp)
2247                   else if(iTmp2 .eq. 3) then
2248                      varRealTmp = RT_DOMAIN(domainId)%QSTRMVOLRT_ACC(iTmp,jTmp)
2249                   else if(iTmp2 .eq. 4) then
2250                      varRealTmp = RT_DOMAIN(domainId)%overland%control%boundary_flux(iTmp,jTmp)
2251                   else if(iTmp2 .eq. 5) then
2252                      varRealTmp = rt_domain(domainId)%subsurface%grid_transform%smcrt(iTmp,jTmp,zTmp)
2253                   endif
2255                   ! Run a quick gross check on values to ensure they aren't outside our
2256                   ! defined limits.
2257                   !if(varRealTmp .lt. fileMeta%validMinDbl(iTmp2)) then
2258                   !   varRealTmp = fileMeta%fillReal(iTmp2)
2259                   !endif
2260                   !if(varRealTmp .gt. fileMeta%validMaxDbl(iTmp2)) then
2261                   !   varRealTmp = fileMeta%fillReal(iTmp2)
2262                   !endif
2263                   if(varRealTmp .ne. varRealTmp) then
2264                      varRealTmp = fileMeta%fillReal(iTmp2)
2265                   endif
2266                   ! If we are on time 0, make sure we don't need to fill in the
2267                   ! grid with NDV values.
2268                   if(minSinceSim .eq. 0 .and. fileMeta%timeZeroFlag(iTmp2) .eq. 0) then
2269                      localCompTmp(iTmp,jTmp) = fileMeta%fillComp(iTmp2)
2270                      localRealTmp(iTmp,jTmp) = fileMeta%fillReal(iTmp2)
2271                   else
2272                      if(varRealTmp .eq. fileMeta%modelNdv) then
2273                         localCompTmp(iTmp,jTmp) = INT(fileMeta%fillComp(iTmp2))
2274                         localRealTmp(iTmp,jTmp) = fileMeta%fillReal(iTmp2)
2275                      else
2276                         localCompTmp(iTmp,jTmp) = NINT((varRealTmp-fileMeta%addOffset(iTmp2))*scaleFactorReciprocal)
2277                         localRealTmp(iTmp,jTmp) = varRealTmp
2278                      endif
2279                   endif
2280                end do
2281             end do
2282             ! Collect local integer arrays into the global integer grid to be
2283             ! written out.
2284             if(mppFlag .eq. 1) then
2285 #ifdef MPP_LAND
2286                call write_IO_rt_int(localCompTmp,globalOutComp(:,zTmp,:))
2287                call write_IO_rt_real(localRealTmp,globalOutReal(:,zTmp,:))
2288 #endif
2289             else
2290                globalOutComp(:,zTmp,:) = localCompTmp
2291                globalOutReal(:,zTmp,:) = localRealTmp
2292             endif
2293          end do ! End looping through levels
2295          ! Write output to NetCDF file.
2296          if(myId .eq. 0) then
2297             iret = nf90_inq_varid(ftn,trim(fileMeta%varNames(iTmp2)),varId)
2298             call nwmCheck(diagFlag,iret,'ERROR: Unable to find variable ID for var: '//trim(fileMeta%varNames(iTmp2)))
2299             if(numLev .eq. 1) then
2300                if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
2301                   iret = nf90_put_var(ftn,varId,globalOutComp,(/1,1,1/),(/RT_DOMAIN(domainId)%g_ixrt,RT_DOMAIN(domainId)%g_jxrt,1/))
2302                else
2303                   iret = nf90_put_var(ftn,varId,globalOutReal,(/1,1,1/),(/RT_DOMAIN(domainId)%g_ixrt,RT_DOMAIN(domainId)%g_jxrt,1/))
2304                endif
2305             else
2306                if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
2307                   iret = nf90_put_var(ftn,varId,globalOutComp,(/1,1,1,1/),(/RT_DOMAIN(domainId)%g_ixrt,numLev,RT_DOMAIN(domainId)%g_jxrt,1/))
2308                else
2309                   iret = nf90_put_var(ftn,varId,globalOutReal,(/1,1,1,1/),(/RT_DOMAIN(domainId)%g_ixrt,numLev,RT_DOMAIN(domainId)%g_jxrt,1/))
2310                endif
2311             endif
2312             call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into output variable: '//trim(fileMeta%varNames(iTmp2)))
2313          endif
2315          ! Deallocate memory for this variable.
2316          deallocate(globalOutComp)
2317          deallocate(localCompTmp)
2318          deallocate(globalOutReal)
2319          deallocate(localRealTmp)
2320       endif
2321    end do
2323    if(myId .eq. 0) then
2324       ! Close the output file
2325       iret = nf90_close(ftn)
2326       call nwmCheck(diagFlag,iret,'ERROR: Unable to close RT_DOMAIN file.')
2327    endif
2330 end subroutine output_rt_NWM
2332 !==============================================================================
2333 ! Program Name: output_lakes_NWM
2334 ! Author(s)/Contact(s): Logan R Karsten <karsten><ucar><edu>
2335 ! Abstract: Output routine for lake points for the National Water Model.
2336 ! History Log:
2337 ! 3/6/17 -Created, LRK.
2338 ! Usage:
2339 ! Parameters: None.
2340 ! Input Files: None.
2341 ! Output Files: None.
2342 ! Condition codes: None.
2344 ! User controllable options: None.
2346 subroutine output_lakes_NWM(domainId,iGrid)
2347    use module_rt_data, only: rt_domain
2348    use config_base, only: nlst
2349    use Module_Date_utilities_rt, only: geth_newdate, geth_idts
2350    use module_NWM_io_dict
2351    use netcdf
2352 #ifdef MPP_LAND
2353      use module_mpp_land
2354 #endif
2355    implicit none
2357    integer, intent(in) :: domainId
2358    integer, intent(in) :: iGrid
2360    ! Derived types.
2361    type(lakeMeta) :: fileMeta
2363    ! Local variables
2364    integer :: mppFlag, diagFlag
2365    integer :: minSinceSim ! Number of minutes since beginning of simulation.
2366    integer :: minSinceEpoch1 ! Number of minutes from EPOCH to the beginning of the model simulation.
2367    integer :: minSinceEpoch ! Number of minutes from EPOCH to the current model valid time.
2368    character(len=16) :: epochDate ! EPOCH represented as a string.
2369    character(len=16) :: startDate ! Start of model simulation, represented as a string.
2370    character(len=256) :: output_flnm ! CHRTOUT_DOMAIN filename
2371    integer :: iret ! NetCDF return statuses
2372    integer :: ftn ! NetCDF file handle
2373    character(len=256) :: validTime ! Global attribute time string
2374    character(len=256) :: initTime ! Global attribute time string
2375    integer :: dimId(4) ! Dimension ID values created during NetCDF created.
2376    integer :: varId ! Variable ID value created as NetCDF variables are created and populated.
2377    integer :: timeId ! Dimension ID for the time dimension.
2378    integer :: refTimeId ! Dimension ID for the reference time dimension.
2379    integer :: coordVarId ! Variable to hold crs
2380    integer :: featureVarId ! feature_id NetCDF variable ID
2381    integer :: reservoirTypeVarId ! reservoir_type netCDF variable ID
2382    integer :: reservoirAssimilatedValueVarId ! reservoir_assimilated_value netCDF variable ID
2383    integer :: reservoirAssimilatedSourceFileVarId ! reservoir_assimilated_source_file netCDF variable ID
2384    integer :: latVarId, lonVarId ! lat/lon NetCDF variable ID values
2385    integer :: elevVarId ! elevation NetCDF variable ID
2386    integer :: varRange(2) ! Local storage of valid min/max values
2387    real :: varRangeReal(2) ! Local storage of valid min/max values
2388    integer :: gSize ! Global size of lake out arrays
2389    integer :: iTmp
2390    integer :: ftnRt,indVarId,indTmp ! For the feature_id sorting process.
2391    integer :: ierr, myId ! MPI return status, process ID
2392    integer :: ascFlag ! Flag for resorting timeseries output by feature_id.
2393    ! Allocatable arrays to hold output variables.
2394    real, allocatable, dimension(:) :: g_lakeLat,g_lakeLon,g_lakeElev
2395    real, allocatable, dimension(:) :: g_lakeInflow,g_lakeOutflow
2396    real, allocatable, dimension(:) :: g_lakeType
2397    real, allocatable, dimension(:) :: g_lake_assimilated_value
2398    character(len=256), allocatable, dimension(:) :: g_lake_assimilated_source_file
2399    integer(kind=int64), allocatable, dimension(:) :: g_lakeid
2400    real, allocatable, dimension(:) :: g_lakeLatOut,g_lakeLonOut,g_lakeElevOut
2401    real, allocatable, dimension(:) :: g_lakeInflowOut,g_lakeOutflowOut
2402    integer(kind=int64), allocatable, dimension(:) :: g_lakeTypeOut, g_lakeidOut
2403    real, allocatable, dimension(:) :: g_lake_assimilated_valueOut
2404    character(len=256), allocatable, dimension(:) :: g_lake_assimilated_source_fileOut
2405    real, allocatable, dimension(:,:) :: varOutReal   ! Array holding output variables in real format
2406    integer, allocatable, dimension(:) :: varOutInt ! Array holding output variables after
2407                                                      ! scale_factor/add_offset
2408                                                      ! have been applied.
2409    integer, allocatable, dimension(:) :: chIndArray ! Array of index values for
2410    character (len=64) :: modelConfigType ! This is character verion (long name) for the io_config_outputs
2412    !each channel point. feature_id will need to be sorted in ascending order once
2413    !data is collected into the global array. From there, the index values are
2414    !re-sorted, and used to re-sort output arrays.
2416    ! Initialize the ascFlag.
2417    ascFlag = 1
2419    ! Establish macro variables to hlep guide this subroutine.
2420 #ifdef MPP_LAND
2421    mppFlag = 1
2422 #else
2423    mppFlag = 0
2424 #endif
2426 #ifdef HYDRO_D
2427    diagFlag = 1
2428 #else
2429    diagFlag = 0
2430 #endif
2432    ! If we are running over MPI, determine which processor number we are on.
2433    ! If not MPI, then default to 0, which is the I/O ID.
2434    if(mppFlag .eq. 1) then
2435 #ifdef MPP_LAND
2436       call MPI_COMM_RANK( HYDRO_COMM_WORLD, myId, ierr )
2437       call nwmCheck(diagFlag,ierr,'ERROR: Unable to determine MPI process ID.')
2438 #endif
2439    else
2440       myId = 0
2441    endif
2443    ! Some sanity checking here.
2444    if(nlst(domainId)%outlake .eq. 0) then
2445       ! No output requested here. Return to the parent calling program.
2446       return
2447    endif
2449    ! Initialize NWM dictionary derived type containing all the necessary metadat
2450    ! for the output file.
2451    call initLakeDict(fileMeta,myId,diagFlag)
2453    if(nlst(1)%io_config_outputs .eq. 0) then
2454       ! All
2455       fileMeta%outFlag(:) = [1,1]
2456    else if(nlst(1)%io_config_outputs .eq. 1) then
2457       ! Analysis and Assimilation
2458       fileMeta%outFlag(:) = [1,1]
2459    else if(nlst(1)%io_config_outputs .eq. 2) then
2460       ! Short Range
2461       fileMeta%outFlag(:) = [1,1]
2462    else if(nlst(1)%io_config_outputs .eq. 3) then
2463       ! Medium Range
2464       fileMeta%outFlag(:) = [1,1]
2465    else if(nlst(1)%io_config_outputs .eq. 4) then
2466       ! Long Range
2467       fileMeta%outFlag(:) = [1,1]
2468    else if(nlst(1)%io_config_outputs .eq. 5) then
2469       ! Retrospective
2470       fileMeta%outFlag(:) = [1,1]
2471    else if(nlst(1)%io_config_outputs .eq. 6) then
2472       ! Diagnostics
2473       fileMeta%outFlag(:) = [1,1]
2474    else
2475       call nwmCheck(diagFlag,1,'ERROR: Invalid IOC flag provided by namelist file.')
2476    endif
2478    ! call the GetModelConfigType function
2479    modelConfigType = GetModelConfigType(nlst(1)%io_config_outputs)
2481    ! First step is to collect and assemble all data that will be written to the
2482    ! NetCDF file. If we are not using MPI, we bypass the collection step through
2483    ! MPI.
2484    if(mppFlag .eq. 1) then
2485       gSize = rt_domain(domainId)%NLAKES
2487       allocate(g_lakeLon(gsize))
2488       allocate(g_lakeLat(gsize))
2489       allocate(g_lakeElev(gsize))
2490       allocate(g_lakeInflow(gsize))
2491       allocate(g_lakeOutflow(gsize))
2492       allocate(g_lakeType(gsize))
2493       allocate(g_lake_assimilated_value(gsize))
2494       allocate(g_lake_assimilated_source_file(gsize))
2495       allocate(g_lakeid(gsize))
2497       if(myId == 0) then
2498          allocate(g_lakeLonOut(gsize))
2499          allocate(g_lakeLatOut(gsize))
2500          allocate(g_lakeElevOut(gsize))
2501          allocate(g_lakeInflowOut(gsize))
2502          allocate(g_lakeOutflowOut(gsize))
2503          allocate(g_lakeTypeOut(gsize))
2504          allocate(g_lake_assimilated_valueOut(gsize))
2505          allocate(g_lake_assimilated_source_fileOut(gsize))
2506          allocate(g_lakeidOut(gsize))
2507          allocate(chIndArray(gsize))
2508       endif
2510       g_lakeLat = RT_DOMAIN(domainID)%LATLAKE
2511       g_lakeLon = RT_DOMAIN(domainID)%LONLAKE
2512       g_lakeElev = RT_DOMAIN(domainID)%RESHT
2513       g_lakeInflow = RT_DOMAIN(domainID)%QLAKEI
2514       g_lakeOutflow = RT_DOMAIN(domainID)%QLAKEO
2515       g_lakeid = RT_DOMAIN(domainId)%LAKEIDM
2516       g_lakeType = RT_DOMAIN(domainID)%final_reservoir_type
2517       g_lake_assimilated_value = RT_DOMAIN(domainID)%reservoir_assimilated_value
2518       g_lake_assimilated_source_file = RT_DOMAIN(domainID)%reservoir_assimilated_source_file
2520       ! Collect arrays from various processors through MPI, and
2521       ! assemble into global arrays previously allocated.
2522 #ifdef MPP_LAND
2523       call write_lake_real(g_lakeLat,RT_DOMAIN(domainId)%lake_index,gsize)
2524       call write_lake_real(g_lakeLon,RT_DOMAIN(domainId)%lake_index,gsize)
2525       call write_lake_real(g_lakeElev,RT_DOMAIN(domainId)%lake_index,gsize)
2526       call write_lake_real(g_lakeInflow,RT_DOMAIN(domainId)%lake_index,gsize)
2527       call write_lake_real(g_lakeOutflow,RT_DOMAIN(domainId)%lake_index,gsize)
2528       call write_lake_real(g_lakeType,RT_DOMAIN(domainId)%lake_index,gsize)
2529       call write_lake_real(g_lake_assimilated_value,RT_DOMAIN(domainId)%lake_index,gsize)
2530       !call write_lake_char(g_lake_assimilated_source_file,RT_DOMAIN(domainId)%lake_index,gsize)
2532 #endif
2533    else
2534       gSize = rt_domain(domainId)%NLAKES
2535       ! No MPI - single processor
2536       allocate(g_lakeLon(gsize))
2537       allocate(g_lakeLat(gsize))
2538       allocate(g_lakeElev(gsize))
2539       allocate(g_lakeInflow(gsize))
2540       allocate(g_lakeOutflow(gsize))
2541       allocate(g_lakeid(gsize))
2542       allocate(g_lakeLonOut(gsize))
2543       allocate(g_lakeLatOut(gsize))
2544       allocate(g_lakeElevOut(gsize))
2545       allocate(g_lakeInflowOut(gsize))
2546       allocate(g_lakeOutflowOut(gsize))
2547       allocate(g_lakeidOut(gsize))
2548       allocate(g_lakeTypeOut(gsize))
2549       allocate(g_lake_assimilated_valueOut(gsize))
2550       allocate(g_lake_assimilated_source_fileOut(gsize))
2551       allocate(chIndArray(gsize))
2552       g_lakeLat = RT_DOMAIN(domainID)%LATLAKE
2553       g_lakeLon = RT_DOMAIN(domainID)%LONLAKE
2554       g_lakeElev = RT_DOMAIN(domainID)%RESHT
2555       g_lakeInflow = RT_DOMAIN(domainID)%QLAKEI
2556       g_lakeOutflow = RT_DOMAIN(domainID)%QLAKEO
2557       g_lakeid = RT_DOMAIN(domainId)%LAKEIDM
2558       g_lakeType = RT_DOMAIN(domainId)%final_reservoir_type
2559       g_lake_assimilated_value = RT_DOMAIN(domainID)%reservoir_assimilated_value
2560       g_lake_assimilated_source_file = RT_DOMAIN(domainID)%reservoir_assimilated_source_file
2561    endif
2563    ! Calculate datetime information.
2564    ! First compose strings of EPOCH and simulation start date.
2565    epochDate = trim("1970-01-01 00:00")
2566    startDate = trim(nlst(domainId)%startdate(1:4)//"-"//&
2567                     nlst(domainId)%startdate(6:7)//&
2568                     &"-"//nlst(domainId)%startdate(9:10)//" "//&
2569                     nlst(domainId)%startdate(12:13)//":"//&
2570                     nlst(domainId)%startdate(15:16))
2571    ! Second, utilize NoahMP date utilities to calculate the number of minutes
2572    ! from EPOCH to the beginning of the model simulation.
2573    call geth_idts(startDate,epochDate,minSinceEpoch1)
2574    ! Third, calculate the number of minutes since the beginning of the
2575    ! simulation.
2576    minSinceSim = int(nlst(1)%out_dt*(rt_domain(1)%out_counts-1))
2577    ! Fourth, calculate the total number of minutes from EPOCH to the current
2578    ! model time step.
2579    minSinceEpoch = minSinceEpoch1 + minSinceSim
2580    ! Fifth, compose global attribute time strings that will be used.
2581    validTime = trim(nlst(domainId)%olddate(1:4)//'-'//&
2582                     nlst(domainId)%olddate(6:7)//'-'//&
2583                     nlst(domainId)%olddate(9:10)//'_'//&
2584                     nlst(domainId)%olddate(12:13)//':'//&
2585                     nlst(domainId)%olddate(15:16)//&
2586                     &':00')
2587    initTime = trim(nlst(domainId)%startdate(1:4)//'-'//&
2588                   nlst(domainId)%startdate(6:7)//'-'//&
2589                   nlst(domainId)%startdate(9:10)//'_'//&
2590                   nlst(domainId)%startdate(12:13)//':'//&
2591                   nlst(domainId)%startdate(15:16)//&
2592                   &':00')
2593    ! Replace default values in the dictionary.
2594    fileMeta%initTime = trim(initTime)
2595    fileMeta%validTime = trim(validTime)
2597    ! calculate the minimum and maximum time
2598    fileMeta%timeValidMin = minSinceEpoch1 + nlst(1)%out_dt
2599    fileMeta%timeValidMax = minSinceEpoch1 + int(nlst(1)%khour * 60/nlst(1)%out_dt) * nlst(1)%out_dt
2601    ! calculate total_valid_time
2602    fileMeta%totalValidTime = int(nlst(1)%khour * 60 / nlst(1)%out_dt)  ! # number of valid time (#of output files)
2604    ! Compose output file name.
2605    write(output_flnm, '(A12,".LAKEOUT_DOMAIN",I1)')nlst(domainId)%olddate(1:4)//&
2606          nlst(domainId)%olddate(6:7)//nlst(domainId)%olddate(9:10)//&
2607          nlst(domainId)%olddate(12:13)//nlst(domainId)%olddate(15:16),nlst(domainId)%igrid
2609    ! Only run NetCDF library calls to output data if we are on the master
2610    ! processor.
2611    if(myId .eq. 0) then
2612       ! Read in index values from Routelink that will be used to sort output
2613       ! variables by ascending feature_id.
2614       iret = nf90_open(trim(nlst(1)%route_lake_f),NF90_NOWRITE,ncid=ftnRt)
2615       call nwmCheck(diagFlag,iret,'ERROR: Unable to open LAKEPARM file for index extraction')
2616       iret = nf90_inq_varid(ftnRt,'ascendingIndex',indVarId)
2617       if(iret .ne. 0) then
2618          call postDiagMsg(diagFlag,'WARNING: ascendingIndex not found in LAKEPARM file. No resorting will take place.')
2619          ascFlag = 0
2620       endif
2621       if(ascFlag .eq. 1) then
2622          iret = nf90_get_var(ftnRt,indVarId,chIndArray)
2623          call nwmCheck(diagFlag,iret,'ERROR: Unable to extract ascendingIndex from LAKEPARM file.')
2624       endif
2625       iret = nf90_close(ftnRt)
2626       call nwmCheck(diagFlag,iret,'ERROR: Unable to close LAKEPARM file.')
2628       ! Place all output arrays into one real array that will be looped over
2629       ! during conversion to compressed integer format.
2630       allocate(varOutReal(fileMeta%numVars,gSize))
2631       allocate(varOutInt(gSize))
2632       if(ascFlag .eq. 1) then
2633          ! Sort feature_id values by ascending values using the index array
2634          ! extracted from the RouteLink file.
2635          do iTmp=1,gSize
2636             indTmp = chIndArray(iTmp)
2637             indTmp = indTmp + 1 ! Python starts index values at 0, so we need to add one.
2638             g_lakeInflowOut(iTmp) = g_lakeInflow(indTmp)
2639             g_lakeOutflowOut(iTmp) = g_lakeOutflow(indTmp)
2640             g_lakeLonOut(iTmp) = g_lakeLon(indTmp)
2641             g_lakeLatOut(iTmp) = g_lakeLat(indTmp)
2642             g_lakeElevOut(iTmp) = g_lakeElev(indTmp)
2643             g_lakeTypeOut(iTmp) = g_lakeType(indTmp)
2644             g_lake_assimilated_valueOut(iTmp) = g_lake_assimilated_value(indTmp)
2645             g_lake_assimilated_source_fileOut(iTmp) = g_lake_assimilated_source_file(indTmp)
2646             g_lakeidOut(iTmp) = g_lakeid(indTmp)
2647          end do
2648       else
2649          g_lakeInflowOut = g_lakeInflow
2650          g_lakeOutflowOut = g_lakeOutflow
2651          g_lakeLonOut = g_lakeLon
2652          g_lakeLatOut = g_lakeLat
2653          g_lakeElevOut = g_lakeElev
2654          g_lakeTypeOut = g_lakeType
2655          g_lake_assimilated_valueOut = g_lake_assimilated_value
2656          g_lake_assimilated_source_fileOut = g_lake_assimilated_source_file
2657          g_lakeidOut = g_lakeid
2658       endif
2659       varOutReal(1,:) = g_lakeInflowOut(:)
2660       varOutReal(2,:) = g_lakeOutflowOut(:)
2662       ! Mask out missing values
2663       where ( varOutReal == fileMeta%modelNdv ) varOutReal = -9999.0
2665       iret = nf90_create(trim(output_flnm),cmode=NF90_NETCDF4,ncid = ftn)
2666       call nwmCheck(diagFlag,iret,'ERROR: Unable to create LAKEOUT NetCDF file.')
2668       ! Write global attributes.
2669       iret = nf90_put_att(ftn,NF90_GLOBAL,"TITLE",trim(fileMeta%title))
2670       call nwmCheck(diagFlag,iret,'ERROR: Unable to create TITLE attribute')
2671       iret = nf90_put_att(ftn,NF90_GLOBAL,"compiler_version",compiler_version())
2672       call nwmCheck(diagFlag,iret,'ERROR: Unable to create compiler_version attribute')
2673       iret = nf90_put_att(ftn,NF90_GLOBAL,"featureType",trim(fileMeta%fType))
2674       call nwmCheck(diagFlag,iret,'ERROR: Unable to create featureType attribute')
2675       iret = nf90_put_att(ftn,NF90_GLOBAL,"proj4",trim(fileMeta%proj4))
2676       call nwmCheck(diagFlag,iret,'ERROR: Unable to create proj4 attribute')
2677       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_initialization_time",trim(fileMeta%initTime))
2678       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model init attribute')
2679       iret = nf90_put_att(ftn,NF90_GLOBAL,"station_dimension",trim(fileMeta%lakeDim))
2680       call nwmCheck(diagFlag,iret,'ERROR: Unable to create st. dimension attribute')
2681       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_output_valid_time",trim(fileMeta%validTime))
2682       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model valid attribute')
2683       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_total_valid_times",fileMeta%totalValidTime)
2684       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model total valid times attribute')
2685       !iret = nf90_put_att(ftn,NF90_GLOBAL,"esri_pe_string",trim(fileMeta%esri))
2686       !call nwmCheck(diagFlag,iret,'ERROR: Unable to create ESRI attribute')
2687       iret = nf90_put_att(ftn,NF90_GLOBAL,"Conventions",trim(fileMeta%conventions))
2688       call nwmCheck(diagFlag,iret,'ERROR: Unable to create conventions attribute')
2689       iret = nf90_put_att(ftn,NF90_GLOBAL,"code_version",trim(get_code_version()))
2690       call nwmCheck(diagFlag,iret,'ERROR: Unable to create code_version attribute')
2691 #ifdef NWM_META
2692       iret = nf90_put_att(ftn,NF90_GLOBAL,"NWM_version_number",trim(get_nwm_version()))
2693       call nwmCheck(diagFlag,iret,'ERROR: Unable to create NWM_version_number attribute')
2694 #endif
2695       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_output_type",trim(fileMeta%modelOutputType))
2696       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_output_type attribute')
2697       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_configuration",modelConfigType)
2698       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_configuration attribute')
2700       ! Create dimensions
2701       iret = nf90_def_dim(ftn,"feature_id",gSize,dimId(1))
2702       call nwmCheck(diagFlag,iret,'ERROR: Unable to create feature_id dimension')
2703       iret = nf90_def_dim(ftn,"time",NF90_UNLIMITED,dimId(2))
2704       call nwmCheck(diagFlag,iret,'ERROR: Unable to create time dimension')
2705       iret = nf90_def_dim(ftn,"reference_time",1,dimId(3))
2706       call nwmCheck(diagFlag,iret,'ERROR: Unable to create reference_time dimension')
2707       !iret = nf90_def_dim(ftn,"string_length",256,dimId(4))
2708       !call nwmCheck(diagFlag,iret,'ERROR: Unable to create string length dimension')
2710       ! Create and populate reference_time and time variables.
2711       iret = nf90_def_var(ftn,"time",nf90_int,dimId(2),timeId)
2712       call nwmCheck(diagFlag,iret,'ERROR: Unable to create time variable')
2713       iret = nf90_put_att(ftn,timeId,'long_name',trim(fileMeta%timeLName))
2714       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into time variable')
2715       iret = nf90_put_att(ftn,timeId,'standard_name',trim(fileMeta%timeStName))
2716       call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into time variable')
2717       iret = nf90_put_att(ftn,timeId,'units',trim(fileMeta%timeUnits))
2718       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into time variable')
2719       iret = nf90_put_att(ftn,timeId,'valid_min',fileMeta%timeValidMin)
2720       call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_min attribute into time variable')
2721       iret = nf90_put_att(ftn,timeId,'valid_max',fileMeta%timeValidMax)
2722       call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_max attribute into time variable')
2723       iret = nf90_def_var(ftn,"reference_time",nf90_int,dimId(3),refTimeId)
2724       call nwmCheck(diagFlag,iret,'ERROR: Unable to create reference_time variable')
2725       iret = nf90_put_att(ftn,refTimeId,'long_name',trim(fileMeta%rTimeLName))
2726       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into reference_time variable')
2727       iret = nf90_put_att(ftn,refTimeId,'standard_name',trim(fileMeta%rTimeStName))
2728       call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into reference_time variable')
2729       iret = nf90_put_att(ftn,refTimeId,'units',trim(fileMeta%rTimeUnits))
2730       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into reference_time variable')
2732       ! Create a crs variable.
2733       ! NOTE - For now, we are hard-coding in for lat/lon points. However, this
2734       ! may be more flexible in future iterations.
2735       iret = nf90_def_var(ftn,'crs',nf90_char,varid=coordVarId)
2736       call nwmCheck(diagFlag,iret,'ERROR: Unable to create crs variable.')
2737       iret = nf90_put_att(ftn,coordVarId,'transform_name','latitude longitude')
2738       call nwmCheck(diagFlag,iret,'ERROR: Unable to place transform_name attribute into crs variable.')
2739       iret = nf90_put_att(ftn,coordVarId,'grid_mapping_name','latitude longitude')
2740       call nwmCheck(diagFlag,iret,'ERROR: Unable to place grid_mapping_name attribute into crs variable.')
2741       iret = nf90_put_att(ftn,coordVarId,'esri_pe_string','GEOGCS["GCS_WGS_1984",DATUM["D_WGS_1984",&
2742                                           &SPHEROID["WGS_1984",6378137.0,298.257223563]],PRIMEM["Greenwich",0.0],UNIT["Degree",&
2743                                           &0.0174532925199433]];-400 -400 1000000000;&
2744                                           &-100000 10000;-100000 10000;8.98315284119521E-09;0.001;0.001;IsHighPrecision')
2745       call nwmCheck(diagFlag,iret,'ERROR: Unable to place esri_pe_string into crs variable.')
2746       iret = nf90_put_att(ftn,coordVarId,'spatial_ref','GEOGCS["GCS_WGS_1984",DATUM["D_WGS_1984",&
2747                                           &SPHEROID["WGS_1984",6378137.0,298.257223563]],PRIMEM["Greenwich",0.0],UNIT["Degree",&
2748                                           &0.0174532925199433]];-400 -400 1000000000;&
2749                                           &-100000 10000;-100000 10000;8.98315284119521E-09;0.001;0.001;IsHighPrecision')
2750       call nwmCheck(diagFlag,iret,'ERROR: Unable to place spatial_ref into crs variable.')
2751       iret = nf90_put_att(ftn,coordVarId,'long_name','CRS definition')
2752       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name into crs variable.')
2753       iret = nf90_put_att(ftn,coordVarId,'longitude_of_prime_meridian',0.0)
2754       call nwmCheck(diagFlag,iret,'ERROR: Unable to place longitude_of_prime_meridian into crs variable.')
2755       iret = nf90_put_att(ftn,coordVarId,'_CoordinateAxes','latitude longitude')
2756       call nwmCheck(diagFlag,iret,'ERROR: Unable to place _CoordinateAxes into crs variable.')
2757       iret = nf90_put_att(ftn,coordVarId,'semi_major_axis',6378137.0)
2758       call nwmCheck(diagFlag,iret,'ERROR: Unable to place semi_major_axis into crs variable.')
2759       iret = nf90_put_att(ftn,coordVarId,'semi_minor_axis',6356752.31424518)
2760       call nwmCheck(diagFlag,iret,'ERROR: Unable to place semi_minor_axis into crs variable.')
2761       iret = nf90_put_att(ftn,coordVarId,'inverse_flattening',298.257223563)
2762       call nwmCheck(diagFlag,iret,'ERROR: Unable to place inverse_flattening into crs variable.')
2764       ! Create feature_id variable
2765       iret = nf90_def_var(ftn,"feature_id",nf90_int64,dimId(1),featureVarId)
2766       call nwmCheck(diagFlag,iret,'ERROR: Unable to create feature_id variable.')
2767       iret = nf90_put_att(ftn,featureVarId,'long_name',trim(fileMeta%featureIdLName))
2768       call nwmCheck(diagFlag,iret,'ERROR: Uanble to place long_name attribute into feature_id variable')
2769       iret = nf90_put_att(ftn,featureVarId,'comment',trim(fileMeta%featureIdComment))
2770       call nwmCheck(diagFlag,iret,'ERROR: Unable to place comment attribute into feature_id variable')
2771       iret = nf90_put_att(ftn,featureVarId,'cf_role',trim(fileMeta%cfRole))
2772       call nwmCheck(diagFlag,iret,'ERROR: Unable to place cf_role attribute into feature_id variable')
2774       ! Create reservoir_type variable
2775       iret = nf90_def_var(ftn, "reservoir_type", nf90_int, dimId(1), reservoirTypeVarId)
2776       call nwmCheck(diagFlag, iret, 'ERROR: Unable to create reservoir_type variable.')
2777       iret = nf90_put_att(ftn, reservoirTypeVarId, 'long_name', trim(fileMeta%reservoirTypeLName))
2778       call nwmCheck(diagFlag, iret, 'ERROR: Unable to place long_name attribute into reservoir_type variable')
2779       iret = nf90_put_att(ftn, reservoirTypeVarId, 'flag_values', fileMeta%reservoirTypeFlagValues)
2780       call nwmCheck(diagFlag, iret, 'ERROR: Unable to place flag_values attribute into reservoir_type variable')
2781       iret = nf90_put_att(ftn, reservoirTypeVarId, 'flag_meanings', trim(fileMeta%reservoirTypeFlagMeanings))
2782       call nwmCheck(diagFlag, iret, 'ERROR: Unable to place flag_meanings attribute into reservoir_type variable')
2784       ! Create reservoir_assimilated_value variable
2785       iret = nf90_def_var(ftn, "reservoir_assimilated_value", nf90_float, dimId(1), reservoirAssimilatedValueVarId)
2786       call nwmCheck(diagFlag, iret, 'ERROR: Unable to create reservoir_assimilated_value variable.')
2787       iret = nf90_put_att(ftn, reservoirAssimilatedValueVarId, 'long_name', trim(fileMeta%reservoirAssimilatedValueLName))
2788       call nwmCheck(diagFlag, iret, 'ERROR: Unable to place long_name attribute into reservoir_assimilated_value variable')
2789       iret = nf90_put_att(ftn,reservoirAssimilatedValueVarId,'units',trim(fileMeta%reservoirAssimilatedValueUnits))
2790       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into reservoir_assimilated_value variable')
2792       ! Create reservoir_assimilated_source_file variable
2793       !iret = nf90_def_var(ftn, "reservoir_assimilated_source_file", nf90_char, [dimId(4), dimId(1)], reservoirAssimilatedSourceFileVarId)
2794       !call nwmCheck(diagFlag, iret, 'ERROR: Unable to create reservoir_assimilated_source_file variable.')
2795       !iret = nf90_put_att(ftn, reservoirAssimilatedSourceFileVarId, 'long_name', trim(fileMeta%reservoirAssimilatedSourceFileLName))
2796       !call nwmCheck(diagFlag, iret, 'ERROR: Unable to place long_name attribute into reservoir_assimilated_source_file variable')
2797       !iret = nf90_def_var_fill(ftn, reservoirAssimilatedSourceFileVarId, 0, 0);
2798       !call nwmCheck(diagFlag, iret, 'ERROR: Unable to place _FillValue attribute into reservoir_assimilated_source_file variable')
2800       ! Create lake lat/lon variables
2801       iret = nf90_def_var(ftn,"latitude",nf90_float,dimId(1),latVarId)
2802       call nwmCheck(diagFlag,iret,'ERROR: Unable to create latitude variable.')
2803       iret = nf90_put_att(ftn,latVarId,'long_name',trim(fileMeta%latLName))
2804       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into latitude variable')
2805       iret = nf90_put_att(ftn,latVarId,'standard_name',trim(fileMeta%latStName))
2806       call nwmCheck(diagFlag,iret,'ERROR: Unable to place stndard_name attribute into latitude variable')
2807       iret = nf90_put_att(ftn,latVarId,'units',trim(fileMeta%latUnits))
2808       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into latitude variable')
2809       iret = nf90_def_var(ftn,"longitude",nf90_float,dimId(1),lonVarId)
2810       call nwmCheck(diagFlag,iret,'ERROR: Unable to create longitude variable.')
2811       iret = nf90_put_att(ftn,lonVarId,'long_name',trim(fileMeta%lonLName))
2812       call nwmCheck(diagFlag,iret,'ERROR: Uanble to place long_name attribute into longitude variable')
2813       iret = nf90_put_att(ftn,lonVarId,'standard_name',trim(fileMeta%lonStName))
2814       call nwmCheck(diagFlag,iret,'ERROR: Unable to place stndard_name attribute into longitude variable')
2815       iret = nf90_put_att(ftn,lonVarId,'units',trim(fileMeta%lonUnits))
2816       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into longitude variable')
2818       ! Create channel elevation variable
2819       iret = nf90_def_var(ftn,"water_sfc_elev",nf90_float,dimId(1),elevVarId)
2820       call nwmCheck(diagFlag,iret,'ERROR: Unable to create water_sfc_elev variable.')
2821       iret = nf90_put_att(ftn,elevVarId,'long_name',trim(fileMeta%elevLName))
2822       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into water_sfc_elev variable')
2823       iret = nf90_put_att(ftn,elevVarId,'units',trim(fileMeta%elevUnits))
2824       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into water_sfc_elev variable')
2825       iret = nf90_put_att(ftn,elevVarId,'comment',trim(fileMeta%elevComment))
2826       call nwmCheck(diagFlag,iret,'ERROR: Unable to place comment attribute into water_sfc_elev variable')
2828       ! Define deflation levels for these meta-variables. For now, we are going to
2829       ! default to a compression level of 2. Only compress if io_form_outputs is set to 1.
2830       if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
2831          iret = nf90_def_var_deflate(ftn,timeId,0,1,2)
2832          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for time.')
2833          iret = nf90_def_var_deflate(ftn,featureVarId,0,1,2)
2834          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for feature_id.')
2835          iret = nf90_def_var_deflate(ftn,reservoirTypeVarId,0,1,2)
2836          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for reservoir_type.')
2837          iret = nf90_def_var_deflate(ftn,refTimeId,0,1,2)
2838          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for reference_time.')
2839          iret = nf90_def_var_deflate(ftn,latVarId,0,1,2)
2840          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for latitude.')
2841          iret = nf90_def_var_deflate(ftn,lonVarId,0,1,2)
2842          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for longitude.')
2843          iret = nf90_def_var_deflate(ftn,elevVarId,0,1,2)
2844          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for elevation.')
2845       endif
2847       ! Allocate memory for the output variables, then place the real output
2848       ! variables into a single array. This array will be accessed throughout the
2849       ! output looping below for conversion to compressed integer values.
2850       ! Loop through and create each output variable, create variable attributes,
2851       ! and insert data.
2852       do iTmp=1,fileMeta%numVars
2853          if(fileMeta%outFlag(iTmp) .eq. 1) then
2854             ! First create variable
2855             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
2856                iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_int,dimId(1),varId)
2857             else
2858                iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_float,dimId(1),varId)
2859             endif
2860             call nwmCheck(diagFlag,iret,'ERROR: Unable to create variable:'//trim(fileMeta%varNames(iTmp)))
2862             ! Extract valid range into a 1D array for placement.
2863             varRange(1) = fileMeta%validMinComp(iTmp)
2864             varRange(2) = fileMeta%validMaxComp(iTmp)
2865             varRangeReal(1) = real(fileMeta%validMinDbl(iTmp))
2866             varRangeReal(2) = real(fileMeta%validMaxDbl(iTmp))
2868             ! Establish a compression level for the variables. For now we are using a
2869             ! compression level of 2. In addition, we are choosing to turn the shuffle
2870             ! filter off for now. Kelley Eicher did some testing with this and
2871             ! determined that the benefit wasn't worth the extra time spent writing output.
2872             ! Only compress if io_form_outputs is set to 1.
2873             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
2874                iret = nf90_def_var_deflate(ftn,varId,0,1,2)
2875                call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression for: '//trim(fileMeta%varNames(iTmp)))
2876             endif
2878             ! Create variable attributes
2879             iret = nf90_put_att(ftn,varId,'long_name',trim(fileMeta%longName(iTmp)))
2880             call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into variable '//trim(fileMeta%varNames(iTmp)))
2881             iret = nf90_put_att(ftn,varId,'units',trim(fileMeta%units(iTmp)))
2882             call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into variable '//trim(fileMeta%varNames(iTmp)))
2883             iret = nf90_put_att(ftn,varId,'coordinates',trim(fileMeta%coordNames(iTmp)))
2884             call nwmCheck(diagFlag,iret,'ERROR: Unable to place coordinates attribute into variable '//trim(fileMeta%varNames(iTmp)))
2885             iret = nf90_put_att(ftn,varId,'grid_mapping','crs')
2886             call nwmCheck(diagFlag,iret,'ERROR: Unable to place grid_mapping attribute into variable '//trim(fileMeta%varNames(iTmp)))
2887             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
2888                iret = nf90_put_att(ftn,varId,'_FillValue',fileMeta%fillComp(iTmp))
2889                call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
2890                iret = nf90_put_att(ftn,varId,'missing_value',fileMeta%missingComp(iTmp))
2891                call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
2892                iret = nf90_put_att(ftn,varId,'scale_factor',fileMeta%scaleFactor(iTmp))
2893                call nwmCheck(diagFlag,iret,'ERROR: Unable to place scale_factor attribute into variable '//trim(fileMeta%varNames(iTmp)))
2894                iret = nf90_put_att(ftn,varId,'add_offset',fileMeta%addOffset(iTmp))
2895                call nwmCheck(diagFlag,iret,'ERROR: Unable to place add_offset attribute into variable '//trim(fileMeta%varNames(iTmp)))
2896                iret = nf90_put_att(ftn,varId,'valid_range',varRange)
2897                call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
2898             else
2899                iret = nf90_put_att(ftn,varId,'_FillValue',fileMeta%fillReal(iTmp))
2900                call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
2901                iret = nf90_put_att(ftn,varId,'missing_value',fileMeta%missingReal(iTmp))
2902                call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
2903                iret = nf90_put_att(ftn,varId,'valid_range',varRangeReal)
2904                call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
2905             endif
2906          endif
2907       end do
2909       ! Remove NetCDF file from definition mode.
2910       iret = nf90_enddef(ftn)
2911       call nwmCheck(diagFlag,iret,'ERROR: Unable to take LAKETOUT file out of definition mode')
2913       ! Place lake ID, elevation, lat, and lon values into appropriate
2914       ! variables.
2915       do iTmp=1,fileMeta%numVars
2916          if(fileMeta%outFlag(iTmp) .eq. 1) then
2917             ! We are outputing this variable.
2918             ! Convert reals to integer. If we are on time 0, make sure we don't
2919             ! need to fill in with NDV values.
2920             if(minSinceSim .eq. 0 .and. fileMeta%timeZeroFlag(iTmp) .eq. 0) then
2921                varOutInt(:) = fileMeta%fillComp(iTmp)
2922                varOutReal(iTmp,:) = fileMeta%fillReal(iTmp)
2923             else
2924                varOutInt(:) = NINT((varOutReal(iTmp,:)-fileMeta%addOffset(iTmp))/fileMeta%scaleFactor(iTmp))
2925             endif
2926             ! Get NetCDF variable id.
2927             iret = nf90_inq_varid(ftn,trim(fileMeta%varNames(iTmp)),varId)
2928             call nwmCheck(diagFlag,iret,'ERROR: Unable to find variable ID for var: '//trim(fileMeta%varNames(iTmp)))
2929             ! Put data into NetCDF file
2930             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
2931                iret = nf90_put_var(ftn,varId,varOutInt)
2932             else
2933                iret = nf90_put_var(ftn,varId,varOutReal(iTmp,:))
2934             endif
2935             call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into output variable: '//trim(fileMeta%varNames(iTmp)))
2936          endif
2937       end do
2939       ! Place link ID values into the NetCDF file
2940       iret = nf90_inq_varid(ftn,'feature_id',varId)
2941       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate feature_id in NetCDF file.')
2942       iret = nf90_put_var(ftn,varId,g_lakeidOut)
2943       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into feature_id output variable.')
2945       ! Place reservoir_type values into the NetCDF file
2946       iret = nf90_inq_varid(ftn,'reservoir_type',varId)
2947       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate reservoir_type in NetCDF file.')
2948       iret = nf90_put_var(ftn,varId,g_lakeTypeOut)
2949       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into reservoir_type output variable.')
2951       ! Place reservoir_assimilated_value values into the NetCDF file
2952       iret = nf90_inq_varid(ftn,'reservoir_assimilated_value',varId)
2953       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate reservoir_assimilated_value in NetCDF file.')
2954       iret = nf90_put_var(ftn,varId,g_lake_assimilated_valueOut)
2955       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into reservoir_assimilated_value output variable.')
2957       ! Place reservoir_assimilated_source_file values into the NetCDF file
2958       !iret = nf90_inq_varid(ftn,'reservoir_assimilated_source_file',varId)
2959       !call nwmCheck(diagFlag,iret,'ERROR: Unable to locate reservoir_assimilated_source_file in NetCDF file.')
2960       !do iTmp = 1, gSize
2961       !   iret = nf90_put_var(ftn,varId,trim(g_lake_assimilated_source_fileOut(iTmp)), start=[1,iTmp])
2962       !   call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into reservoir_assimilated_source_file output variable.')
2963       !end do
2965       ! Place lake metadata into NetCDF file
2966       iret = nf90_inq_varid(ftn,'water_sfc_elev',varId)
2967       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate water_sfc_elev in NetCDF file.')
2968       iret = nf90_put_var(ftn,varId,g_lakeElevOut)
2969       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into water_sfc_elev output variable.')
2971       iret = nf90_inq_varid(ftn,'latitude',varId)
2972       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate latitude in NetCDF file.')
2973       iret = nf90_put_var(ftn,varId,g_lakeLatOut)
2974       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into latitude output variable.')
2976       iret = nf90_inq_varid(ftn,'longitude',varId)
2977       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate longitude in NetCDF file.')
2978       iret = nf90_put_var(ftn,varId,g_lakeLonOut)
2979       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into longitude output variable.')
2981       ! Place time values into time variables.
2982       iret = nf90_inq_varid(ftn,'time',varId)
2983       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate time variable')
2984       iret = nf90_put_var(ftn,varId,minSinceEpoch)
2985       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into time variable')
2986       iret = nf90_inq_varid(ftn,'reference_time',varId)
2987       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate reference_time variable')
2988       iret = nf90_put_var(ftn,varId,minSinceEpoch1)
2989       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into reference_time variable')
2991       ! Close the output file
2992       iret = nf90_close(ftn)
2993       call nwmCheck(diagFlag,iret,'ERROR: Unable to close LAKE file.')
2995    endif ! End if we are on master processor.
2997    ! Deallocate all memory
2998    if(myId .eq. 0) then
2999       deallocate(varOutReal)
3000       deallocate(varOutInt)
3001    endif
3002    deallocate(g_lakeLon)
3003    deallocate(g_lakeLat)
3004    deallocate(g_lakeElev)
3005    deallocate(g_lakeInflow)
3006    deallocate(g_lakeOutflow)
3007    deallocate(g_lakeid)
3008    deallocate(g_lakeType)
3009    deallocate(g_lake_assimilated_value)
3010    deallocate(g_lake_assimilated_source_file)
3012    if(myId .eq. 0) then
3013       deallocate(g_lakeLonOut)
3014       deallocate(g_lakeLatOut)
3015       deallocate(g_lakeElevOut)
3016       deallocate(g_lakeInflowOut)
3017       deallocate(g_lakeOutflowOut)
3018       deallocate(g_lakeidOut)
3019       deallocate(g_lakeTypeOut)
3020       deallocate(g_lake_assimilated_valueOut)
3021       deallocate(g_lake_assimilated_source_fileOut)
3022       deallocate(chIndArray)
3023    endif
3026 end subroutine output_lakes_NWM
3028 !==================================================================
3029 ! Program Name: output_chrtout_grd_NWM
3030 ! Author(s)/Contact(s): Logan R Karsten <karsten><ucar><edu>
3031 ! Abstract: Ouptut routine for gridden streamflow variables
3032 !           for non-reach based routing.
3033 ! History Log:
3034 ! 8/6/17 - Created, LRK.
3035 ! Usage:
3036 ! Parameters: None.
3037 ! Input Files: None.
3038 ! Output Files: None.
3039 ! Condition codes: None.
3041 ! User controllable options: None.
3043 subroutine output_chrtout_grd_NWM(domainId,iGrid)
3044    use module_rt_data, only: rt_domain
3045    use config_base, only: nlst
3046    use Module_Date_utilities_rt, only: geth_newdate, geth_idts
3047    use module_NWM_io_dict
3048    use netcdf
3049 #ifdef MPP_LAND
3050    use module_mpp_land
3051    use module_mpp_reachls,  only: ReachLS_write_io
3052 #endif
3053    implicit none
3055    ! subroutine arguments
3056    integer, intent(in) :: domainId
3057    integer, intent(in) :: iGrid
3059    ! Derived types.
3060    type(chrtGrdMeta) :: fileMeta
3062    ! Local variables
3063    integer :: mppFlag, diagFlag
3064    integer :: minSinceSim ! Number of minutes since beginning of simulation.
3065    integer :: minSinceEpoch1 ! Number of minutes from EPOCH to the beginning of the model simulation.
3066    integer :: minSinceEpoch ! Number of minutes from EPOCH to the current model valid time.
3067    character(len=16) :: epochDate ! EPOCH represented as a string.
3068    character(len=16) :: startDate ! Start of model simulation, represented as a string.
3069    character(len=256) :: output_flnm ! CHRTOUT_GRID filename
3070    integer :: iret ! NetCDF return statuses
3071    integer :: ftn ! NetCDF file handle
3072    character(len=256) :: validTime ! Global attribute time string
3073    character(len=256) :: initTime ! Global attribute time string
3074    integer :: dimId(4) ! Dimension ID values created during NetCDF created.
3075    integer :: varId ! Variable ID value created as NetCDF variables are created and populated.
3076    integer :: timeId ! Dimension ID for the time dimension.
3077    integer :: refTimeId ! Dimension ID for the reference time dimension.
3078    integer :: xVarId,yVarId,coordVarId ! Coordinate variable NC ID values
3079    integer :: varRange(2) ! Local storage for valid min/max ranges
3080    real :: varRangeReal(2) ! Local storage for valid min/max ranges
3081    integer :: ierr, myId ! MPI return status, process ID
3082    integer :: ftnGeo,geoXVarId,geoYVarId
3083    integer :: iTmp,jTmp,jTmp2,iTmp2
3084    integer :: gNumLnks,lNumLnks
3085    integer :: indexVarId
3086    ! Allocatable array to hold temporary streamflow for checking
3087    real, allocatable, dimension(:) :: strFlowLocal
3088    ! Allocatable array to hold global qlink values
3089    real, allocatable, dimension(:,:) :: g_qlink
3090    ! Allocatable array to hold streamflow index values
3091    integer(kind=int64), allocatable, dimension(:,:) :: CH_NETLNK
3092    ! allocatable global array to hold grid of output streamflow values
3093    integer, allocatable, dimension(:,:) :: tmpFlow
3094    real, allocatable, dimension(:,:) :: tmpFlowReal
3095    ! allocatable arrays to hold coordinate values
3096    real*8, allocatable, dimension(:) :: yCoord,xCoord,yCoord2
3098    character (len=64) :: modelConfigType ! This is character verion (long name) for the io_config_outputs
3100 ! Establish macro variables to hlep guide this subroutine.
3101 #ifdef MPP_LAND
3102    mppFlag = 1
3103 #else
3104    mppFlag = 0
3105 #endif
3107 #ifdef HYDRO_D
3108    diagFlag = 1
3109 #else
3110    diagFlag = 0
3111 #endif
3113    ! We will print a warning to the user if they request CHRTOUT_GRID under
3114    ! reach-based routing. Currently, this is not supported as we don't have a
3115    ! way to map reaches to individual cells on the channel grid in the Fulldom
3116    ! file.
3117    if(nlst(domainId)%CHRTOUT_GRID .eq. 1) then
3118       if(nlst(domainId)%channel_option .ne. 3) then
3119          call postDiagMsg(diagFlag,'WARNING: CHRTOUT_GRID only available for gridded channel routing, not reach-based routing.')
3120          return
3121       endif
3122    endif
3124    ! If we are running over MPI, determine which processor number we are on.
3125    ! If not MPI, then default to 0, which is the I/O ID.
3126    if(mppFlag .eq. 1) then
3127 #ifdef MPP_LAND
3128       call MPI_COMM_RANK( HYDRO_COMM_WORLD, myId, ierr )
3129       call nwmCheck(diagFlag,ierr,'ERROR: Unable to determine MPI process ID.')
3130 #endif
3131    else
3132       myId = 0
3133    endif
3135    ! Some sanity checking here.
3136    if(nlst(domainId)%CHRTOUT_GRID .eq. 0) then
3137       ! No output requested here. Return to the parent calling program.
3138       return
3139    endif
3141    ! Initialize qlink arrays and collect data from processors for output.
3142    gNumLnks = rt_domain(domainId)%gnlinks
3143    lNumLnks = rt_domain(domainId)%NLINKS
3144    if(myId .eq. 0) then
3145       ! Channel index values
3146       allocate(CH_NETLNK(RT_DOMAIN(domainId)%g_ixrt,RT_DOMAIN(domainId)%g_jxrt))
3147       ! Global qlink values
3148       allocate(g_qlink(gNumLnks,2) )
3149       ! Grid of global streamflow values via scale_factor/add_offset
3150       allocate(tmpFlow(RT_DOMAIN(domainId)%g_ixrt,RT_DOMAIN(domainId)%g_jxrt))
3151       allocate(tmpFlowReal(RT_DOMAIN(domainId)%g_ixrt,RT_DOMAIN(domainId)%g_jxrt))
3152    else
3153       allocate(CH_NETLNK(1,1))
3154       allocate(g_qlink(1,2) )
3155       allocate(tmpFlow(1,1))
3156       allocate(tmpFlowReal(1,1))
3157    endif
3158    ! Allocate local streamflow array. We need to do a check to
3159    ! for lake_type 2. However, we cannot set the values in the global array
3160    ! to missing as this causes the model to crash.
3161    allocate(strFlowLocal(RT_DOMAIN(domainId)%NLINKS))
3162    strFlowLocal = RT_DOMAIN(domainId)%QLINK(:,1)
3163    ! Loop through all the local links on this processor. For lake_type
3164    ! of 2, we need to manually set the streamflow values
3165    ! to the model NDV value.
3166    if (RT_DOMAIN(domainId)%NLAKES .gt. 0) then
3167       do iTmp=1,RT_DOMAIN(domainId)%NLINKS
3168          if (RT_DOMAIN(domainId)%TYPEL(iTmp) .eq. 2) then
3169             strFlowLocal(iTmp) = fileMeta%modelNdv
3170          endif
3171       end do
3172    endif
3173    if(nlst(domainId)%channel_option .eq. 3) then
3174       call write_chanel_real(strFlowLocal,RT_DOMAIN(domainId)%map_l2g,gNumLnks,lNumLnks,g_qlink(:,1))
3175       call write_chanel_real(RT_DOMAIN(domainId)%qlink(:,2),RT_DOMAIN(domainId)%map_l2g,gNumLnks,lNumLnks,g_qlink(:,2))
3176    endif
3177    call write_IO_rt_int8(RT_DOMAIN(domainId)%GCH_NETLNK, CH_NETLNK)
3179    ! Initialize NWM dictionary derived type containing all the necessary metadat
3180    ! for the output file.
3181    call initChrtGrdDict(fileMeta,myId,diagFlag)
3183    ! For now, we will default to outputting all variables until further notice.
3184    fileMeta%outFlag(:) = [1]
3186    ! Calculate datetime information.
3187    ! First compose strings of EPOCH and simulation start date.
3188    epochDate = trim("1970-01-01 00:00")
3189    startDate = trim(nlst(domainId)%startdate(1:4)//"-"//&
3190                     nlst(domainId)%startdate(6:7)//&
3191                     &"-"//nlst(domainId)%startdate(9:10)//" "//&
3192                     nlst(domainId)%startdate(12:13)//":"//&
3193                     nlst(domainId)%startdate(15:16))
3194    ! Second, utilize NoahMP date utilities to calculate the number of minutes
3195    ! from EPOCH to the beginning of the model simulation.
3196    call geth_idts(startDate,epochDate,minSinceEpoch1)
3197    ! Third, calculate the number of minutes since the beginning of the
3198    ! simulation.
3199    minSinceSim = int(nlst(1)%out_dt*(rt_domain(1)%out_counts-1))
3200    ! Fourth, calculate the total number of minutes from EPOCH to the current
3201    ! model time step.
3202    minSinceEpoch = minSinceEpoch1 + minSinceSim
3203    ! Fifth, compose global attribute time strings that will be used.
3204    validTime = trim(nlst(domainId)%olddate(1:4)//'-'//&
3205                     nlst(domainId)%olddate(6:7)//'-'//&
3206                     nlst(domainId)%olddate(9:10)//'_'//&
3207                     nlst(domainId)%olddate(12:13)//':'//&
3208                     nlst(domainId)%olddate(15:16)//&
3209                     &':00')
3210    initTime = trim(nlst(domainId)%startdate(1:4)//'-'//&
3211                   nlst(domainId)%startdate(6:7)//'-'//&
3212                   nlst(domainId)%startdate(9:10)//'_'//&
3213                   nlst(domainId)%startdate(12:13)//':'//&
3214                   nlst(domainId)%startdate(15:16)//&
3215                   &':00')
3216    ! Replace default values in the dictionary.
3217    fileMeta%initTime = trim(initTime)
3218    fileMeta%validTime = trim(validTime)
3220    ! calculate the minimum and maximum time
3221    fileMeta%timeValidMin = minSinceEpoch1 + nlst(1)%out_dt
3222    fileMeta%timeValidMax = minSinceEpoch1 + int(nlst(1)%khour * 60/nlst(1)%out_dt) * nlst(1)%out_dt
3224    ! calculate total_valid_time
3225    fileMeta%totalValidTime = int(nlst(1)%khour * 60 / nlst(1)%out_dt)  ! # number of valid time (#of output files)
3227    ! Create output filename
3228    write(output_flnm, '(A12,".CHRTOUT_GRID",I1)') nlst(domainId)%olddate(1:4)//&
3229                        nlst(domainId)%olddate(6:7)//&
3230                        nlst(domainId)%olddate(9:10)//&
3231                        nlst(domainId)%olddate(12:13)//&
3232                        nlst(domainId)%olddate(15:16), igrid
3234    ! call the GetModelConfigType function
3235    modelConfigType = GetModelConfigType(nlst(1)%io_config_outputs)
3237    if(myId .eq. 0) then
3238       ! Create output NetCDF file for writing.
3239       iret = nf90_create(trim(output_flnm),cmode=NF90_NETCDF4,ncid = ftn)
3240       call nwmCheck(diagFlag,iret,'ERROR: Unable to create RT_DOMAIN NetCDF file.')
3242       ! Write global attributes
3243       iret = nf90_put_att(ftn,NF90_GLOBAL,'TITLE',trim(fileMeta%title))
3244       call nwmCheck(diagFlag,iret,'ERROR: Unable to create TITLE attribute')
3245       iret = nf90_put_att(ftn,NF90_GLOBAL,"compiler_version",compiler_version())
3246       call nwmCheck(diagFlag,iret,'ERROR: Unable to create compiler_version attribute')
3247       iret = nf90_put_att(ftn,NF90_GLOBAL,'model_initialization_time',trim(fileMeta%initTime))
3248       call nwmCheck(diagFlag,iret,'ERROR: Unable to place model init time attribute into RT_DOMAIN file.')
3249       iret = nf90_put_att(ftn,NF90_GLOBAL,'model_output_valid_time',trim(fileMeta%validTime))
3250       call nwmCheck(diagFlag,iret,'ERROR: Unable to place model output time attribute into RT_DOMAIN file.')
3251       iret = nf90_put_att(ftn,NF90_GLOBAL,'model_total_valid_times',fileMeta%totalValidTime)
3252       call nwmCheck(diagFlag,iret,'ERROR: Unable to place model total valid times attribute into RT_DOMAIN file.')
3253       iret = nf90_put_att(ftn,NF90_GLOBAL,'Conventions',trim(fileMeta%conventions))
3254       call nwmCheck(diagFlag,iret,'ERROR: Unable to place CF conventions attribute into RT_DOMAIN file.')
3255       iret = nf90_put_att(ftn,NF90_GLOBAL,"code_version",trim(get_code_version()))
3256       call nwmCheck(diagFlag,iret,'ERROR: Unable to create code_version attribute')
3257 #ifdef NWM_META
3258       iret = nf90_put_att(ftn,NF90_GLOBAL,"NWM_version_number",trim(get_nwm_version()))
3259       call nwmCheck(diagFlag,iret,'ERROR: Unable to create NWM_version_number attribute')
3260 #endif
3261       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_output_type",trim(fileMeta%modelOutputType))
3262       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_output_type attribute')
3263       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_configuration",modelConfigType)
3264       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_configuration attribute')
3265       iret = nf90_put_att(ftn,NF90_GLOBAL,"proj4",trim(fileMeta%proj4))
3266       call nwmCheck(diagFlag,iret,'ERROR: Unable to create proj4 attribute')
3267       iret = nf90_put_att(ftn,NF90_GLOBAL,"GDAL_DataType","Generic")
3268       call nwmCheck(diagFlag,iret,'ERROR: Unable to create GDAL_DataType attribute')
3270       ! Create dimensions
3271       iret = nf90_def_dim(ftn,'time',NF90_UNLIMITED,dimId(1))
3272       call nwmCheck(diagFlag,iret,'ERROR: Unable to define time dimension')
3273       iret = nf90_def_dim(ftn,'x',RT_DOMAIN(domainId)%g_ixrt,dimId(2))
3274       call nwmCheck(diagFlag,iret,'ERROR: Unable to define x dimension')
3275       iret = nf90_def_dim(ftn,'y',RT_DOMAIN(domainId)%g_jxrt,dimId(3))
3276       call nwmCheck(diagFlag,iret,'ERROR: Unable to define y dimension')
3277       iret = nf90_def_dim(ftn,'reference_time',1,dimId(4))
3278       call nwmCheck(diagFlag,iret,'ERROR: Unable to define reference_time dimension')
3280       ! Create and populate reference_time and time variables.
3281       iret = nf90_def_var(ftn,"time",nf90_int,dimId(1),timeId)
3282       call nwmCheck(diagFlag,iret,'ERROR: Unable to create time variable')
3283       iret = nf90_put_att(ftn,timeId,'long_name',trim(fileMeta%timeLName))
3284       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into time variable')
3285       iret = nf90_put_att(ftn,timeId,'standard_name',trim(fileMeta%timeStName))
3286       call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into time variable')
3287       iret = nf90_put_att(ftn,timeId,'units',trim(fileMeta%timeUnits))
3288       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into time variable')
3289       iret = nf90_put_att(ftn,timeId,'valid_min',fileMeta%timeValidMin)
3290       call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_min attribute into time variable')
3291       iret = nf90_put_att(ftn,timeId,'valid_max',fileMeta%timeValidMax)
3292       call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_max attribute into time variable')
3293       iret = nf90_def_var(ftn,"reference_time",nf90_int,dimId(4),refTimeId)
3294       call nwmCheck(diagFlag,iret,'ERROR: Unable to create reference_time variable')
3295       iret = nf90_put_att(ftn,refTimeId,'long_name',trim(fileMeta%rTimeLName))
3296       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into reference_time variable')
3297       iret = nf90_put_att(ftn,refTimeId,'standard_name',trim(fileMeta%rTimeStName))
3298       call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into reference_time variable')
3299       iret = nf90_put_att(ftn,refTimeId,'units',trim(fileMeta%rTimeUnits))
3300       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into reference_time variable')
3302       ! Create x/y coordinate variables
3303       iret = nf90_def_var(ftn,'x',nf90_double,dimId(2),xVarId)
3304       call nwmCheck(diagFlag,iret,'ERROR: Unable to create x coordinate variable')
3305       do iTmp=1,fileMeta%nxRealAtts
3306          iret = nf90_put_att(ftn,xVarId,trim(fileMeta%xFloatAttNames(iTmp)),&
3307                              fileMeta%xRealAttVals(iTmp,1:fileMeta%xRealAttLen(iTmp)))
3308          call nwmCheck(diagFlag,iret,'ERROR: Unable to place x floating point attributes into CHRTOUT_GRID file.')
3309       end do
3310       do iTmp=1,fileMeta%nxCharAtts
3311          iret = nf90_put_att(ftn,xVarId,trim(fileMeta%xCharAttNames(iTmp)),trim(fileMeta%xCharAttVals(iTmp)))
3312          call nwmCheck(diagFlag,iret,'ERROR: Unable to place x string point attributes into CHRTOUT_GRID file.')
3313       end do
3314       iret = nf90_def_var(ftn,'y',nf90_double,dimId(3),yVarId)
3315       call nwmCheck(diagFlag,iret,'ERROR: Unable to create y coordinate variable')
3316       do iTmp=1,fileMeta%nyRealAtts
3317          iret = nf90_put_att(ftn,yVarId,trim(fileMeta%yFloatAttNames(iTmp)),&
3318                              fileMeta%yRealAttVals(iTmp,1:fileMeta%yRealAttLen(iTmp)))
3319          call nwmCheck(diagFlag,iret,'ERROR: Unable to place y floating point attributes into CHRTOUT_GRID file.')
3320       end do
3321       do iTmp=1,fileMeta%nyCharAtts
3322          iret = nf90_put_att(ftn,yVarId,trim(fileMeta%yCharAttNames(iTmp)),trim(fileMeta%yCharAttVals(iTmp)))
3323          call nwmCheck(diagFlag,iret,'ERROR: Unable to place y string point attributes into CHRTOUT_GRID file.')
3324       end do
3326       ! Define compression for meta-variables only if io_form_outputs is set to 1.
3327       if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
3328          iret = nf90_def_var_deflate(ftn,timeId,0,1,2)
3329          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for time.')
3330          iret = nf90_def_var_deflate(ftn,refTimeId,0,1,2)
3331          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for reference_time.')
3332          iret = nf90_def_var_deflate(ftn,xVarId,0,1,2)
3333          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for x.')
3334          iret = nf90_def_var_deflate(ftn,yVarId,0,1,2)
3335          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for y.')
3336       endif
3338       ! Translate crs variable info from land spatial metadata file to output
3339       ! file.
3340       iret = nf90_def_var(ftn,'crs',nf90_char,varid=coordVarId)
3341       call nwmCheck(diagFlag,iret,'ERROR: Unable to create crs variable in CHRTOUT_GRID file.')
3342       do iTmp=1,fileMeta%nCrsRealAtts
3343          iret = nf90_put_att(ftn,coordVarId,trim(fileMeta%crsFloatAttNames(iTmp)),&
3344                              fileMeta%crsRealAttVals(iTmp,1:fileMeta%crsRealAttLen(iTmp)))
3345          call nwmCheck(diagFlag,iret,'ERROR: Unable to place crs floating point attributes into CHRTOUT_GRID file.')
3346       end do
3347       do iTmp=1,fileMeta%nCrsCharAtts
3348          iret = nf90_put_att(ftn,coordVarId,trim(fileMeta%crsCharAttNames(iTmp)),trim(fileMeta%crsCharAttVals(iTmp)))
3349          call nwmCheck(diagFlag,iret,'ERROR: Unable to place crs string point attributes into CHRTOUT_GRID file.')
3350       end do
3352       ! Create channel index variable.
3353       iret = nf90_def_var(ftn,'index',nf90_int,(/dimId(2),dimId(3)/),varid=indexVarId)
3354       iret = nf90_put_att(ftn,indexVarId,'_FillValue',-9999)
3355       call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable index')
3356       iret = nf90_put_att(ftn,indexVarId,'missing_value',-9999)
3357       call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable index')
3358       iret = nf90_put_att(ftn,indexVarId,'long_name','Streamflow Index Value')
3359       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into variable index')
3360       iret = nf90_put_att(ftn,indexVarId,'units','-')
3361       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into variable index')
3362       iret = nf90_put_att(ftn,indexVarId,'grid_mapping','crs')
3363       call nwmCheck(diagFlag,iret,'ERROR: Unable to place grid_mapping attribute into variable: index')
3364       ! Place necessary geospatial attributes into the variable.
3365       do iTmp2=1,fileMeta%nCrsCharAtts
3366          if(trim(fileMeta%crsCharAttNames(iTmp2)) .eq. 'esri_pe_string') then
3367             iret = nf90_put_att(ftn,indexVarId,trim(fileMeta%crsCharAttNames(iTmp2)),trim(fileMeta%crsCharAttVals(iTmp2)))
3368             call nwmCheck(diagFlag,iret,'ERROR: Unable to place esri_pe_string attribute into '//trim(fileMeta%varNames(iTmp)))
3369          endif
3370       end do
3371       ! Define compression for meta-variables only if io_form_outputs is set to 1.
3372       if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
3373          iret = nf90_def_var_deflate(ftn,indexVarId,0,1,2)
3374          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for index.')
3375       endif
3377       ! Loop through all possible variables and create them, along with their
3378       ! metadata attributes.
3379       do iTmp=1,fileMeta%numVars
3380          if(fileMeta%outFlag(iTmp) .eq. 1) then
3381             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
3382                iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_int,(/dimId(2),dimId(3),dimId(1)/),varId)
3383             else
3384                iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_float,(/dimId(2),dimId(3),dimId(1)/),varId)
3385             endif
3386             call nwmCheck(diagFlag,iret,"ERROR: Unable to create variable: "//trim(fileMeta%varNames(iTmp)))
3388             ! Extract valid range into a 1D array for placement.
3389             varRange(1) = fileMeta%validMinComp(iTmp)
3390             varRange(2) = fileMeta%validMaxComp(iTmp)
3391             varRangeReal(1) = real(fileMeta%validMinDbl(iTmp))
3392             varRangeReal(2) = real(fileMeta%validMaxDbl(iTmp))
3394             ! Establish a compression level for the variables. For now we are
3395             ! using a
3396             ! compression level of 2. In addition, we are choosing to turn the
3397             ! shuffle
3398             ! filter off for now. Kelley Eicher did some testing with this and
3399             ! determined that the benefit wasn't worth the extra time spent
3400             ! writing output.
3401             ! Only compress if io_form_outputs is set to 1.
3402             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
3403                iret = nf90_def_var_deflate(ftn,varId,0,1,2)
3404                call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression for: '//trim(fileMeta%varNames(iTmp)))
3405             endif
3407             ! Create variable attributes
3408             iret = nf90_put_att(ftn,varId,'long_name',trim(fileMeta%longName(iTmp)))
3409             call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into variable '//trim(fileMeta%varNames(iTmp)))
3410             iret = nf90_put_att(ftn,varId,'units',trim(fileMeta%units(iTmp)))
3411             call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into variable '//trim(fileMeta%varNames(iTmp)))
3412             iret = nf90_put_att(ftn,varId,'grid_mapping','crs')
3413             call nwmCheck(diagFlag,iret,'ERROR: Unable to place grid_mapping attribute into variable: '//trim(fileMeta%varNames(iTmp)))
3414             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
3415                iret = nf90_put_att(ftn,varId,'_FillValue',fileMeta%fillComp(iTmp))
3416                call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
3417                iret = nf90_put_att(ftn,varId,'missing_value',fileMeta%missingComp(iTmp))
3418                call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
3419                iret = nf90_put_att(ftn,varId,'scale_factor',fileMeta%scaleFactor(iTmp))
3420                call nwmCheck(diagFlag,iret,'ERROR: Unable to place scale_factor attribute into variable '//trim(fileMeta%varNames(iTmp)))
3421                iret = nf90_put_att(ftn,varId,'add_offset',fileMeta%addOffset(iTmp))
3422                call nwmCheck(diagFlag,iret,'ERROR: Unable to place add_offset attribute into variable '//trim(fileMeta%varNames(iTmp)))
3423                iret = nf90_put_att(ftn,varId,'valid_range',varRange)
3424                call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
3425             else
3426                iret = nf90_put_att(ftn,varId,'_FillValue',fileMeta%fillReal(iTmp))
3427                call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
3428                iret = nf90_put_att(ftn,varId,'missing_value',fileMeta%missingReal(iTmp))
3429                call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
3430                iret = nf90_put_att(ftn,varId,'valid_range',varRangeReal)
3431                call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
3432             endif
3433             ! Place necessary geospatial attributes into the variable.
3434             do iTmp2=1,fileMeta%nCrsCharAtts
3435                if(trim(fileMeta%crsCharAttNames(iTmp2)) .eq. 'esri_pe_string') then
3436                   iret = nf90_put_att(ftn,varId,trim(fileMeta%crsCharAttNames(iTmp2)),trim(fileMeta%crsCharAttVals(iTmp2)))
3437                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place esri_pe_string attribute into '//trim(fileMeta%varNames(iTmp)))
3438                endif
3439             end do
3440          endif
3441       end do ! end looping through variable output list.
3443       ! Remove NetCDF file from definition mode.
3444       iret = nf90_enddef(ftn)
3445       call nwmCheck(diagFlag,iret,'ERROR: Unable to take RT_DOMAIN file out of definition mode')
3447       ! Read in coordinates from FullDom file. These will be placed into the
3448       ! output file coordinate variables.
3449       allocate(xCoord(RT_DOMAIN(domainId)%g_ixrt))
3450       allocate(yCoord(RT_DOMAIN(domainId)%g_jxrt))
3451       allocate(yCoord2(RT_DOMAIN(domainId)%g_jxrt))
3452       iret = nf90_open(trim(nlst(domainId)%geo_finegrid_flnm),NF90_NOWRITE,ncid=ftnGeo)
3453       call nwmCheck(diagFlag,iret,'ERROR: Unable to open FullDom file')
3454       iret = nf90_inq_varid(ftnGeo,'x',geoXVarId)
3455       call nwmCheck(diagFlag,iret,'ERROR: Unable to find x coordinate in FullDom file')
3456       iret = nf90_get_var(ftnGeo,geoXVarId,xCoord)
3457       call nwmCheck(diagFlag,iret,'ERROR: Unable to extract x coordinate from FullDom file')
3458       iret = nf90_inq_varid(ftnGeo,'y',geoYVarId)
3459       call nwmCheck(diagFlag,iret,'ERROR: Unable to find y coordinate in FullDom file')
3460       iret = nf90_get_var(ftnGeo,geoYVarId,yCoord)
3461       call nwmCheck(diagFlag,iret,'ERROR: Unable to extract y coordinate from FullDom file')
3462       iret = nf90_close(ftnGeo)
3463       call nwmCheck(diagFlag,iret,'ERROR: Unable to close geoGrid file.')
3465       ! Reverse Y coordinates. They are read in reverse.
3466       jTmp2 = 0
3467       do jTmp = RT_DOMAIN(domainId)%g_jxrt,1,-1
3468          jTmp2 = jTmp2 + 1
3469          yCoord2(jTmp2) = yCoord(jTmp)
3470       end do
3471       ! Place coordinate values into output file
3472       iret = nf90_inq_varid(ftn,'x',varId)
3473       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate x coordinate variable.')
3474       iret = nf90_put_var(ftn,varId,xCoord)
3475       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into x coordinate variable')
3476       iret = nf90_inq_varid(ftn,'y',varId)
3477       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate y coordinate variable')
3478       iret = nf90_put_var(ftn,varId,yCoord2)
3479       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into y coordinate variable')
3480       deallocate(xCoord)
3481       deallocate(yCoord)
3482       deallocate(yCoord2)
3484       ! Place streamflow index values into output file.
3485       iret = nf90_inq_varid(ftn,'index',varId)
3486       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate index variable.')
3487       iret = nf90_put_var(ftn,varId,CH_NETLNK,(/1,1/),(/RT_DOMAIN(domainId)%g_ixrt,RT_DOMAIN(domainId)%g_jxrt/))
3488       call nwmCheck(diagFlag,iret,'ERROR: Unable to place CH_NETLNK values into index variable.')
3490       ! Place time values into time variables.
3491       iret = nf90_inq_varid(ftn,'time',varId)
3492       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate time variable')
3493       iret = nf90_put_var(ftn,varId,minSinceEpoch)
3494       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into time variable')
3495       iret = nf90_inq_varid(ftn,'reference_time',varId)
3496       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate reference_time variable')
3497       iret = nf90_put_var(ftn,varId,minSinceEpoch1)
3498       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into reference_time variable')
3500       ! Since the only variable we are "looping" over for output is streamflow,
3501       ! handle below. If other variables are added later, we can modify this
3502       ! section.
3503       do jTmp=1,RT_DOMAIN(domainId)%g_jxrt
3504          do iTmp=1,RT_DOMAIN(domainId)%g_ixrt
3505             if(CH_NETLNK(iTmp,jTmp).GE.0) then
3506                tmpFlow(iTmp,jTmp) = NINT((g_qlink(CH_NETLNK(iTmp,jTmp),1)-fileMeta%addOffset(1))/fileMeta%scaleFactor(1))
3507                tmpFlowReal(iTmp,jTmp) = g_qlink(CH_NETLNK(iTmp,jTmp),1)
3508             else
3509                 tmpFlow(iTmp,jTmp) = fileMeta%fillComp(1)
3510                 tmpFlowReal(iTmp,jTmp) = fileMeta%fillReal(1)
3511             endif
3512          enddo
3513       enddo
3515       ! Place streamflow grid into output file.
3516       iret = nf90_inq_varid(ftn,'streamflow',varId)
3517       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate streamflow variable.')
3518       if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
3519          iret = nf90_put_var(ftn,varId,tmpFlow,(/1,1,1/),(/RT_DOMAIN(domainId)%g_ixrt,RT_DOMAIN(domainId)%g_jxrt,1/))
3520       else
3521          iret = nf90_put_var(ftn,varId,tmpFlowReal,(/1,1,1/),(/RT_DOMAIN(domainId)%g_ixrt,RT_DOMAIN(domainId)%g_jxrt,1/))
3522       endif
3523       call nwmCheck(diagFlag,iret,'ERROR: Unable to place streamflow values into CHRTOUT_GRID')
3525    endif ! End if statement if on I/O ID
3527    if(myId .eq. 0) then
3528       ! Close the output file
3529       iret = nf90_close(ftn)
3530       call nwmCheck(diagFlag,iret,'ERROR: Unable to close RT_DOMAIN file.')
3531    endif
3533    ! Deallocate memory as needed
3534    deallocate(g_qlink, CH_NETLNK, tmpFlow, tmpFlowReal, strFlowLocal)
3536 end subroutine output_chrtout_grd_NWM
3538 !===============================================================================
3539 ! Program Name: output_lsmOut_NWM
3540 ! Author(s)/Contact(s): Logan R Karsten <karsten><ucar><edu>
3541 ! Abstract: Output routine fro diagnostic LSM grids.
3542 ! History Log:
3543 ! 8/9/17 -Created, LRK.
3544 ! Usage:
3545 ! Parameters: None.
3546 ! Input Files. None.
3547 ! Output Files: None.
3548 ! Condition codes: None.
3550 ! User controllable options: None.
3552 subroutine output_lsmOut_NWM(domainId)
3553   use module_rt_data, only: rt_domain
3554   use config_base, only: nlst
3555   use Module_Date_utilities_rt, only: geth_newdate, geth_idts
3556   use module_NWM_io_dict
3557   use netcdf
3558 #ifdef MPP_LAND
3559   use module_mpp_land
3560 #endif
3561   implicit none
3563    ! Subroutine arguments
3564    integer, intent(in) :: domainId
3566    ! Derived types.
3567    type(lsmMeta) :: fileMeta
3569    ! Local variables
3570    integer :: minSinceSim ! Number of minutes since beginning of simulation.
3571    integer :: minSinceEpoch1 ! Number of minutes from EPOCH to the beginning of the model simulation.
3572    integer :: minSinceEpoch ! Number of minutes from EPOCH to the current model valid time.
3573    character(len=16) :: epochDate ! EPOCH represented as a string.
3574    character(len=16) :: startDateTmp ! Start of model simulation, represented as a string.
3575    character(len=256) :: validTime ! Global attribute time string
3576    character(len=256) :: initTime ! Global attribute time string
3577    integer :: mppFlag, diagFlag
3578    character(len=1024) :: output_flnm ! Output file name
3579    integer :: iret ! NetCDF return status
3580    integer :: ftn  ! NetCDF file handle
3581    integer :: dimId(4) ! NetCDF dimension ID values
3582    integer :: varId ! NetCDF variable ID value
3583    integer :: timeId ! NetCDF time variable ID
3584    integer :: refTimeId ! NetCDF reference_time variable ID
3585    integer :: coordVarId ! NetCDF coordinate variable ID
3586    integer :: xVarId,yVarId ! NetCDF x/y variable ID
3587    integer :: ierr, myId ! MPI related values
3588    !integer :: varRange(2) ! Local storage of valid min/max values
3589    real :: varRange(2) ! Local storage of valid min/max values
3590    integer :: iTmp,jTmp,iTmp2,jTmp2
3591    integer :: ftnGeo,geoXVarId,geoYVarId
3592    integer :: waterVal ! Value in HRLDAS in WRFINPUT file used to define water bodies for masking
3593    real*8, allocatable, dimension(:) :: yCoord,xCoord,yCoord2
3594    real :: varRealTmp
3595    real, allocatable, dimension(:,:) :: localRealTmp, globalOutReal
3596    !integer, allocatable, dimension(:,:) :: globalCompTmp, localCompTmp
3598    character (len=64) :: modelConfigType ! This is character verion (long name) for the io_config_outputs
3600 #ifdef MPP_LAND
3601    mppFlag = 1
3602 #else
3603    mppFlag = 0
3604 #endif
3606 #ifdef HYDRO_D
3607    diagFlag = 1
3608 #else
3609    diagFlag = 0
3610 #endif
3612    ! If we are running over MPI, determine which processor number we are on.
3613    ! If not MPI, then default to 0, which is the I/O ID.
3614    if(mppFlag .eq. 1) then
3615 #ifdef MPP_LAND
3616       call MPI_COMM_RANK( HYDRO_COMM_WORLD, myId, ierr )
3617       call nwmCheck(diagFlag,ierr,'ERROR: Unable to determine MPI process ID.')
3618 #endif
3619    else
3620       myId = 0
3621    endif
3623    ! Some sanity checking here.
3624    if(nlst(domainId)%LSMOUT_DOMAIN .eq. 0) then
3625       ! No output requested here. Return to the parent calling program.
3626       return
3627    endif
3629    ! Call routine to initialize metadata structure
3630    call initLsmOutDict(fileMeta,myId,diagFlag)
3632    ! Initialize the water type
3633    waterVal = rt_domain(domainId)%iswater
3635    ! Calculate necessary datetime information that will go into the output file.
3636    ! First compose strings of EPOCH and simulation start date.
3637    epochDate = trim("1970-01-01 00:00")
3638    startDateTmp = trim(nlst(1)%startdate(1:4)//"-"//&
3639                        nlst(1)%startdate(6:7)//&
3640                        &"-"//nlst(1)%startdate(9:10)//" "//&
3641                        nlst(1)%startdate(12:13)//":"//&
3642                        nlst(1)%startdate(15:16))
3643    ! Second, utilize NoahMP date utilities to calculate the number of minutes
3644    ! from EPOCH to the beginning of the model simulation.
3645    call geth_idts(startDateTmp,epochDate,minSinceEpoch1)
3646    ! Third, calculate the number of minutes since the beginning of the
3647    ! simulation.
3648    minSinceSim = int(nlst(1)%out_dt*(rt_domain(1)%out_counts-1))
3649    ! Fourth, calculate the total number of minutes from EPOCH to the current
3650    ! model time step.
3651    minSinceEpoch = minSinceEpoch1 + minSinceSim
3652    ! Fifth, compose global attribute time strings that will be used.
3653    validTime = trim(nlst(1)%olddate(1:4)//'-'//&
3654                     nlst(1)%olddate(6:7)//'-'//&
3655                     nlst(1)%olddate(9:10)//'_'//&
3656                     nlst(1)%olddate(12:13)//':'//&
3657                     nlst(1)%olddate(15:16)//&
3658                     &':00')
3659    initTime = trim(nlst(1)%startdate(1:4)//'-'//&
3660                   nlst(1)%startdate(6:7)//'-'//&
3661                   nlst(1)%startdate(9:10)//'_'//&
3662                   nlst(1)%startdate(12:13)//':'//&
3663                   nlst(1)%startdate(15:16)//&
3664                   &':00')
3665    ! Replace default values in the dictionary.
3666    fileMeta%initTime = trim(initTime)
3667    fileMeta%validTime = trim(validTime)
3669    ! calculate the minimum and maximum time
3670    fileMeta%timeValidMin = minSinceEpoch1 + nlst(1)%out_dt
3671    fileMeta%timeValidMax = minSinceEpoch1 + int(nlst(1)%khour * 60/nlst(1)%out_dt) * nlst(1)%out_dt
3673    ! calculate total_valid_time
3674    fileMeta%totalValidTime = int(nlst(1)%khour * 60 / nlst(1)%out_dt)  ! # number of valid time (#of output files)
3676    ! For now, will always default to outputting all available
3677    ! variables since the nature of this output file is
3678    ! diagnostic in nature.
3679    fileMeta%outFlag(:) = [1,1,1,1,1,1,1,1,1,1,1,1,1,1]
3681    ! call the GetModelConfigType function
3682    modelConfigType = GetModelConfigType(nlst(1)%io_config_outputs)
3684    if(myId .eq. 0) then
3685       ! We are on the I/O node. Create output file.
3686       write(output_flnm,'(A12,".LSMOUT_DOMAIN",I1)') nlst(domainId)%olddate(1:4)//&
3687             nlst(domainId)%olddate(6:7)//nlst(domainId)%olddate(9:10)//&
3688             nlst(domainId)%olddate(12:13)//nlst(domainId)%olddate(15:16),&
3689             nlst(domainId)%igrid
3691       iret = nf90_create(trim(output_flnm),cmode=NF90_NETCDF4,ncid = ftn)
3692       call nwmCheck(diagFlag,iret,'ERROR: Unable to create LSMOUT NetCDF file.')
3694       ! Write global attributes
3695       iret = nf90_put_att(ftn,NF90_GLOBAL,'TITLE',trim(fileMeta%title))
3696       call nwmCheck(diagFlag,iret,'ERROR: Unable to place TITLE attribute into LSMOUT file.')
3697       iret = nf90_put_att(ftn,NF90_GLOBAL,"compiler_version",compiler_version())
3698       call nwmCheck(diagFlag,iret,'ERROR: Unable to create compiler_version attribute')
3699       iret = nf90_put_att(ftn,NF90_GLOBAL,'model_initialization_time',trim(fileMeta%initTime))
3700       call nwmCheck(diagFlag,iret,'ERROR: Unable to place model init time attribute into LSMOUT file.')
3701       iret = nf90_put_att(ftn,NF90_GLOBAL,'model_output_valid_time',trim(fileMeta%validTime))
3702       call nwmCheck(diagFlag,iret,'ERROR: Unable to place model output time attribute into LSMOUT file.')
3703       iret = nf90_put_att(ftn,NF90_GLOBAL,'modle_total_valid_time',fileMeta%totalValidTime)
3704       call nwmCheck(diagFlag,iret,'ERROR: Unable to place model total valid time attribute into LSMOUT file.')
3705       iret = nf90_put_att(ftn,NF90_GLOBAL,'Conventions',trim(fileMeta%conventions))
3706       call nwmCheck(diagFlag,iret,'ERROR: Unable to place CF conventions attribute into LSMOUT file.')
3707       iret = nf90_put_att(ftn,NF90_GLOBAL,"code_version",trim(get_code_version()))
3708       call nwmCheck(diagFlag,iret,'ERROR: Unable to create code_version attribute')
3709 #ifdef NWM_META
3710       iret = nf90_put_att(ftn,NF90_GLOBAL,"NWM_version_number",trim(get_nwm_version()))
3711       call nwmCheck(diagFlag,iret,'ERROR: Unable to create NWM_version_number attribute')
3712 #endif
3713       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_output_type",trim(fileMeta%modelOutputType))
3714       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_output_type attribute')
3715       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_configuration",modelConfigType)
3716       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_configuration attribute')
3717       iret = nf90_put_att(ftn,NF90_GLOBAL,"proj4",trim(fileMeta%proj4))
3718       call nwmCheck(diagFlag,iret,'ERROR: Unable to create proj4 attribute')
3719       iret = nf90_put_att(ftn,NF90_GLOBAL,"GDAL_DataType","Generic")
3720       call nwmCheck(diagFlag,iret,'ERROR: Unable to create GDAL_DataType attribute')
3722       ! Create dimensions
3723       iret = nf90_def_dim(ftn,'time',NF90_UNLIMITED,dimId(1))
3724       call nwmCheck(diagFlag,iret,'ERROR: Unable to define time dimension')
3725       iret = nf90_def_dim(ftn,'x',global_nx,dimId(2))
3726       call nwmCheck(diagFlag,iret,'ERROR: Unable to define x dimension')
3727       iret = nf90_def_dim(ftn,'y',global_ny,dimId(3))
3728       call nwmCheck(diagFlag,iret,'ERROR: Unable to define y dimension')
3729       iret = nf90_def_dim(ftn,'reference_time',1,dimId(4))
3730       call nwmCheck(diagFlag,iret,'ERROR: Unable to define reference_time dimension')
3732       ! Create and populate reference_time and time variables.
3733       iret = nf90_def_var(ftn,"time",nf90_int,dimId(1),timeId)
3734       call nwmCheck(diagFlag,iret,'ERROR: Unable to create time variable')
3735       iret = nf90_put_att(ftn,timeId,'long_name',trim(fileMeta%timeLName))
3736       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into time variable')
3737       iret = nf90_put_att(ftn,timeId,'standard_name',trim(fileMeta%timeStName))
3738       call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into time variable')
3739       iret = nf90_put_att(ftn,timeId,'units',trim(fileMeta%timeUnits))
3740       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into time variable')
3741       iret = nf90_put_att(ftn,timeId,'valid_min',fileMeta%timeValidMin)
3742       call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_min attribute into time variable')
3743       iret = nf90_put_att(ftn,timeId,'valid_max',fileMeta%timeValidMax)
3744       call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_max attribute into time variable')
3745       iret = nf90_def_var(ftn,"reference_time",nf90_int,dimId(4),refTimeId)
3746       call nwmCheck(diagFlag,iret,'ERROR: Unable to create reference_time variable')
3747       iret = nf90_put_att(ftn,refTimeId,'long_name',trim(fileMeta%rTimeLName))
3748       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into reference_time variable')
3749       iret = nf90_put_att(ftn,refTimeId,'standard_name',trim(fileMeta%rTimeStName))
3750       call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into reference_time variable')
3751       iret = nf90_put_att(ftn,refTimeId,'units',trim(fileMeta%rTimeUnits))
3752       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into reference_time variable')
3754       ! Create x/y coordinate variables
3755       iret = nf90_def_var(ftn,'x',nf90_double,dimId(2),xVarId)
3756       call nwmCheck(diagFlag,iret,'ERROR: Unable to create x coordinate variable')
3757       do iTmp=1,fileMeta%nxRealAtts
3758          iret = nf90_put_att(ftn,xVarId,trim(fileMeta%xFloatAttNames(iTmp)),&
3759                              fileMeta%xRealAttVals(iTmp,1:fileMeta%xRealAttLen(iTmp)))
3760          call nwmCheck(diagFlag,iret,'ERROR: Unable to place x floating point attributes into LSMOUT file.')
3761       end do
3762       do iTmp=1,fileMeta%nxCharAtts
3763          iret = nf90_put_att(ftn,xVarId,trim(fileMeta%xCharAttNames(iTmp)),trim(fileMeta%xCharAttVals(iTmp)))
3764          call nwmCheck(diagFlag,iret,'ERROR: Unable to place x string point attributes into LSMOUT file.')
3765       end do
3766       iret = nf90_def_var(ftn,'y',nf90_double,dimId(3),yVarId)
3767       call nwmCheck(diagFlag,iret,'ERROR: Unable to create y coordinate variable')
3768       do iTmp=1,fileMeta%nyRealAtts
3769          iret = nf90_put_att(ftn,yVarId,trim(fileMeta%yFloatAttNames(iTmp)),&
3770                              fileMeta%yRealAttVals(iTmp,1:fileMeta%yRealAttLen(iTmp)))
3771          call nwmCheck(diagFlag,iret,'ERROR: Unable to place y floating point attributes into LSMOUT file.')
3772       end do
3773       do iTmp=1,fileMeta%nyCharAtts
3774          iret = nf90_put_att(ftn,yVarId,trim(fileMeta%yCharAttNames(iTmp)),trim(fileMeta%yCharAttVals(iTmp)))
3775          call nwmCheck(diagFlag,iret,'ERROR: Unable to place y string point attributes into LSMOUT file.')
3776       end do
3778       ! Define compression for meta-variables. Only compress if io_form_outputs is set
3779       ! to 1.
3780       if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
3781          iret = nf90_def_var_deflate(ftn,timeId,0,1,2)
3782          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for time.')
3783          iret = nf90_def_var_deflate(ftn,refTimeId,0,1,2)
3784          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for reference_time.')
3785          iret = nf90_def_var_deflate(ftn,xVarId,0,1,2)
3786          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for x.')
3787          iret = nf90_def_var_deflate(ftn,yVarId,0,1,2)
3788          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for y.')
3789       endif
3791       ! Translate crs variable info from land spatial metadata file to output
3792       ! file.
3793       iret = nf90_def_var(ftn,'crs',nf90_char,varid=coordVarId)
3794       call nwmCheck(diagFlag,iret,'ERROR: Unable to create crs variable in LSMOUT file.')
3795       do iTmp=1,fileMeta%nCrsRealAtts
3796          iret = nf90_put_att(ftn,coordVarId,trim(fileMeta%crsFloatAttNames(iTmp)),&
3797                              fileMeta%crsRealAttVals(iTmp,1:fileMeta%crsRealAttLen(iTmp)))
3798          call nwmCheck(diagFlag,iret,'ERROR: Unable to place crs floating point attributes into LSMOUT file.')
3799       end do
3800       do iTmp=1,fileMeta%nCrsCharAtts
3801          iret = nf90_put_att(ftn,coordVarId,trim(fileMeta%crsCharAttNames(iTmp)),trim(fileMeta%crsCharAttVals(iTmp)))
3802          call nwmCheck(diagFlag,iret,'ERROR: Unable to place crs string point attributes into LSMOUT file.')
3803       end do
3805       ! Loop through all possible variables and create them, along with their
3806       ! metadata attributes.
3807       do iTmp=1,fileMeta%numVars
3808          if(fileMeta%outFlag(iTmp) .eq. 1) then
3809             !iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_int,(/dimId(2),dimId(3),dimId(1)/),varId)
3810             iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_float,(/dimId(2),dimId(3),dimId(1)/),varId)
3811             call nwmCheck(diagFlag,iret,"ERROR: Unable to create variable: "//trim(fileMeta%varNames(iTmp)))
3813             ! Extract valid range into a 1D array for placement.
3814             varRange(1) = fileMeta%validMinDbl(iTmp)
3815             varRange(2) = fileMeta%validMaxDbl(iTmp)
3817             ! Establish a compression level for the variables. For now we are using a
3818             ! compression level of 2. In addition, we are choosing to turn the shuffle
3819             ! filter off for now. Kelley Eicher did some testing with this and
3820             ! determined that the benefit wasn't worth the extra time spent writing output.
3821             ! Only compress if io_form_outputs is set to 1.
3822             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
3823                iret = nf90_def_var_deflate(ftn,varId,0,1,2)
3824                call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression for: '//trim(fileMeta%varNames(iTmp)))
3825             endif
3827             ! Create variable attributes
3828             iret = nf90_put_att(ftn,varId,'_FillValue',fileMeta%fillReal(iTmp))
3829             call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
3830             iret = nf90_put_att(ftn,varId,'missing_value',fileMeta%missingReal(iTmp))
3831             call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
3832             iret = nf90_put_att(ftn,varId,'long_name',trim(fileMeta%longName(iTmp)))
3833             call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into variable '//trim(fileMeta%varNames(iTmp)))
3834             iret = nf90_put_att(ftn,varId,'units',trim(fileMeta%units(iTmp)))
3835             call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into variable '//trim(fileMeta%varNames(iTmp)))
3836             iret = nf90_put_att(ftn,varId,'grid_mapping','crs')
3837             call nwmCheck(diagFlag,iret,'ERROR: Unable to place grid_mapping attribute into variable: '//trim(fileMeta%varNames(iTmp)))
3838             ! Place necessary geospatial attributes into the variable.
3839             do iTmp2=1,fileMeta%nCrsCharAtts
3840                if(trim(fileMeta%crsCharAttNames(iTmp2)) .eq. 'esri_pe_string') then
3841                   iret = nf90_put_att(ftn,varId,trim(fileMeta%crsCharAttNames(iTmp2)),trim(fileMeta%crsCharAttVals(iTmp2)))
3842                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place esri_pe_string attribute into '//trim(fileMeta%varNames(iTmp)))
3843                endif
3844             end do
3845          endif ! End if output flag is on
3846       end do ! end looping through variable output list.
3848       ! Remove NetCDF file from definition mode.
3849       iret = nf90_enddef(ftn)
3850       call nwmCheck(diagFlag,iret,'ERROR: Unable to take LSMOUT file out of definition mode')
3852       ! Read in coordinates from GeoGrid file. These will be placed into the
3853       ! output file coordinate variables.
3854       allocate(xCoord(global_nx))
3855       allocate(yCoord(global_ny))
3856       allocate(yCoord2(global_ny))
3857       iret = nf90_open(trim(nlst(1)%land_spatial_meta_flnm),NF90_NOWRITE,ncid=ftnGeo)
3858       if(iret .ne. 0) then
3859          ! Spatial metadata file not found for land grid. Warn the user no
3860          ! file was found, and set x/y coordinates to -9999.0
3861          call postDiagMsg(diagFlag,'WARNING: Unable to find LAND spatial metadata file')
3862          xCoord = -9999.0
3863          yCoord = -9999.0
3864          yCoord2 = -9999.0
3865       else
3866          iret = nf90_inq_varid(ftnGeo,'x',geoXVarId)
3867          call nwmCheck(diagFlag,iret,'ERROR: Unable to find x coordinate in geoGrid file')
3868          iret = nf90_get_var(ftnGeo,geoXVarId,xCoord)
3869          call nwmCheck(diagFlag,iret,'ERROR: Unable to extract x coordinate from geoGrid file')
3870          iret = nf90_inq_varid(ftnGeo,'y',geoYVarId)
3871          call nwmCheck(diagFlag,iret,'ERROR: Unable to find y coordinate in geoGrid file')
3872          iret = nf90_get_var(ftnGeo,geoYVarId,yCoord)
3873          call nwmCheck(diagFlag,iret,'ERROR: Unable to extract y coordinate from geoGrid file')
3874          iret = nf90_close(ftnGeo)
3875          call nwmCheck(diagFlag,iret,'ERROR: Unable to close geoGrid file.')
3876          ! Reverse Y coordinates. They are read in reverse.
3877          jTmp2 = 0
3878          do jTmp = global_ny,1,-1
3879             jTmp2 = jTmp2 + 1
3880             yCoord2(jTmp2) = yCoord(jTmp)
3881          end do
3882       endif
3884       ! Place coordinate values into output file
3885       iret = nf90_inq_varid(ftn,'x',varId)
3886       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate x coordinate variable.')
3887       iret = nf90_put_var(ftn,varId,xCoord)
3888       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into x coordinate variable')
3889       iret = nf90_inq_varid(ftn,'y',varId)
3890       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate y coordinate variable')
3891       iret = nf90_put_var(ftn,varId,yCoord2)
3892       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into y coordinate variable')
3893       deallocate(xCoord)
3894       deallocate(yCoord)
3895       deallocate(yCoord2)
3897       ! Place time values into time variables.
3898       iret = nf90_inq_varid(ftn,'time',varId)
3899       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate time variable')
3900       iret = nf90_put_var(ftn,varId,minSinceEpoch)
3901       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into time variable')
3902       iret = nf90_inq_varid(ftn,'reference_time',varId)
3903       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate reference_time variable')
3904       iret = nf90_put_var(ftn,varId,minSinceEpoch1)
3905       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into reference_time variable')
3907    end if ! End if we are on the I/O processor.
3909    ! Allocate temporary local memory
3910    allocate(localRealTmp(rt_domain(domainId)%ix,rt_domain(domainId)%jx))
3912    ! Loop through all possible variables to output. Collect the data to the
3913    ! global grid and output to the necessary NetCDF variable.
3914    do iTmp=1,fileMeta%numVars
3915       if(fileMeta%outFlag(iTmp) .eq. 1) then
3916          ! Allocate memory necessary
3917          if(myId .eq. 0) then
3918             allocate(globalOutReal(global_nx,global_ny))
3919          else
3920             allocate(globalOutReal(1,1))
3921          endif
3923          ! Loop through the local array and convert floating point values
3924          ! to integer via scale_factor/add_offset. If the pixel value
3925          ! falls within a water class value, leave as ndv.
3926          do iTmp2 = 1,rt_domain(domainId)%ix
3927             do jTmp2 = 1,rt_domain(domainId)%jx
3928                if(iTmp .eq. 1) then
3929                   varRealTmp = rt_domain(domainId)%stc(iTmp2,jTmp2,1)
3930                else if(iTmp .eq. 2) then
3931                   varRealTmp = rt_domain(domainId)%smc(iTmp2,jTmp2,1)
3932                else if(iTmp .eq. 3) then
3933                   varRealTmp = rt_domain(domainId)%sh2ox(iTmp2,jTmp2,1)
3934                else if(iTmp .eq. 4) then
3935                   varRealTmp = rt_domain(domainId)%stc(iTmp2,jTmp2,2)
3936                else if(iTmp .eq. 5) then
3937                   varRealTmp = rt_domain(domainId)%smc(iTmp2,jTmp2,2)
3938                else if(iTmp .eq. 6) then
3939                   varRealTmp = rt_domain(domainId)%sh2ox(iTmp2,jTmp2,2)
3940                else if(iTmp .eq. 7) then
3941                   varRealTmp = rt_domain(domainId)%stc(iTmp2,jTmp2,3)
3942                else if(iTmp .eq. 8) then
3943                   varRealTmp = rt_domain(domainId)%smc(iTmp2,jTmp2,3)
3944                else if(iTmp .eq. 9) then
3945                   varRealTmp = rt_domain(domainId)%sh2ox(iTmp2,jTmp2,3)
3946                else if(iTmp .eq. 10) then
3947                   varRealTmp = rt_domain(domainId)%stc(iTmp2,jTmp2,4)
3948                else if(iTmp .eq. 11) then
3949                   varRealTmp = rt_domain(domainId)%smc(iTmp2,jTmp2,4)
3950                else if(iTmp .eq. 12) then
3951                   varRealTmp = rt_domain(domainId)%sh2ox(iTmp2,jTmp2,4)
3952                else if(iTmp .eq. 13) then
3953                   varRealTmp = rt_domain(domainId)%INFXSRT(iTmp2,jTmp2)
3954                else if(iTmp .eq. 14) then
3955                   varRealTmp = rt_domain(domainId)%overland%control%surface_water_head_lsm(iTmp2,jTmp2) ! updated to use new location of sfcheadrt
3956                endif
3958                ! For now, we are foregoing converting these variables to integer
3959                ! via scale_factor/add_offset. This file is meant for diagnostic
3960                ! purposes, so we want to keep full precision.
3961                localRealTmp(iTmp2,jTmp2) = varRealTmp
3963                ! If we are on time 0, make sure we don't need to fill in the
3964                ! grid with NDV values.
3965                !if(minSinceSim .eq. 0 .and. fileMeta%timeZeroFlag(iTmp) .eq. 0) then
3966                !   localCompTmp(iTmp2,jTmp2) = fileMeta%fillComp(iTmp)
3967                !else
3968                !   if(varRealTmp .eq. fileMeta%modelNdv) then
3969                !      localCompTmp(iTmp2,jTmp2) = INT(fileMeta%fillComp(iTmp))
3970                !   else
3971                !      localCompTmp(iTmp2,jTmp2) = NINT((varRealTmp-fileMeta%addOffset(iTmp))/fileMeta%scaleFactor(iTmp))
3972                !   endif
3973                !   if(vegTyp(iTmp2,jTmp2) .eq. waterVal) then
3974                !      localCompTmp(iTmp2,jTmp2) = INT(fileMeta%fillComp(iTmp))
3975                !   endif
3976                !endif
3977             enddo
3978          enddo
3979          ! Collect local 2D arrays to global 2D array
3980          if(mppFlag .eq. 1) then
3981 #ifdef MPP_LAND
3982             call write_IO_real(localRealTmp,globalOutReal)
3983 #endif
3984          else
3985             globalOutReal = localRealTmp
3986          endif
3988          ! Write array out to NetCDF file
3989          if(myId .eq. 0) then
3990             iret = nf90_inq_varid(ftn,trim(fileMeta%varNames(iTmp)),varId)
3991             call nwmCheck(diagFlag,iret,'ERROR: Unable to find variable ID for var: '//trim(fileMeta%varNames(iTmp)))
3992             iret = nf90_put_var(ftn,varId,globalOutReal,(/1,1,1/),(/global_nx,global_ny,1/))
3993             call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into output variable: '//trim(fileMeta%varNames(iTmp)))
3994          endif
3996          deallocate(globalOutReal)
3997       endif
3998    enddo
4000    if(myId .eq. 0) then
4001       ! Close the output file
4002       iret = nf90_close(ftn)
4003       call nwmCheck(diagFlag,iret,'ERROR: Unable to close LSMOUT_DOMAIN file.')
4004    endif
4006    deallocate(localRealTmp)
4008 end subroutine output_lsmOut_NWM
4010 !==============================================================================
4011 ! Program Name: output_frxstPts
4012 ! Author(s)/Contact(s): Logan R Karsten <karsten><ucar><edu>
4013 ! Abstract: Output frxstPts ASCII file from streamflow at forecast points
4014 ! defined in the Fulldom file.
4015 ! History Log:
4016 ! 9/18/17 -Created, LRK.
4017 ! Usage:
4018 ! Parameters: None.
4019 ! Input Files: None.
4020 ! Output Files: None.
4021 ! Condition codes: None.
4023 ! User controllable options: None.
4024 subroutine output_frxstPts(domainId)
4025    use module_rt_data, only: rt_domain
4026    use config_base, only: nlst
4027    use Module_Date_utilities_rt, only: geth_newdate, geth_idts
4028    use module_NWM_io_dict
4029 #ifdef MPP_LAND
4030    use module_mpp_land
4031    use module_mpp_reachls,  only: ReachLS_write_io
4032 #endif
4033 implicit none
4035    ! Pass in "did" value from hydro driving program.
4036    integer, intent(in) :: domainId
4038    ! Local variables
4039    integer :: mppFlag, diagFlag, ierr, myId
4040    integer :: seconds_since
4041    integer :: gSize, iTmp, numPtsOut
4042    integer, allocatable, dimension(:) :: g_STRMFRXSTPTS, g_outInd
4043    real, allocatable, dimension(:,:) :: g_qlink, g_qlinkOut
4044    real, allocatable, dimension(:) :: g_chlat, g_chlon, g_hlink, strFlowLocal
4045    integer, allocatable, dimension(:) :: frxstPtsLocal, g_STRMFRXSTPTSOut
4046    real, allocatable, dimension(:) :: g_chlatOut, g_chlonOut, g_hlinkOut
4047    integer(kind=int64), allocatable, dimension(:) :: g_linkid, g_linkidOut
4049 #ifdef MPP_LAND
4050    mppFlag = 1
4051 #else
4052    mppFlag = 0
4053 #endif
4055 #ifdef HYDRO_D
4056    diagFlag = 1
4057 #else
4058    diagFlag = 0
4059 #endif
4061    if(nlst(domainId)%frxst_pts_out .eq. 0) then
4062       ! No output requested here, return to parent calling program/subroutine.
4063       return
4064    endif
4066    ! If we are running over MPI, determine which processor number we are on.
4067    ! If not MPI, then default to 0, which is the I/O ID.
4068    if(mppFlag .eq. 1) then
4069 #ifdef MPP_LAND
4070       call MPI_COMM_RANK( HYDRO_COMM_WORLD, myId, ierr )
4071       call nwmCheck(diagFlag,ierr,'ERROR: Unable to determine MPI process ID.')
4072 #endif
4073    else
4074       myId = 0
4075    endif
4077    ! Calculate datetime information
4078    seconds_since = int(nlst(1)%out_dt*60*(rt_domain(1)%out_counts-1))
4080    ! First step is to allocate a global array of index values. This "index"
4081    ! array will be used to subset after collection has taken place. Also,
4082    ! the sum of this array will be used to determine the size of the output
4083    ! arrays.
4084    if(mppFlag .eq. 1) then
4085       if(nlst(domainId)%channel_option .ne. 3) then
4086          gSize = rt_domain(domainId)%gnlinksl
4087       else
4088          gSize = rt_domain(domainId)%gnlinks
4089       endif
4091       if(myId .eq. 0) then
4092          allocate(g_STRMFRXSTPTS(gSize))
4093          allocate(g_outInd(gSize))
4094          allocate(g_qlink(gSize,2))
4095          allocate(g_chlat(gSize))
4096          allocate(g_chlon(gSize))
4097          allocate(g_hlink(gSize))
4098          allocate(g_linkid(gSize))
4099       else
4100          allocate(g_STRMFRXSTPTS(1))
4101          allocate(g_outInd(1))
4102          allocate(g_qlink(1,2))
4103          allocate(g_chlat(1))
4104          allocate(g_chlon(1))
4105          allocate(g_hlink(1))
4106          allocate(g_linkid(1))
4107       endif
4109       ! Initialize the index array to 0
4110       g_outInd = 0
4112       ! Allocate local streamflow arrays. We need to do a check to
4113       ! for lake_type 2. However, we cannot set the values in the global array
4114       ! to missing as this causes the model to crash.
4115       allocate(strFlowLocal(RT_DOMAIN(domainId)%NLINKS))
4116       allocate(frxstPtsLocal(RT_DOMAIN(domainId)%NLINKS))
4117       strFlowLocal = RT_DOMAIN(domainId)%QLINK(:,1)
4118       frxstPtsLocal = rt_domain(domainId)%STRMFRXSTPTS
4120       ! Loop through all the local links on this processor. For lake_type
4121       ! of 2, we need to manually set the streamflow values
4122       ! to the model NDV value.
4123       if (RT_DOMAIN(domainId)%NLAKES .gt. 0) then
4124          do iTmp=1,RT_DOMAIN(domainId)%NLINKS
4125             if (RT_DOMAIN(domainId)%TYPEL(iTmp) .eq. 2) then
4126                !strFlowLocal(iTmp) = fileMeta%modelNdv
4127                strFlowLocal(iTmp) = -9.E15
4128                frxstPtsLocal(iTmp) = -9999
4129             endif
4130          end do
4131       endif
4133       ! Collect arrays from various processors
4134       if(nlst(domainId)%channel_option .eq. 3) then
4135          call write_chanel_int(frxstPtsLocal,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_STRMFRXSTPTS)
4136          call write_chanel_real(strFlowLocal,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_qlink(:,1))
4137          call write_chanel_real(RT_DOMAIN(domainId)%QLINK(:,2),rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_qlink(:,2))
4138          call write_chanel_real(RT_DOMAIN(domainId)%CHLAT,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_chlat)
4139          call write_chanel_real(RT_DOMAIN(domainId)%CHLON,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_chlon)
4140          call write_chanel_real(RT_DOMAIN(domainId)%HLINK,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_hlink)
4141       else
4142          call ReachLS_write_io(strFlowLocal,g_qlink(:,1))
4143          call ReachLS_write_io(RT_DOMAIN(domainId)%QLINK(:,2),g_qlink(:,2))
4144          call ReachLS_write_io(RT_DOMAIN(domainId)%linkid,g_linkid)
4145          call ReachLS_write_io(RT_DOMAIN(domainId)%CHLAT,g_chlat)
4146          call ReachLS_write_io(RT_DOMAIN(domainId)%CHLON,g_chlon)
4147          call ReachLS_write_io(RT_DOMAIN(domainId)%HLINK,g_hlink)
4148       endif
4150       deallocate(strFlowLocal)
4151       deallocate(frxstPtsLocal)
4153    else
4154       ! Running sequentially on a single processor.
4155       gSize = rt_domain(domainId)%nlinks
4156       allocate(g_STRMFRXSTPTS(gSize))
4157       allocate(g_outInd(gSize))
4158       allocate(g_chlon(gSize))
4159       allocate(g_chlat(gSize))
4160       allocate(g_hlink(gSize))
4161       allocate(g_qlink(gSize,2))
4162       allocate(g_linkid(gSize))
4164       ! Initialize the index array to 0
4165       g_outInd = 0
4167       g_STRMFRXSTPTS = rt_domain(domainId)%STRMFRXSTPTS
4168       g_chlon = RT_DOMAIN(domainId)%CHLON
4169       g_chlat = RT_DOMAIN(domainId)%CHLAT
4170       g_hlink = RT_DOMAIN(domainId)%HLINK
4171       g_qlink = RT_DOMAIN(domainId)%QLINK
4172       g_linkid = RT_DOMAIN(domainId)%linkid
4173    endif
4175    if(myId .eq. 0) then
4176       ! Set index values to 1 where we have forecast points.
4177       if(nlst(domainId)%channel_option .eq. 3) then
4178          where(g_STRMFRXSTPTS .ne. -9999) g_outInd = 1
4179       endif
4181       if(nlst(domainId)%channel_option .ne. 3) then
4182          ! Check to see if we have any gages that need to be added for reach-based
4183          ! routing.
4184          call checkRouteGages(diagFlag,gSize,g_outInd)
4185       endif
4187       ! Filter out any missing values that may have filtered through to this
4188       ! point.
4189       where(g_qlink(:,1) .le. -9999) g_outInd = 0
4191       ! Allocate output arrays based on size of number of forecast points.
4192       numPtsOut = SUM(g_outInd)
4194       if(numPtsOut .eq. 0) then
4195          ! Write warning message to user showing there are NO forecast points to
4196          ! write. Simply return to the main calling function.
4197          call postDiagMsg(diagFlag,'WARNING: No forecast or gage points found for frxstPtsOut. No file will be created.')
4198          return
4199       endif
4201       ! Allocate output arrays based on number of output forecast points.
4202       allocate(g_STRMFRXSTPTSOut(numPtsOut))
4203       allocate(g_chlonOut(numPtsOut))
4204       allocate(g_chlatOut(numPtsOut))
4205       allocate(g_hlinkOut(numPtsOut))
4206       allocate(g_qlinkOut(numPtsOut,2))
4207       allocate(g_linkidOut(numPtsOut))
4209       ! Subset global arrays for forecast points.
4210       g_STRMFRXSTPTSOut = PACK(g_STRMFRXSTPTS,g_outInd == 1)
4211       g_chlonOut = PACK(g_chlon,g_outInd == 1)
4212       g_chlatOut = PACK(g_chlat,g_outInd == 1)
4213       g_hlinkOut = PACK(g_hlink,g_outInd == 1)
4214       g_qlinkOut(:,1) = PACK(g_qlink(:,1),g_outInd == 1)
4215       g_qlinkOut(:,2) = PACK(g_qlink(:,2),g_outInd == 1)
4216       g_linkidOut = PACK(g_linkid,g_outInd == 1)
4218       ! Open the output file.
4219       open (unit=55,file='frxst_pts_out.txt',status='unknown',position='append')
4221       ! Loop through forecast points and write output.
4222       do iTmp=1,numPtsOut
4223          if(nlst(domainId)%channel_option .eq. 3) then
4224             ! Instead of a gage ID, we are simply going to output the forecast
4225             ! point number assigned during the pre-processing.
4226 117         FORMAT(I8,",",A10,1X,A8,",",I12,",",F10.5,",",F8.5,",",F15.3,",",F18.3,",",F6.3)
4227             write(55,117) seconds_since, nlst(domainId)%olddate(1:18),&
4228                           nlst(domainId)%olddate(12:19),&
4229                           g_STRMFRXSTPTSOut(iTmp),g_chlonOut(iTmp),&
4230                           g_chlatOut(iTmp),g_qlinkOut(iTmp,1),&
4231                           g_qlinkOut(iTmp,1)*35.314666711511576,&
4232                           g_hlinkOut(iTmp)
4233          else
4234             write(55,117) seconds_since, nlst(domainId)%olddate(1:18),&
4235                           nlst(domainId)%olddate(12:19),&
4236                           g_linkidOut(iTmp),g_chlonOut(iTmp),&
4237                           g_chlatOut(iTmp),g_qlinkOut(iTmp,1),&
4238                           g_qlinkOut(iTmp,1)*35.314666711511576,&
4239                           g_hlinkOut(iTmp)
4240          endif
4241       end do
4243       ! Close the output file
4244       close(55)
4245    else
4246       allocate(g_STRMFRXSTPTSOut(1))
4247       allocate(g_chlonOut(1))
4248       allocate(g_chlatOut(1))
4249       allocate(g_hlinkOut(1))
4250       allocate(g_qlinkOut(1,2))
4251       allocate(g_linkidOut(1))
4252    endif
4254    ! Deallocate memory
4255    deallocate(g_STRMFRXSTPTS)
4256    deallocate(g_STRMFRXSTPTSOut)
4257    deallocate(g_chlonOut)
4258    deallocate(g_chlatOut)
4259    deallocate(g_hlinkOut)
4260    deallocate(g_qlinkOut)
4261    deallocate(g_linkidOut)
4262    deallocate(g_chlat)
4263    deallocate(g_chlon)
4264    deallocate(g_hlink)
4265    deallocate(g_qlink)
4266    deallocate(g_outInd)
4267    deallocate(g_linkid)
4269 end subroutine output_frxstPts
4271 !==============================================================================
4272 ! Program Name: output_chanObs_NWM
4273 ! Author(s)/Contact(s): Logan R Karsten <karsten><ucar><edu>
4274 ! Abstract: Output routine for channel points at predefined forecast points.
4275 ! History Log:
4276 ! 9/19/17 -Created, LRK.
4277 ! Usage:
4278 ! Parameters: None.
4279 ! Input Files: None.
4280 ! Output Files: None.
4281 ! Condition codes: None.
4283 ! User controllable options: None.
4284 subroutine output_chanObs_NWM(domainId)
4285    use module_rt_data, only: rt_domain
4286    use config_base, only: nlst
4287    use Module_Date_utilities_rt, only: geth_newdate, geth_idts
4288    use module_NWM_io_dict
4289    use netcdf
4290 #ifdef MPP_LAND
4291    use module_mpp_land
4292    use module_mpp_reachls,  only: ReachLS_write_io
4293 #endif
4294    implicit none
4296    ! Pass in "did" value from hydro driving program.
4297    integer, intent(in) :: domainId
4299    ! Derived types.
4300    type(chObsMeta) :: fileMeta
4302    ! Local variables
4303    logical :: single_output_file, single_output_file_exists
4304    integer :: nudgeFlag, mppFlag, diagFlag
4305    integer :: minSinceSim ! Number of minutes since beginning of simulation.
4306    integer :: minSinceEpoch1 ! Number of minutes from EPOCH to the beginning of the model simulation.
4307    integer :: minSinceEpoch ! Number of minutes from EPOCH to the current model valid time.
4308    integer, dimension(1) :: minSinceEpochVect
4309    character(len=16) :: epochDate ! EPOCH represented as a string.
4310    character(len=16) :: startDate ! Start of model simulation, represented as a string.
4311    character(len=256) :: output_flnm ! CHRTOUT_DOMAIN filename
4312    integer :: iret ! NetCDF return statuses
4313    integer :: ftn ! NetCDF file handle
4314    character(len=256) :: validTime ! Global attribute time string
4315    character(len=256) :: initTime ! Global attribute time string
4316    integer :: dimId(3) ! Dimension ID values created during NetCDF created.
4317    integer :: varId ! Variable ID value created as NetCDF variables are created and populated.
4318    integer :: timeId ! Dimension ID for the time dimension.
4319    integer :: tmpDimId, n_times, n_feature_ids
4320    integer :: refTimeId ! Dimension ID for the reference time dimension.
4321    integer :: coordVarId ! Variable to hold crs
4322    integer :: featureVarId, elevVarId, orderVarId ! Misc NetCDF variable id values
4323    integer :: latVarId, lonVarId ! Lat/lon NetCDF variable id values.
4324    integer :: varRange(2) ! Local storage of min/max valid range values.
4325    real :: varRangeReal(2) ! Local storage of min/max valid range values.
4326    integer :: gSize ! Global size of channel point array.
4327    integer :: numPtsOut ! Number of forecast/gage points
4328    integer :: iTmp, indTmp ! Misc integer values.
4329    integer :: ierr, myId ! MPI return status, process ID
4330    ! Establish local, allocatable arrays
4331    ! These are used to hold global output arrays, and global output arrays after
4332    ! sorting has taken place by ascending feature_id value.
4333    real, allocatable, dimension(:) :: strFlowLocal,velocityLocal
4334    real, allocatable, dimension(:,:) :: g_qlink
4335    integer, allocatable, dimension(:) :: g_order
4336    integer(kind=int64), allocatable, dimension(:) :: g_linkid
4337    real, allocatable, dimension(:) :: g_chlat,g_chlon,g_hlink,g_zelev
4338    real, allocatable, dimension(:,:) :: g_qlinkOut
4339    integer, allocatable, dimension(:) :: g_orderOut
4340    integer(kind=int64), allocatable, dimension(:) :: g_linkidOut
4341    real, allocatable, dimension(:) :: g_chlatOut,g_chlonOut,g_hlinkOut,g_zelevOut
4342    real, allocatable, dimension(:,:) :: varOutReal   ! Array holding output variables in real format
4343    integer, allocatable, dimension(:) :: varOutInt ! Array holding output variables after
4344                                                      ! scale_factor/add_offset
4345                                                      ! have been applied.
4346    integer, allocatable, dimension(:) :: g_STRMFRXSTPTS, g_outInd
4347    integer, allocatable, dimension(:) :: frxstPtsLocal, g_STRMFRXSTPTSOut
4348    character (len=64) :: modelConfigType ! This is character verion (long name) for the io_config_outputs
4350    ! Establish macro variables to hlep guide this subroutine.
4351 #ifdef WRF_HYDRO_NUDGING
4352    nudgeFlag = 1
4353 #else
4354    nudgeFlag = 0
4355 #endif
4357 #ifdef MPP_LAND
4358    mppFlag = 1
4359 #else
4360    mppFlag = 0
4361 #endif
4363 #ifdef HYDRO_D
4364    diagFlag = 1
4365 #else
4366    diagFlag = 0
4367 #endif
4369    if(nlst(domainId)%CHANOBS_DOMAIN .eq. 0) then
4370       ! No output requested here, return to parent calling program/subroutine.
4371       return
4372    endif
4374    ! If we are running over MPI, determine which processor number we are on.
4375    ! If not MPI, then default to 0, which is the I/O ID.
4376    if(mppFlag .eq. 1) then
4377 #ifdef MPP_LAND
4378       call MPI_COMM_RANK( HYDRO_COMM_WORLD, myId, ierr )
4379       call nwmCheck(diagFlag,ierr,'ERROR: Unable to determine MPI process ID.')
4380 #endif
4381    else
4382       myId = 0
4383    endif
4385    ! Initialize NWM dictionary derived type containing all the necessary metadat
4386    ! for the output file.
4387    call initChanObsDict(fileMeta, diagFlag, myId)
4389    ! For now, keep all output variables on, regardless of IOC flag
4390    fileMeta%outFlag(:) = [1]
4392    ! Calculate datetime information.
4393    ! First compose strings of EPOCH and simulation start date.
4394    epochDate = trim("1970-01-01 00:00")
4395    startDate = trim(nlst(domainId)%startdate(1:4)//"-"//&
4396                     nlst(domainId)%startdate(6:7)//&
4397                     &"-"//nlst(domainId)%startdate(9:10)//" "//&
4398                     nlst(domainId)%startdate(12:13)//":"//&
4399                     nlst(domainId)%startdate(15:16))
4400    ! Second, utilize NoahMP date utilities to calculate the number of minutes
4401    ! from EPOCH to the beginning of the model simulation.
4402    call geth_idts(startDate,epochDate,minSinceEpoch1)
4403    ! Third, calculate the number of minutes since the beginning of the
4404    ! simulation.
4405    minSinceSim = int(nlst(1)%out_dt*(rt_domain(1)%out_counts-1))
4406    ! Fourth, calculate the total number of minutes from EPOCH to the current
4407    ! model time step.
4408    minSinceEpoch = minSinceEpoch1 + minSinceSim
4409    minSinceEpochVect(1) = minSinceEpoch
4410    ! Fifth, compose global attribute time strings that will be used.
4411    validTime = trim(nlst(domainId)%olddate(1:4)//'-'//&
4412                     nlst(domainId)%olddate(6:7)//'-'//&
4413                     nlst(domainId)%olddate(9:10)//'_'//&
4414                     nlst(domainId)%olddate(12:13)//':'//&
4415                     nlst(domainId)%olddate(15:16)//&
4416                     &':00')
4417    initTime = trim(nlst(domainId)%startdate(1:4)//'-'//&
4418                   nlst(domainId)%startdate(6:7)//'-'//&
4419                   nlst(domainId)%startdate(9:10)//'_'//&
4420                   nlst(domainId)%startdate(12:13)//':'//&
4421                   nlst(domainId)%startdate(15:16)//&
4422                   &':00')
4423    ! Replace default values in the dictionary.
4424    fileMeta%initTime = trim(initTime)
4425    fileMeta%validTime = trim(validTime)
4427    ! calculate the minimum and maximum time
4428    fileMeta%timeValidMin = minSinceEpoch1 + nlst(1)%out_dt
4429    fileMeta%timeValidMax = minSinceEpoch1 + int(nlst(1)%khour * 60/nlst(1)%out_dt) * nlst(1)%out_dt
4431    ! calculate total_valid_time
4432    fileMeta%totalValidTime = int(nlst(1)%khour * 60 / nlst(1)%out_dt)  ! # number of valid time (#of output files)
4434    ! Compose output file name.
4435    ! 0 means do not split = single output file
4436    single_output_file = nlst(domainId)%split_output_count .eq. 0
4437    if(single_output_file) then
4438       write(output_flnm,'("CHANOBS_DOMAIN",I1,".nc")') nlst(domainId)%igrid
4439    else
4440       write(output_flnm,'(A12,".CHANOBS_DOMAIN",I1)')nlst(domainId)%olddate(1:4)//&
4441            nlst(domainId)%olddate(6:7)//nlst(domainId)%olddate(9:10)//&
4442            nlst(domainId)%olddate(12:13)//nlst(domainId)%olddate(15:16),&
4443            nlst(domainId)%igrid
4444    endif
4446    ! First step is to allocate a global array of index values. This "index"
4447    ! array will be used to subset after collection has taken place. Also,
4448    ! the sum of this array will be used to determine the size of the output
4449    ! arrays.
4450    if(mppFlag .eq. 1) then
4451       if(nlst(domainId)%channel_option .ne. 3) then
4452          gSize = rt_domain(domainId)%gnlinksl
4453       else
4454          gSize = rt_domain(domainId)%gnlinks
4455       endif
4457       if(myId .eq. 0) then
4458          allocate(g_STRMFRXSTPTS(gSize))
4459          allocate(g_outInd(gSize))
4460          allocate(g_qlink(gSize,2))
4461          allocate(g_chlat(gSize))
4462          allocate(g_chlon(gSize))
4463          allocate(g_hlink(gSize))
4464          allocate(g_zelev(gSize))
4465          allocate(g_order(gSize))
4466          allocate(g_linkid(gSize))
4467       else
4468          allocate(g_STRMFRXSTPTS(1))
4469          allocate(g_outInd(1))
4470          allocate(g_qlink(1,2))
4471          allocate(g_chlat(1))
4472          allocate(g_chlon(1))
4473          allocate(g_hlink(1))
4474          allocate(g_zelev(1))
4475          allocate(g_order(1))
4476          allocate(g_linkid(1))
4477       endif
4479       ! Initialize the index array to 0
4480       g_outInd = 0
4482       ! Allocate local streamflow arrays. We need to do a check to
4483       ! for lake_type 2. However, we cannot set the values in the global array
4484       ! to missing as this causes the model to crash.
4485       allocate(strFlowLocal(RT_DOMAIN(domainId)%NLINKS))
4486       allocate(frxstPtsLocal(RT_DOMAIN(domainId)%NLINKS))
4487       strFlowLocal = RT_DOMAIN(domainId)%QLINK(:,1)
4488       frxstPtsLocal = rt_domain(domainId)%STRMFRXSTPTS
4490       ! Loop through all the local links on this processor. For lake_type
4491       ! of 2, we need to manually set the streamflow values
4492       ! to the model NDV value.
4493       if (RT_DOMAIN(domainId)%NLAKES .gt. 0) then
4494          do iTmp=1,RT_DOMAIN(domainId)%NLINKS
4495             if (RT_DOMAIN(domainId)%TYPEL(iTmp) .eq. 2) then
4496                !strFlowLocal(iTmp) = fileMeta%modelNdv
4497                strFlowLocal(iTmp) = -9.E15
4498                frxstPtsLocal(iTmp) = -9999
4499             endif
4500          end do
4501       endif
4503       ! Collect arrays from various processors
4504       if(nlst(domainId)%channel_option .eq. 3) then
4505          call write_chanel_int(frxstPtsLocal,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_STRMFRXSTPTS)
4506          call write_chanel_real(strFlowLocal,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_qlink(:,1))
4507          call write_chanel_real(RT_DOMAIN(domainId)%QLINK(:,2),rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_qlink(:,2))
4508          call write_chanel_real(RT_DOMAIN(domainId)%CHLAT,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_chlat)
4509          call write_chanel_real(RT_DOMAIN(domainId)%CHLON,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_chlon)
4510          call write_chanel_real(RT_DOMAIN(domainId)%HLINK,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_hlink)
4511          call write_chanel_int8(RT_DOMAIN(domainId)%linkid,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_linkid)
4512          call write_chanel_int(RT_DOMAIN(domainId)%ORDER,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_order)
4513          call write_chanel_real(RT_DOMAIN(domainId)%ZELEV,rt_domain(domainId)%map_l2g,gSize,rt_domain(domainId)%nlinks,g_zelev)
4514       else
4515          call ReachLS_write_io(frxstPtsLocal,g_STRMFRXSTPTS)
4516          call ReachLS_write_io(strFlowLocal,g_qlink(:,1))
4517          call ReachLS_write_io(RT_DOMAIN(domainId)%QLINK(:,2),g_qlink(:,2))
4518          call ReachLS_write_io(RT_DOMAIN(domainId)%ORDER,g_order)
4519          call ReachLS_write_io(RT_DOMAIN(domainId)%linkid,g_linkid)
4520          call ReachLS_write_io(RT_DOMAIN(domainId)%CHLAT,g_chlat)
4521          call ReachLS_write_io(RT_DOMAIN(domainId)%CHLON,g_chlon)
4522          call ReachLS_write_io(RT_DOMAIN(domainId)%ZELEV,g_zelev)
4523          call ReachLS_write_io(RT_DOMAIN(domainId)%HLINK,g_hlink)
4524       endif
4526       deallocate(strFlowLocal)
4527       deallocate(frxstPtsLocal)
4529    else
4530       ! Running sequentially on a single processor.
4531       gSize = rt_domain(domainId)%nlinks
4532       allocate(g_STRMFRXSTPTS(gSize))
4533       allocate(g_outInd(gSize))
4534       allocate(g_chlon(gSize))
4535       allocate(g_chlat(gSize))
4536       allocate(g_hlink(gSize))
4537       allocate(g_qlink(gSize,2))
4538       allocate(g_linkid(gSize))
4539       allocate(g_order(gSize))
4540       allocate(g_zelev(gSize))
4542       ! Initialize the index array to 0
4543       g_outInd = 0
4545       g_STRMFRXSTPTS = rt_domain(domainId)%STRMFRXSTPTS
4546       g_chlon = RT_DOMAIN(domainId)%CHLON
4547       g_chlat = RT_DOMAIN(domainId)%CHLAT
4548       g_hlink = RT_DOMAIN(domainId)%HLINK
4549       g_qlink = RT_DOMAIN(domainId)%QLINK
4550       g_linkid = RT_DOMAIN(domainId)%linkid
4551       g_order = RT_DOMAIN(domainId)%ORDER
4552       g_zelev = RT_DOMAIN(domainId)%ZELEV
4553    endif
4555    if(myId .eq. 0) then
4556       ! Set index values to 1 where we have forecast points.
4557       if(nlst(domainId)%channel_option .eq. 3) then
4558          where(g_STRMFRXSTPTS .ne. -9999) g_outInd = 1
4559       endif
4561       if(nlst(domainId)%channel_option .ne. 3) then
4562          ! Check to see if we have any gages that need to be added for
4563          ! reach-based routing.
4564          call checkRouteGages(diagFlag,gSize,g_outInd)
4565       endif
4567       ! Filter out any missing values that may have filtered through to this
4568       ! point.
4569       where(g_qlink(:,1) .le. -9999) g_outInd = 0
4571       ! Allocate output arrays based on size of number of forecast points.
4572       numPtsOut = sum(g_outInd)
4574       if(numPtsOut .eq. 0) then
4575          ! Write warning message to user showing there are NO forecast points to
4576          ! write. Simply return to the main calling function.
4577          call postDiagMsg(diagFlag,'WARNING: No forecast or gage points found for CHANOBS. No file will be created.')
4578          return
4579       endif
4581       ! Allocate output arrays based on number of output forecast points.
4582       allocate(g_STRMFRXSTPTSOut(numPtsOut))
4583       allocate(g_chlonOut(numPtsOut))
4584       allocate(g_chlatOut(numPtsOut))
4585       allocate(g_hlinkOut(numPtsOut))
4586       allocate(g_qlinkOut(numPtsOut,2))
4587       allocate(g_linkidOut(numPtsOut))
4588       allocate(g_orderOut(numPtsOut))
4589       allocate(g_zelevOut(numPtsOut))
4591       ! Subset global arrays for forecast points.
4592       g_STRMFRXSTPTSOut = pack(g_STRMFRXSTPTS,g_outInd == 1)
4593       g_chlonOut = pack(g_chlon,g_outInd == 1)
4594       g_chlatOut = pack(g_chlat,g_outInd == 1)
4595       g_hlinkOut = pack(g_hlink,g_outInd == 1)
4596       g_qlinkOut(:,1) = pack(g_qlink(:,1),g_outInd == 1)
4597       g_qlinkOut(:,2) = pack(g_qlink(:,2),g_outInd == 1)
4598       g_linkidOut = pack(g_linkid,g_outInd == 1)
4599       g_orderOut = pack(g_order,g_outInd == 1)
4600       g_zelevOut = pack(g_zelev,g_outInd == 1)
4602       allocate(varOutReal(fileMeta%numVars,numPtsOut))
4603       allocate(varOutInt(numPtsOut))
4605       varOutReal(1,:) = g_qlinkOut(:,1)
4607       ! Mask out missing values
4608       where ( varOutReal == fileMeta%modelNdv ) varOutReal = -9999.0
4610       ! call the GetModelConfigType function
4611       modelConfigType = GetModelConfigType(nlst(1)%io_config_outputs)
4613       ! Create NetCDF for output?
4615       inquire(file=trim(output_flnm), exist=single_output_file_exists)
4616       if ((.not. single_output_file) .or. (.not. single_output_file_exists)) then
4617          iret = nf90_create(trim(output_flnm), cmode=nf90_netcdf4, ncid=ftn)
4618          call nwmCheck(diagFlag,iret,'ERROR: Unable to create CHANOBS NetCDF file.')
4620       ! Write global attributes.
4621          iret = nf90_put_att(ftn,NF90_GLOBAL,"TITLE",trim(fileMeta%title))
4622          call nwmCheck(diagFlag,iret,'ERROR: Unable to create TITLE attribute')
4623          iret = nf90_put_att(ftn,NF90_GLOBAL,"compiler_version",compiler_version())
4624          call nwmCheck(diagFlag,iret,'ERROR: Unable to create compiler_version attribute')
4625          iret = nf90_put_att(ftn,NF90_GLOBAL,"featureType",trim(fileMeta%fType))
4626          call nwmCheck(diagFlag,iret,'ERROR: Unable to create featureType attribute')
4627          iret = nf90_put_att(ftn,NF90_GLOBAL,"proj4",trim(fileMeta%proj4))
4628          call nwmCheck(diagFlag,iret,'ERROR: Unable to create proj4 attribute')
4629          iret = nf90_put_att(ftn,NF90_GLOBAL,"model_initialization_time",trim(fileMeta%initTime))
4630          call nwmCheck(diagFlag,iret,'ERROR: Unable to create model init attribute')
4631          iret = nf90_put_att(ftn,NF90_GLOBAL,"station_dimension",trim(fileMeta%stDim))
4632          call nwmCheck(diagFlag,iret,'ERROR: Unable to create st. dimension attribute')
4633          iret = nf90_put_att(ftn,NF90_GLOBAL,"model_output_valid_time",trim(fileMeta%validTime))
4634          call nwmCheck(diagFlag,iret,'ERROR: Unable to create model valid attribute')
4635          iret = nf90_put_att(ftn,NF90_GLOBAL,"model_total_valid_times",fileMeta%totalValidTime)
4636          call nwmCheck(diagFlag,iret,'ERROR: Unable to create model total valid times attribute')
4637          iret = nf90_put_att(ftn,NF90_GLOBAL,"stream_order_output",fileMeta%stOrder)
4638          call nwmCheck(diagFlag,iret,'ERROR: Unable to create order attribute')
4639          iret = nf90_put_att(ftn,NF90_GLOBAL,"cdm_datatype",trim(fileMeta%cdm))
4640          call nwmCheck(diagFlag,iret,'ERROR: Unable to create CDM attribute')
4641          !iret = nf90_put_att(ftn,NF90_GLOBAL,"esri_pe_string",trim(fileMeta%esri))
4642          !call nwmCheck(diagFlag,iret,'ERROR: Unable to create ESRI attribute')
4643          iret = nf90_put_att(ftn,NF90_GLOBAL,"Conventions",trim(fileMeta%conventions))
4644          call nwmCheck(diagFlag,iret,'ERROR: Unable to create conventions attribute')
4645          iret = nf90_put_att(ftn,NF90_GLOBAL,"code_version",trim(get_code_version()))
4646          call nwmCheck(diagFlag,iret,'ERROR: Unable to create code_version attribute')
4647 #ifdef NWM_META
4648          iret = nf90_put_att(ftn,NF90_GLOBAL,"NWM_version_number",trim(get_nwm_version()))
4649          call nwmCheck(diagFlag,iret,'ERROR: Unable to create NWM_version_number attribute')
4650 #endif
4651          iret = nf90_put_att(ftn,NF90_GLOBAL,"model_output_type",trim(fileMeta%modelOutputType))
4652          call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_output_type attribute')
4653          iret = nf90_put_att(ftn,NF90_GLOBAL,"model_configuration",modelConfigType)
4654          call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_configuration attribute')
4656          ! Create global attributes specific to running output through the
4657          ! channel-only configuration of the model.
4658          iret = nf90_put_att(ftn,NF90_GLOBAL,"dev_OVRTSWCRT",nlst(domainId)%OVRTSWCRT)
4659          call nwmCheck(diagFlag,iret,'ERROR: Unable to create dev_OVRTSWCRT attribute')
4660          iret = nf90_put_att(ftn,NF90_GLOBAL,"dev_NOAH_TIMESTEP",int(nlst(domainId)%dt))
4661          call nwmCheck(diagFlag,iret,'ERROR: Unable to create dev_NOAH_TIMESTEP attribute')
4662          iret = nf90_put_att(ftn,NF90_GLOBAL,"dev_channel_only",nlst(domainId)%channel_only)
4663          call nwmCheck(diagFlag,iret,'ERROR: Unable to create dev_channel_only attribute')
4664          iret = nf90_put_att(ftn,NF90_GLOBAL,"dev_channelBucket_only",nlst(domainId)%channelBucket_only)
4665          call nwmCheck(diagFlag,iret,'ERROR: Unable to create dev_channelBucket_only attribute')
4666          iret = nf90_put_att(ftn,NF90_GLOBAL,'dev','dev_ prefix indicates development/internal meta data')
4667          call nwmCheck(diagFlag,iret,'ERROR: Unable to create dev attribute')
4669          ! Create dimensions
4670          iret = nf90_def_dim(ftn,"feature_id",numPtsOut,dimId(1))
4671          call nwmCheck(diagFlag,iret,'ERROR: Unable to create feature_id dimension')
4672          iret = nf90_def_dim(ftn,"time",NF90_UNLIMITED,dimId(2))
4673          call nwmCheck(diagFlag,iret,'ERROR: Unable to create time dimension')
4674          iret = nf90_def_dim(ftn,"reference_time",1,dimId(3))
4675          call nwmCheck(diagFlag,iret,'ERROR: Unable to create reference_time dimension')
4677          ! Create and populate reference_time and time variables.
4678          iret = nf90_def_var(ftn,"time",nf90_int,dimId(2),timeId)
4679          call nwmCheck(diagFlag,iret,'ERROR: Unable to create time variable')
4680          iret = nf90_put_att(ftn,timeId,'long_name',trim(fileMeta%timeLName))
4681          call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into time variable')
4682          iret = nf90_put_att(ftn,timeId,'standard_name',trim(fileMeta%timeStName))
4683          call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into time variable')
4684          iret = nf90_put_att(ftn,timeId,'units',trim(fileMeta%timeUnits))
4685          call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into time variable')
4686          if(.not. single_output_file) then
4687             iret = nf90_put_att(ftn,timeId,'valid_min',fileMeta%timeValidMin)
4688             call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_min attribute into time variable')
4689             iret = nf90_put_att(ftn,timeId,'valid_max',fileMeta%timeValidMax)
4690             call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_max attribute into time variable')
4691          endif
4693          iret = nf90_def_var(ftn,"reference_time",nf90_int,dimId(3),refTimeId)
4694          call nwmCheck(diagFlag,iret,'ERROR: Unable to create reference_time variable')
4695          iret = nf90_put_att(ftn,refTimeId,'long_name',trim(fileMeta%rTimeLName))
4696          call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into reference_time variable')
4697          iret = nf90_put_att(ftn,refTimeId,'standard_name',trim(fileMeta%rTimeStName))
4698          call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into reference_time variable')
4699          iret = nf90_put_att(ftn,refTimeId,'units',trim(fileMeta%rTimeUnits))
4700          call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into reference_time variable')
4702          ! Create a crs variable.
4703          ! NOTE - For now, we are hard-coding in for lat/lon points. However, this
4704          ! may be more flexible in future iterations.
4705          iret = nf90_def_var(ftn,'crs',nf90_char,varid=coordVarId)
4706          call nwmCheck(diagFlag,iret,'ERROR: Unable to create crs variable.')
4707          iret = nf90_put_att(ftn,coordVarId,'transform_name','latitude longitude')
4708          call nwmCheck(diagFlag,iret,'ERROR: Unable to place transform_name attribute into crs variable.')
4709          iret = nf90_put_att(ftn,coordVarId,'grid_mapping_name','latitude longitude')
4710          call nwmCheck(diagFlag,iret,'ERROR: Unable to place grid_mapping_name attribute into crs variable.')
4711          iret = nf90_put_att(ftn,coordVarId,'esri_pe_string','GEOGCS["GCS_WGS_1984",DATUM["D_WGS_1984",&
4712               &SPHEROID["WGS_1984",6378137.0,298.257223563]],PRIMEM["Greenwich",0.0],UNIT["Degree",&
4713               &0.0174532925199433]];-400 -400 1000000000;&
4714               &-100000 10000;-100000 10000;8.98315284119521E-09;0.001;0.001;IsHighPrecision')
4715          call nwmCheck(diagFlag,iret,'ERROR: Unable to place esri_pe_string into crs variable.')
4716          iret = nf90_put_att(ftn,coordVarId,'spatial_ref','GEOGCS["GCS_WGS_1984",DATUM["D_WGS_1984",&
4717               &SPHEROID["WGS_1984",6378137.0,298.257223563]],PRIMEM["Greenwich",0.0],UNIT["Degree",&
4718               &0.0174532925199433]];-400 -400 1000000000;&
4719               &-100000 10000;-100000 10000;8.98315284119521E-09;0.001;0.001;IsHighPrecision')
4720          call nwmCheck(diagFlag,iret,'ERROR: Unable to place spatial_ref into crs variable.')
4721          iret = nf90_put_att(ftn,coordVarId,'long_name','CRS definition')
4722          call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name into crs variable.')
4723          iret = nf90_put_att(ftn,coordVarId,'longitude_of_prime_meridian',0.0)
4724          call nwmCheck(diagFlag,iret,'ERROR: Unable to place longitude_of_prime_meridian into crs variable.')
4725          iret = nf90_put_att(ftn,coordVarId,'_CoordinateAxes','latitude longitude')
4726          call nwmCheck(diagFlag,iret,'ERROR: Unable to place _CoordinateAxes into crs variable.')
4727          iret = nf90_put_att(ftn,coordVarId,'semi_major_axis',6378137.0)
4728          call nwmCheck(diagFlag,iret,'ERROR: Unable to place semi_major_axis into crs variable.')
4729          iret = nf90_put_att(ftn,coordVarId,'semi_minor_axis',6356752.31424518)
4730          call nwmCheck(diagFlag,iret,'ERROR: Unable to place semi_minor_axis into crs variable.')
4731          iret = nf90_put_att(ftn,coordVarId,'inverse_flattening',298.257223563)
4732          call nwmCheck(diagFlag,iret,'ERROR: Unable to place inverse_flattening into crs variable.')
4734          ! Create feature_id variable
4735          iret = nf90_def_var(ftn,"feature_id",nf90_int64,dimId(1),featureVarId)
4736          call nwmCheck(diagFlag,iret,'ERROR: Unable to create feature_id variable.')
4737          ! Specify these attributes based on channel routing methods specified by
4738          ! user.
4739          if(nlst(domainId)%channel_option .eq. 3) then
4740             iret = nf90_put_att(ftn,featureVarId,'long_name','User Specified Forecast Points')
4741             call nwmCheck(diagFlag,iret,'ERROR: Uanble to place long_name attribute into feature_id variable')
4742             iret = nf90_put_att(ftn,featureVarId,'comment','Forecast Points Specified in Fulldom file')
4743             call nwmCheck(diagFlag,iret,'ERROR: Unable to place comment attribute into feature_id variable')
4744          else
4745             iret = nf90_put_att(ftn,featureVarId,'long_name',trim(fileMeta%featureIdLName))
4746             call nwmCheck(diagFlag,iret,'ERROR: Uanble to place long_name attribute into feature_id variable')
4747             iret = nf90_put_att(ftn,featureVarId,'comment',trim(fileMeta%featureIdComment))
4748             call nwmCheck(diagFlag,iret,'ERROR: Unable to place comment attribute into feature_id variable')
4749          endif
4750          iret = nf90_put_att(ftn,featureVarId,'cf_role',trim(fileMeta%cfRole))
4751          call nwmCheck(diagFlag,iret,'ERROR: Unable to place cf_role attribute into feature_id variable')
4753          ! Create channel lat/lon variables
4754          iret = nf90_def_var(ftn,"latitude",nf90_float,dimId(1),latVarId)
4755          call nwmCheck(diagFlag,iret,'ERROR: Unable to create latitude variable.')
4756          iret = nf90_put_att(ftn,latVarId,'long_name',trim(fileMeta%latLName))
4757          call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into latitude variable')
4758          iret = nf90_put_att(ftn,latVarId,'standard_name',trim(fileMeta%latStName))
4759          call nwmCheck(diagFlag,iret,'ERROR: Unable to place stndard_name attribute into latitude variable')
4760          iret = nf90_put_att(ftn,latVarId,'units',trim(fileMeta%latUnits))
4761          call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into latitude variable')
4762          iret = nf90_def_var(ftn,"longitude",nf90_float,dimId(1),lonVarId)
4763          call nwmCheck(diagFlag,iret,'ERROR: Unable to create longitude variable.')
4764          iret = nf90_put_att(ftn,lonVarId,'long_name',trim(fileMeta%lonLName))
4765          call nwmCheck(diagFlag,iret,'ERROR: Uanble to place long_name attribute into longitude variable')
4766          iret = nf90_put_att(ftn,lonVarId,'standard_name',trim(fileMeta%lonStName))
4767          call nwmCheck(diagFlag,iret,'ERROR: Unable to place stndard_name attribute into longitude variable')
4768          iret = nf90_put_att(ftn,lonVarId,'units',trim(fileMeta%lonUnits))
4769          call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into longitude variable')
4771          ! Create channel order variable
4772          iret = nf90_def_var(ftn,"order",nf90_int,dimId(1),orderVarId)
4773          call nwmCheck(diagFlag,iret,'ERROR: Unable to create order variable.')
4774          iret = nf90_put_att(ftn,orderVarId,'long_name',trim(fileMeta%orderLName))
4775          call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into order variable')
4776          iret = nf90_put_att(ftn,orderVarId,'standard_name',trim(fileMeta%orderStName))
4777          call nwmCheck(diagFlag,iret,'ERROR: Unable to place stndard_name attribute into order variable')
4779          ! Create channel elevation variable
4780          iret = nf90_def_var(ftn,"elevation",nf90_float,dimId(1),elevVarId)
4781          call nwmCheck(diagFlag,iret,'ERROR: Unable to create elevation variable.')
4782          iret = nf90_put_att(ftn,elevVarId,'long_name',trim(fileMeta%elevLName))
4783          call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into elevation variable')
4784          iret = nf90_put_att(ftn,elevVarId,'standard_name',trim(fileMeta%elevStName))
4785          call nwmCheck(diagFlag,iret,'ERROR: Unable to place stndard_name attribute into elevation variable')
4787          ! Define deflation levels for these meta-variables. For now, we are going
4788          ! to default to a compression level of 2. Only compress if io_form_outputs is set to 1.
4789          if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
4790             iret = nf90_def_var_deflate(ftn,timeId,0,1,2)
4791             call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for time.')
4792             iret = nf90_def_var_deflate(ftn,featureVarId,0,1,2)
4793             call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for feature_id.')
4794             iret = nf90_def_var_deflate(ftn,refTimeId,0,1,2)
4795             call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for reference_time.')
4796             iret = nf90_def_var_deflate(ftn,latVarId,0,1,2)
4797             call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for latitude.')
4798             iret = nf90_def_var_deflate(ftn,lonVarId,0,1,2)
4799             call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for longitude.')
4800             iret = nf90_def_var_deflate(ftn,orderVarId,0,1,2)
4801             call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for order.')
4802             iret = nf90_def_var_deflate(ftn,elevVarId,0,1,2)
4803             call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for elevation.')
4804          endif
4806          ! Allocate memory for the output variables, then place the real output
4807          ! variables into a single array. This array will be accessed throughout
4808          ! the output looping below for conversion to compressed integer values.
4809          ! Loop through and create each output variable, create variable
4810          ! attributes, and insert data.
4811          do iTmp=1,fileMeta%numVars
4812             if(fileMeta%outFlag(iTmp) .eq. 1) then
4813                if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
4814                   iret = nf90_def_var( &
4815                        ftn, trim(fileMeta%varNames(iTmp)), nf90_int, &
4816                        (/ dimId(1), dimId(2) /), varId)
4817                else
4818                   iret = nf90_def_var( &
4819                        ftn, trim(fileMeta%varNames(iTmp)), nf90_float, &
4820                        (/ dimId(1), dimId(2) /), varId)
4821                endif
4822                call nwmCheck(diagFlag,iret,'ERROR: Unable to create variable:'//trim(fileMeta%varNames(iTmp)))
4824                ! Extract valid range into a 1D array for placement.
4825                varRange(1) = fileMeta%validMinComp(iTmp)
4826                varRange(2) = fileMeta%validMaxComp(iTmp)
4827                varRangeReal(1) = real(fileMeta%validMinDbl(iTmp))
4828                varRangeReal(2) = real(fileMeta%validMaxDbl(iTmp))
4830                ! Establish a compression level for the variables. For now we are
4831                ! using a compression level of 2. In addition, we are choosing to turn the
4832                ! shuffle filter off for now. Kelley Eicher did some testing with this and
4833                ! determined that the benefit wasn't worth the extra time spent
4834                ! writing output. Only compress if io_form_outputs is set to 1.
4835                if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
4836                   iret = nf90_def_var_deflate(ftn,varId,0,1,2)
4837                   call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression for: '//trim(fileMeta%varNames(iTmp)))
4838                endif
4840                ! Create variable attributes
4841                iret = nf90_put_att(ftn,varId,'long_name',trim(fileMeta%longName(iTmp)))
4842                call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into variable '//trim(fileMeta%varNames(iTmp)))
4843                iret = nf90_put_att(ftn,varId,'units',trim(fileMeta%units(iTmp)))
4844                call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into variable '//trim(fileMeta%varNames(iTmp)))
4845                iret = nf90_put_att(ftn,varId,'coordinates',trim(fileMeta%coordNames(iTmp)))
4846                call nwmCheck(diagFlag,iret,'ERROR: Unable to place coordinates attribute into variable '//trim(fileMeta%varNames(iTmp)))
4847                iret = nf90_put_att(ftn,varId,'grid_mapping','crs')
4848                call nwmCheck(diagFlag,iret,'ERROR: Unable to place grid_mapping attribute into variable '//trim(fileMeta%varNames(iTmp)))
4849                if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
4850                   iret = nf90_put_att(ftn,varId,'_FillValue',fileMeta%fillComp(iTmp))
4851                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
4852                   iret = nf90_put_att(ftn,varId,'missing_value',fileMeta%missingComp(iTmp))
4853                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
4854                   iret = nf90_put_att(ftn,varId,'scale_factor',fileMeta%scaleFactor(iTmp))
4855                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place scale_factor attribute into variable '//trim(fileMeta%varNames(iTmp)))
4856                   iret = nf90_put_att(ftn,varId,'add_offset',fileMeta%addOffset(iTmp))
4857                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place add_offset attribute into variable '//trim(fileMeta%varNames(iTmp)))
4858                   iret = nf90_put_att(ftn,varId,'valid_range',varRange)
4859                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
4860                else
4861                   iret = nf90_put_att(ftn,varId,'_FillValue',fileMeta%fillReal(iTmp))
4862                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
4863                   iret = nf90_put_att(ftn,varId,'missing_value',fileMeta%missingReal(iTmp))
4864                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
4865                   iret = nf90_put_att(ftn,varId,'valid_range',varRangeReal)
4866                   call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
4867                endif
4868             endif
4869          end do
4871          ! Remove NetCDF file from definition mode.
4872          iret = nf90_enddef(ftn)
4873          call nwmCheck(diagFlag,iret,'ERROR: Unable to take CHANOBS file out of definition mode')
4875       else
4877          iret = nf90_open(trim(output_flnm), nf90_write, ftn)
4878          call nwmCheck(diagFlag,iret,'ERROR: Unable to open CHANOBS_DOMAIN.nc file.')
4880       endif ! if((.not. single_output_file) .or. (.not. single_output_file_exists)) then
4882       ! Time: length and write
4883       iret =  nf90_inq_dimid(ftn, 'time', tmpDimId)
4884       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate time dimension.')
4885       iret = nf90_inquire_dimension(ftn, tmpDimId, len=n_times)
4886       call nwmCheck(diagFlag,iret,'ERROR: Unable to to get length of time dimension.')
4888       iret = nf90_inq_varid(ftn, 'time', varId)
4889       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate time variable')
4890       iret = nf90_put_var(ftn, varId, minSinceEpochVect, start=(/n_times+1/), count = (/1/))
4891       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into time variable')
4893       ! Feature_id: just length
4894       iret =  nf90_inq_dimid(ftn, 'feature_id', tmpDimId)
4895       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate time dimension.')
4896       iret = nf90_inquire_dimension(ftn, tmpDimId, len=n_feature_ids)
4897       call nwmCheck(diagFlag,iret,'ERROR: Unable to to get length of time dimension.')
4899       ! Loop through all possible output variables, and convert floating points
4900       ! to integers via prescribed scale_factor/add_offset, then write to the
4901       ! NetCDF variable.
4902       do iTmp=1,fileMeta%numVars
4903          if(fileMeta%outFlag(iTmp) .eq. 1) then
4904             ! We are outputing this variable.
4905             ! Convert reals to integer. If this is time zero, check to see if we
4906             ! need to convert all data to NDV
4907             if(minSinceSim .eq. 0 .and. fileMeta%timeZeroFlag(iTmp) .eq. 0) then
4908                varOutInt(:) = fileMeta%fillComp(iTmp)
4909                varOutReal(iTmp,:) = fileMeta%fillReal(iTmp)
4910             else
4911                varOutInt(:) = NINT((varOutReal(iTmp,:)-fileMeta%addOffset(iTmp))/fileMeta%scaleFactor(iTmp))
4912             endif
4913             ! Get NetCDF variable id.
4914             iret = nf90_inq_varid(ftn,trim(fileMeta%varNames(iTmp)),varId)
4915             call nwmCheck(diagFlag,iret,'ERROR: Unable to find variable ID for var: '//trim(fileMeta%varNames(iTmp)))
4916             ! Put data into NetCDF file
4917             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
4918                iret = nf90_put_var(ftn, varId, &
4919                     reshape(varOutInt, (/n_feature_ids, 1/)), &
4920                     start=(/1, n_times+1/), count=(/n_feature_ids, 1/))
4921             else
4922                iret = nf90_put_var( &
4923                     ftn, varId, &
4924                     reshape(varOutReal(iTmp,:), (/n_feature_ids, 1/)), &
4925                     start=(/1, n_times+1/), count=(/n_feature_ids, 1/))
4926             endif
4927             call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into output variable: '//trim(fileMeta%varNames(iTmp)))
4928          endif
4929       end do
4931       ! Place link ID values into the NetCDF file
4932       iret = nf90_inq_varid(ftn,'feature_id',varId)
4933       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate feature_id in NetCDF file.')
4934       ! If we are running gridded routing, output the user-specified forecast
4935       ! point numbers. Otherwise, output the reach ID values.
4936       if(nlst(domainId)%channel_option .eq. 3) then
4937          iret = nf90_put_var(ftn,varId,g_STRMFRXSTPTSOut)
4938          call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into feature_id output variable.')
4939       else
4940          iret = nf90_put_var(ftn,varId,g_linkidOut)
4941          call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into feature_id output variable.')
4942       endif
4944       iret = nf90_inq_varid(ftn,'latitude',varId)
4945       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate latitude in NetCDF file.')
4946       iret = nf90_put_var(ftn,varId,g_chlatOut)
4947       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into latitude output variable.')
4949       iret = nf90_inq_varid(ftn,'longitude',varId)
4950       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate longitude in NetCDF file.')
4951       iret = nf90_put_var(ftn,varId,g_chlonOut)
4952       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into longitude output variable.')
4954       iret = nf90_inq_varid(ftn,'order',varId)
4955       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate order in NetCDF file.')
4956       iret = nf90_put_var(ftn,varId,g_orderOut)
4957       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into order output variable.')
4959       iret = nf90_inq_varid(ftn,'elevation',varId)
4960       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate elevation in NetCDF file.')
4961       iret = nf90_put_var(ftn,varId,g_zelevOut)
4962       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into elevation output variable.')
4964       ! Place reference time value
4965       iret = nf90_inq_varid(ftn,'reference_time',varId)
4966       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate reference_time variable')
4967       iret = nf90_put_var(ftn,varId,minSinceEpoch1)
4968       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into reference_time variable')
4970       ! Close the output file
4971       iret = nf90_close(ftn)
4972       call nwmCheck(diagFlag,iret,'ERROR: Unable to close CHANOBS file.')
4974       deallocate(varOutReal)
4975       deallocate(varOutInt)
4977    else
4979       allocate(g_STRMFRXSTPTSOut(1))
4980       allocate(g_chlonOut(1))
4981       allocate(g_chlatOut(1))
4982       allocate(g_hlinkOut(1))
4983       allocate(g_qlinkOut(1,2))
4984       allocate(g_linkidOut(1))
4985       allocate(g_zelevOut(1))
4986       allocate(g_orderOut(1))
4988    endif
4990    ! Deallocate memory
4991    deallocate(g_STRMFRXSTPTS)
4992    deallocate(g_STRMFRXSTPTSOut)
4993    deallocate(g_chlonOut)
4994    deallocate(g_chlatOut)
4995    deallocate(g_hlinkOut)
4996    deallocate(g_qlinkOut)
4997    deallocate(g_linkidOut)
4998    deallocate(g_zelevOut)
4999    deallocate(g_orderOut)
5000    deallocate(g_chlat)
5001    deallocate(g_chlon)
5002    deallocate(g_hlink)
5003    deallocate(g_qlink)
5004    deallocate(g_outInd)
5005    deallocate(g_linkid)
5006    deallocate(g_zelev)
5007    deallocate(g_order)
5009 end subroutine output_chanObs_NWM
5011 !==============================================================================
5012 ! Program Name: output_gw_NWM
5013 ! Author(s)/Contact(s): Logan R Karsten <karsten><ucar><edu>
5014 ! Abstract: Output routine for groundwater buckets.
5015 ! History Log:
5016 ! 9/22/17 -Created, LRK.
5017 ! Usage:
5018 ! Parameters: None.
5019 ! Input Files: None.
5020 ! Output Files: None.
5021 ! Condition codes: None.
5023 ! User controllable options: None.
5024 subroutine output_gw_NWM(domainId,iGrid)
5025    use module_rt_data, only: rt_domain
5026    use config_base, only: nlst
5027    use Module_Date_utilities_rt, only: geth_newdate, geth_idts
5028    use module_NWM_io_dict
5029    use netcdf
5030 #ifdef MPP_LAND
5031    use MODULE_mpp_GWBUCKET, only: gw_write_io_real, gw_write_io_int
5032    use module_mpp_land
5033    use module_mpp_reachls,  only: ReachLS_write_io
5034 #endif
5035    implicit none
5037    integer, intent(in) :: domainId
5038    integer, intent(in) :: iGrid
5040    ! Derived types.
5041    type(gwMeta) :: fileMeta
5043    ! Local variables
5044    integer :: mppFlag, diagFlag
5045    integer :: minSinceSim ! Number of minutes since beginning of simulation.
5046    integer :: minSinceEpoch1 ! Number of minutes from EPOCH to the beginning of the model simulation.
5047    integer :: minSinceEpoch ! Number of minutes from EPOCH to the current model valid time.
5048    character(len=16) :: epochDate ! EPOCH represented as a string.
5049    character(len=16) :: startDate ! Start of model simulation, represented as a string.
5050    character(len=256) :: output_flnm ! CHRTOUT_DOMAIN filename
5051    integer :: iret ! NetCDF return statuses
5052    integer :: ftn ! NetCDF file handle
5053    character(len=256) :: validTime ! Global attribute time string
5054    character(len=256) :: initTime ! Global attribute time string
5055    integer :: dimId(3) ! Dimension ID values created during NetCDF created.
5056    integer :: varId ! Variable ID value created as NetCDF variables are created and populated.
5057    integer :: timeId ! Dimension ID for the time dimension.
5058    integer :: refTimeId ! Dimension ID for the reference time dimension.
5059    integer :: featureVarId ! feature_id NetCDF variable ID
5060    integer :: varRange(2) ! Local storage of valid min/max values
5061    real :: varRangeReal(2) ! Local storage of valid min/max values
5062    integer :: gSize ! Global size of lake out arrays
5063    integer :: iTmp
5064    integer :: indVarId,indTmp ! For the feature_id sorting process.
5065    integer :: ierr, myId ! MPI return status, process ID
5066    integer :: gnbasns
5067    ! Allocatable arrays to hold output variables.
5068    real, allocatable, dimension(:) :: g_qin_gwsubbas,g_qout_gwsubbas,g_qloss_gwsubbas,g_z_gwsubbas
5069    integer(kind=int64), allocatable, dimension(:) :: g_basnsInd
5070    real, allocatable, dimension(:,:) :: varOutReal   ! Array holding output variables in real format
5071    integer, allocatable, dimension(:) :: varOutInt ! Array holding output variables after
5072                                                      ! scale_factor/add_offset
5073                                                      ! have been applied.
5074    character (len=64) :: modelConfigType ! This is character verion (long name) for the io_config_outputs
5076    ! Establish macro variables to hlep guide this subroutine.
5077 #ifdef MPP_LAND
5078    mppFlag = 1
5079 #else
5080    mppFlag = 0
5081 #endif
5083 #ifdef HYDRO_D
5084    diagFlag = 1
5085 #else
5086    diagFlag = 0
5087 #endif
5089    ! If we are running over MPI, determine which processor number we are on.
5090    ! If not MPI, then default to 0, which is the I/O ID.
5091    if(mppFlag .eq. 1) then
5092 #ifdef MPP_LAND
5093       call MPI_COMM_RANK( HYDRO_COMM_WORLD, myId, ierr )
5094       call nwmCheck(diagFlag,ierr,'ERROR: Unable to determine MPI process ID.')
5095 #endif
5096    else
5097       myId = 0
5098    endif
5100    ! Some sanity checking here.
5101    if(nlst(domainId)%output_gw .eq. 0) then
5102       ! No output requested here. Return to the parent calling program.
5103       return
5104    endif
5106    ! Initialize NWM dictionary derived type containing all the necessary metadat
5107    ! for the output file.
5108    call initGwDict(fileMeta)
5110    if(nlst(1)%io_config_outputs .eq. 0) then
5111       ! All
5112       fileMeta%outFlag(:) = [1,1,0,1]
5113    else if(nlst(1)%io_config_outputs .eq. 1) then
5114       ! Analysis and Assimilation
5115       fileMeta%outFlag(:) = [1,1,0,1]
5116    else if(nlst(1)%io_config_outputs .eq. 2) then
5117       ! Short Range
5118       fileMeta%outFlag(:) = [1,1,0,1]
5119    else if(nlst(1)%io_config_outputs .eq. 3) then
5120       ! Medium Range
5121       fileMeta%outFlag(:) = [1,1,0,1]
5122    else if(nlst(1)%io_config_outputs .eq. 4) then
5123       ! Long Range
5124       fileMeta%outFlag(:) = [1,1,0,1]
5125    else if(nlst(1)%io_config_outputs .eq. 5) then
5126       ! Retrospective
5127       fileMeta%outFlag(:) = [1,1,0,1]
5128    else if(nlst(1)%io_config_outputs .eq. 6) then
5129       ! Diagnostics
5130       fileMeta%outFlag(:) = [1,1,0,1]
5131    else
5132       call nwmCheck(diagFlag,1,'ERROR: Invalid IOC flag provided by namelist file.')
5133    endif
5135    ! call the GetModelConfigType function
5136    modelConfigType = GetModelConfigType(nlst(1)%io_config_outputs)
5138    gnbasns = rt_domain(domainId)%gnumbasns
5139    gSize = gnbasns
5141    ! Collect and assemble local groundwater bucket arrays to a global array for
5142    ! output.
5143    if(mppFlag .eq. 1) then
5145       if(myId .eq. 0) then
5146          allocate(g_qin_gwsubbas(rt_domain(domainId)%gnumbasns))
5147          allocate(g_qout_gwsubbas(rt_domain(domainId)%gnumbasns))
5148          allocate(g_qloss_gwsubbas(rt_domain(domainId)%gnumbasns))
5149          allocate(g_z_gwsubbas(rt_domain(domainId)%gnumbasns))
5150          allocate(g_basnsInd(rt_domain(domainId)%gnumbasns))
5151       else
5152          allocate(g_qin_gwsubbas(1))
5153          allocate(g_qout_gwsubbas(1))
5154          allocate(g_qloss_gwsubbas(1))
5155          allocate(g_z_gwsubbas(1))
5156          allocate(g_basnsInd(1))
5157       endif
5159       if(nlst(domainId)%UDMP_OPT .eq. 1) then
5160          ! This is ONLY for NWM configuration with NHD channel routing. NCAR
5161          ! reach-based routing has the GW physics initialized the same as with
5162          ! gridded routing.
5163          !ADCHANGE: Note units conversion from m3 to m3/s for UPDMP=1 only
5164          call ReachLS_write_io(rt_domain(domainId)%qin_gwsubbas/nlst(domainId)%DT,g_qin_gwsubbas)
5165          call ReachLS_write_io(rt_domain(domainId)%qout_gwsubbas,g_qout_gwsubbas)
5166          !ADCHANGE: Note units conversion from m to mm for UPDMP=1 only
5167          call ReachLS_write_io(rt_domain(domainId)%z_gwsubbas*1000.,g_z_gwsubbas)
5168          call ReachLS_write_io(rt_domain(domainId)%linkid,g_basnsInd)
5169          if(nlst(domainId)%bucket_loss .eq. 1) then
5170             fileMeta%outFlag(3) = 1
5171             call ReachLS_write_io(rt_domain(domainId)%qloss_gwsubbas,g_qloss_gwsubbas)
5172          endif
5173       else
5174          call gw_write_io_real(rt_domain(domainId)%numbasns,rt_domain(domainId)%qin_gwsubbas,  &
5175                                rt_domain(domainId)%basnsInd,g_qin_gwsubbas)
5176          call gw_write_io_real(rt_domain(domainId)%numbasns,rt_domain(domainId)%qout_gwsubbas,  &
5177                                rt_domain(domainId)%basnsInd,g_qout_gwsubbas)
5178          call gw_write_io_real(rt_domain(domainId)%numbasns,rt_domain(domainId)%z_gwsubbas,  &
5179                                rt_domain(domainId)%basnsInd,g_z_gwsubbas)
5180          call gw_write_io_int(rt_domain(domainId)%numbasns,rt_domain(domainId)%basnsInd, &
5181                               rt_domain(domainId)%basnsInd,g_basnsInd)
5182          if(nlst(domainId)%bucket_loss .eq. 1) then
5183              fileMeta%outFlag(3) = 1
5184              call gw_write_io_real(rt_domain(domainId)%numbasns,rt_domain(domainId)%qloss_gwsubbas, &
5185                                    rt_domain(domainId)%basnsInd,g_qloss_gwsubbas)
5186          endif
5187       endif
5189    else
5190       allocate(g_qin_gwsubbas(rt_domain(domainId)%gnumbasns))
5191       allocate(g_qout_gwsubbas(rt_domain(domainId)%gnumbasns))
5192       allocate(g_qloss_gwsubbas(rt_domain(domainId)%gnumbasns))
5193       allocate(g_z_gwsubbas(rt_domain(domainId)%gnumbasns))
5194       allocate(g_basnsInd(rt_domain(domainId)%gnumbasns))
5196       !ADCHANGE: Note units conversion from m3 to m3/s for UPDMP=1 only
5197       g_qin_gwsubbas = rt_domain(domainId)%qin_gwsubbas/nlst(domainId)%DT
5198       g_qout_gwsubbas = rt_domain(domainId)%qout_gwsubbas
5199       g_z_gwsubbas = rt_domain(domainId)%z_gwsubbas
5200       !ADCHANGE: Note units conversion from m to mm for UPDMP=1 only
5201       if(nlst(domainId)%UDMP_OPT .eq. 1) g_z_gwsubbas = g_z_gwsubbas * 1000.
5202       g_basnsInd = rt_domain(domainId)%linkid
5203       if(nlst(domainId)%bucket_loss .eq. 1) then
5204          fileMeta%outFlag(3) = 1
5205          g_qloss_gwsubbas = rt_domain(domainId)%qloss_gwsubbas
5206       endif
5207    endif
5209    ! Calculate datetime information.
5210    ! First compose strings of EPOCH and simulation start date.
5211    epochDate = trim("1970-01-01 00:00")
5212    startDate = trim(nlst(domainId)%startdate(1:4)//"-"//&
5213                     nlst(domainId)%startdate(6:7)//&
5214                     &"-"//nlst(domainId)%startdate(9:10)//" "//&
5215                     nlst(domainId)%startdate(12:13)//":"//&
5216                     nlst(domainId)%startdate(15:16))
5217    ! Second, utilize NoahMP date utilities to calculate the number of minutes
5218    ! from EPOCH to the beginning of the model simulation.
5219    call geth_idts(startDate,epochDate,minSinceEpoch1)
5220    ! Third, calculate the number of minutes since the beginning of the
5221    ! simulation.
5222    minSinceSim = int(nlst(1)%out_dt*(rt_domain(1)%out_counts-1))
5223    ! Fourth, calculate the total number of minutes from EPOCH to the current
5224    ! model time step.
5225    minSinceEpoch = minSinceEpoch1 + minSinceSim
5226    ! Fifth, compose global attribute time strings that will be used.
5227    validTime = trim(nlst(domainId)%olddate(1:4)//'-'//&
5228                     nlst(domainId)%olddate(6:7)//'-'//&
5229                     nlst(domainId)%olddate(9:10)//'_'//&
5230                     nlst(domainId)%olddate(12:13)//':'//&
5231                     nlst(domainId)%olddate(15:16)//&
5232                     &':00')
5233    initTime = trim(nlst(domainId)%startdate(1:4)//'-'//&
5234                   nlst(domainId)%startdate(6:7)//'-'//&
5235                   nlst(domainId)%startdate(9:10)//'_'//&
5236                   nlst(domainId)%startdate(12:13)//':'//&
5237                   nlst(domainId)%startdate(15:16)//&
5238                   &':00')
5239    ! Replace default values in the dictionary.
5240    fileMeta%initTime = trim(initTime)
5241    fileMeta%validTime = trim(validTime)
5243    ! calculate the minimum and maximum time
5244    fileMeta%timeValidMin = minSinceEpoch1 + nlst(1)%out_dt
5245    fileMeta%timeValidMax = minSinceEpoch1 + int(nlst(1)%khour * 60/nlst(1)%out_dt) * nlst(1)%out_dt
5247    ! calculate total_valid_time
5248    fileMeta%totalValidTime = int(nlst(1)%khour * 60 / nlst(1)%out_dt)  ! # number of valid time (#of output files)
5250    ! Compose output file name.
5251    write(output_flnm,'(A12,".GWOUT_DOMAIN",I1)')nlst(domainId)%olddate(1:4)//&
5252          nlst(domainId)%olddate(6:7)//nlst(domainId)%olddate(9:10)//&
5253          nlst(domainId)%olddate(12:13)//nlst(domainId)%olddate(15:16),nlst(domainId)%igrid
5255    ! Only run NetCDF library calls to output data if we are on the master
5256    ! processor.
5257    if(myId .eq. 0) then
5258       ! Place all output arrays into one real array that will be looped over
5259       ! during conversion to compressed integer format.
5260       allocate(varOutReal(fileMeta%numVars,gSize))
5261       allocate(varOutInt(gSize))
5263       varOutReal(1,:) = g_qin_gwsubbas
5264       varOutReal(2,:) = g_qout_gwsubbas
5265       varOutReal(3,:) = g_qloss_gwsubbas
5266       varOutReal(4,:) = g_z_gwsubbas
5268       ! Mask out missing values
5269       where ( varOutReal == fileMeta%modelNdv ) varOutReal = -9999.0
5271       iret = nf90_create(trim(output_flnm),cmode=NF90_NETCDF4,ncid = ftn)
5272       call nwmCheck(diagFlag,iret,'ERROR: Unable to create GWOUT NetCDF file.')
5274       ! Write global attributes.
5275       iret = nf90_put_att(ftn,NF90_GLOBAL,"TITLE",trim(fileMeta%title))
5276       call nwmCheck(diagFlag,iret,'ERROR: Unable to create TITLE attribute')
5277       iret = nf90_put_att(ftn,NF90_GLOBAL,"compiler_version",compiler_version())
5278       call nwmCheck(diagFlag,iret,'ERROR: Unable to create compiler_version attribute')
5279       iret = nf90_put_att(ftn,NF90_GLOBAL,"featureType",trim(fileMeta%fType))
5280       call nwmCheck(diagFlag,iret,'ERROR: Unable to create featureType attribute')
5281       !iret = nf90_put_att(ftn,NF90_GLOBAL,"proj4",trim(fileMeta%proj4))
5282       !call nwmCheck(diagFlag,iret,'ERROR: Unable to create proj4 attribute')
5283       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_initialization_time",trim(fileMeta%initTime))
5284       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model init attribute')
5285       iret = nf90_put_att(ftn,NF90_GLOBAL,"station_dimension",trim(fileMeta%gwDim))
5286       call nwmCheck(diagFlag,iret,'ERROR: Unable to create st. dimension attribute')
5287       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_output_valid_time",trim(fileMeta%validTime))
5288       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model valid attribute')
5289       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_total_valid_times",fileMeta%totalValidTime)
5290       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model total valid times attribute')
5291       !iret = nf90_put_att(ftn,NF90_GLOBAL,"esri_pe_string",trim(fileMeta%esri))
5292       !call nwmCheck(diagFlag,iret,'ERROR: Unable to create ESRI attribute')
5293       iret = nf90_put_att(ftn,NF90_GLOBAL,"Conventions",trim(fileMeta%conventions))
5294       call nwmCheck(diagFlag,iret,'ERROR: Unable to create conventions attribute')
5295       iret = nf90_put_att(ftn,NF90_GLOBAL,"code_version",trim(get_code_version()))
5296       call nwmCheck(diagFlag,iret,'ERROR: Unable to create code_version attribute')
5297 #ifdef NWM_META
5298       iret = nf90_put_att(ftn,NF90_GLOBAL,"NWM_version_number",trim(get_nwm_version()))
5299       call nwmCheck(diagFlag,iret,'ERROR: Unable to create NWM_version_number attribute')
5300 #endif
5301       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_output_type",trim(fileMeta%modelOutputType))
5302       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_output_type attribute')
5303       iret = nf90_put_att(ftn,NF90_GLOBAL,"model_configuration",modelConfigType)
5304       call nwmCheck(diagFlag,iret,'ERROR: Unable to create model_configuration attribute')
5306       ! Create dimensions
5307       iret = nf90_def_dim(ftn,"feature_id",gSize,dimId(1))
5308       call nwmCheck(diagFlag,iret,'ERROR: Unable to create feature_id dimension')
5309       iret = nf90_def_dim(ftn,"time",NF90_UNLIMITED,dimId(2))
5310       call nwmCheck(diagFlag,iret,'ERROR: Unable to create time dimension')
5311       iret = nf90_def_dim(ftn,"reference_time",1,dimId(3))
5312       call nwmCheck(diagFlag,iret,'ERROR: Unable to create reference_time dimension')
5314       ! Create and populate reference_time and time variables.
5315       iret = nf90_def_var(ftn,"time",nf90_int,dimId(2),timeId)
5316       call nwmCheck(diagFlag,iret,'ERROR: Unable to create time variable')
5317       iret = nf90_put_att(ftn,timeId,'long_name',trim(fileMeta%timeLName))
5318       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into time variable')
5319       iret = nf90_put_att(ftn,timeId,'standard_name',trim(fileMeta%timeStName))
5320       call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into time variable')
5321       iret = nf90_put_att(ftn,timeId,'units',trim(fileMeta%timeUnits))
5322       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into time variable')
5323       iret = nf90_put_att(ftn,timeId,'valid_min',fileMeta%timeValidMin)
5324       call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_min attribute into time variable')
5325       iret = nf90_put_att(ftn,timeId,'valid_max',fileMeta%timeValidMax)
5326       call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_max attribute into time variable')
5327       iret = nf90_def_var(ftn,"reference_time",nf90_int,dimId(3),refTimeId)
5328       call nwmCheck(diagFlag,iret,'ERROR: Unable to create reference_time variable')
5329       iret = nf90_put_att(ftn,refTimeId,'long_name',trim(fileMeta%rTimeLName))
5330       call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into reference_time variable')
5331       iret = nf90_put_att(ftn,refTimeId,'standard_name',trim(fileMeta%rTimeStName))
5332       call nwmCheck(diagFlag,iret,'ERROR: Unable to place standard_name attribute into reference_time variable')
5333       iret = nf90_put_att(ftn,refTimeId,'units',trim(fileMeta%rTimeUnits))
5334       call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into reference_time variable')
5336       ! Create feature_id variable
5337       iret = nf90_def_var(ftn,"feature_id",nf90_int64,dimId(1),featureVarId)
5338       call nwmCheck(diagFlag,iret,'ERROR: Unable to create feature_id variable.')
5339       iret = nf90_put_att(ftn,featureVarId,'long_name',trim(fileMeta%featureIdLName))
5340       call nwmCheck(diagFlag,iret,'ERROR: Uanble to place long_name attribute into feature_id variable')
5341       iret = nf90_put_att(ftn,featureVarId,'comment',trim(fileMeta%featureIdComment))
5342       call nwmCheck(diagFlag,iret,'ERROR: Unable to place comment attribute into feature_id variable')
5343       iret = nf90_put_att(ftn,featureVarId,'cf_role',trim(fileMeta%cfRole))
5344       call nwmCheck(diagFlag,iret,'ERROR: Unable to place cf_role attribute into feature_id variable')
5346       ! Define deflation levels for these meta-variables. For now, we are going
5347       ! to
5348       ! default to a compression level of 2. Only compress if io_form_outputs is set to 1.
5349       if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
5350          iret = nf90_def_var_deflate(ftn,timeId,0,1,2)
5351          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for time.')
5352          iret = nf90_def_var_deflate(ftn,featureVarId,0,1,2)
5353          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for feature_id.')
5354          iret = nf90_def_var_deflate(ftn,refTimeId,0,1,2)
5355          call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression level for reference_time.')
5356       endif
5358       ! Allocate memory for the output variables, then place the real output
5359       ! variables into a single array. This array will be accessed throughout
5360       ! the
5361       ! output looping below for conversion to compressed integer values.
5362       ! Loop through and create each output variable, create variable
5363       ! attributes,
5364       ! and insert data.
5365       do iTmp=1,fileMeta%numVars
5366          if(fileMeta%outFlag(iTmp) .eq. 1) then
5367             ! First create variable
5368             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
5369                iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_int,dimId(1),varId)
5370             else
5371                iret = nf90_def_var(ftn,trim(fileMeta%varNames(iTmp)),nf90_float,dimId(1),varId)
5372             endif
5373             call nwmCheck(diagFlag,iret,'ERROR: Unable to create variable:'//trim(fileMeta%varNames(iTmp)))
5375             ! Extract valid range into a 1D array for placement.
5376             varRange(1) = fileMeta%validMinComp(iTmp)
5377             varRange(2) = fileMeta%validMaxComp(iTmp)
5378             varRangeReal(1) = real(fileMeta%validMinDbl(iTmp))
5379             varRangeReal(2) = real(fileMeta%validMaxDbl(iTmp))
5381             ! Establish a compression level for the variables. For now we are using a
5382             ! compression level of 2. In addition, we are choosing to turn the shuffle
5383             ! filter off for now. Kelley Eicher did some testing with this and
5384             ! determined that the benefit wasn't worth the extra time spent writing output.
5385             ! Only compress if io_form_outputs is set to 1.
5386             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 3)) then
5387                iret = nf90_def_var_deflate(ftn,varId,0,1,2)
5388                call nwmCheck(diagFlag,iret,'ERROR: Unable to define compression for: '//trim(fileMeta%varNames(iTmp)))
5389             endif
5391             ! Create variable attributes
5392             iret = nf90_put_att(ftn,varId,'long_name',trim(fileMeta%longName(iTmp)))
5393             call nwmCheck(diagFlag,iret,'ERROR: Unable to place long_name attribute into variable '//trim(fileMeta%varNames(iTmp)))
5394             iret = nf90_put_att(ftn,varId,'units',trim(fileMeta%units(iTmp)))
5395             call nwmCheck(diagFlag,iret,'ERROR: Unable to place units attribute into variable '//trim(fileMeta%varNames(iTmp)))
5396             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
5397                iret = nf90_put_att(ftn,varId,'_FillValue',fileMeta%fillComp(iTmp))
5398                call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
5399                iret = nf90_put_att(ftn,varId,'missing_value',fileMeta%missingComp(iTmp))
5400                call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
5401                iret = nf90_put_att(ftn,varId,'scale_factor',fileMeta%scaleFactor(iTmp))
5402                call nwmCheck(diagFlag,iret,'ERROR: Unable to place scale_factor attribute into variable '//trim(fileMeta%varNames(iTmp)))
5403                iret = nf90_put_att(ftn,varId,'add_offset',fileMeta%addOffset(iTmp))
5404                call nwmCheck(diagFlag,iret,'ERROR: Unable to place add_offset attribute into variable '//trim(fileMeta%varNames(iTmp)))
5405                iret = nf90_put_att(ftn,varId,'valid_range',varRange)
5406                call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
5407             else
5408                iret = nf90_put_att(ftn,varId,'_FillValue',fileMeta%fillReal(iTmp))
5409                call nwmCheck(diagFlag,iret,'ERROR: Unable to place Fill value attribute into variable '//trim(fileMeta%varNames(iTmp)))
5410                iret = nf90_put_att(ftn,varId,'missing_value',fileMeta%missingReal(iTmp))
5411                call nwmCheck(diagFlag,iret,'ERROR: Unable to place missing value attribute into variable '//trim(fileMeta%varNames(iTmp)))
5412                iret = nf90_put_att(ftn,varId,'valid_range',varRangeReal)
5413                call nwmCheck(diagFlag,iret,'ERROR: Unable to place valid_range attribute into variable '//trim(fileMeta%varNames(iTmp)))
5414             endif
5415          endif
5416       end do
5418       ! Remove NetCDF file from definition mode.
5419       iret = nf90_enddef(ftn)
5420       call nwmCheck(diagFlag,iret,'ERROR: Unable to take GWOUT file out of definition mode')
5422       ! Place groundwater bucket ID, lat, and lon values into appropriate
5423       ! variables.
5424       do iTmp=1,fileMeta%numVars
5425          if(fileMeta%outFlag(iTmp) .eq. 1) then
5426             ! We are outputing this variable.
5427             ! Convert reals to integer. If we are on time 0, make sure we don't
5428             ! need to fill in with NDV values.
5429             if(minSinceSim .eq. 0 .and. fileMeta%timeZeroFlag(iTmp) .eq. 0) then
5430                varOutInt(:) = fileMeta%fillComp(iTmp)
5431                varOutReal(iTmp,:) = fileMeta%fillReal(iTmp)
5432             else
5433                varOutInt(:) = NINT((varOutReal(iTmp,:)-fileMeta%addOffset(iTmp))/fileMeta%scaleFactor(iTmp))
5434             endif
5435             ! Get NetCDF variable id.
5436             iret = nf90_inq_varid(ftn,trim(fileMeta%varNames(iTmp)),varId)
5437             call nwmCheck(diagFlag,iret,'ERROR: Unable to find variable ID for var: '//trim(fileMeta%varNames(iTmp)))
5438             ! Put data into NetCDF file
5439             if((nlst(1)%io_form_outputs .eq. 1) .or. (nlst(1)%io_form_outputs .eq. 2)) then
5440                iret = nf90_put_var(ftn,varId,varOutInt)
5441             else
5442                iret = nf90_put_var(ftn,varId,varOutReal(iTmp,:))
5443             endif
5444             call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into output variable: '//trim(fileMeta%varNames(iTmp)))
5445          endif
5446       end do
5448       ! Place link ID values into the NetCDF file
5449       iret = nf90_inq_varid(ftn,'feature_id',varId)
5450       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate feature_id in NetCDF file.')
5451       iret = nf90_put_var(ftn,varId,g_basnsInd)
5452       call nwmCheck(diagFlag,iret,'ERROR: Unable to place data into feature_id output variable.')
5454       ! Place time values into time variables.
5455       iret = nf90_inq_varid(ftn,'time',varId)
5456       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate time variable')
5457       iret = nf90_put_var(ftn,varId,minSinceEpoch)
5458       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into time variable')
5459       iret = nf90_inq_varid(ftn,'reference_time',varId)
5460       call nwmCheck(diagFlag,iret,'ERROR: Unable to locate reference_time variable')
5461       iret = nf90_put_var(ftn,varId,minSinceEpoch1)
5462       call nwmCheck(diagFlag,iret,'ERROR: Failure to place data into reference_time variable')
5464       ! Close the output file
5465       iret = nf90_close(ftn)
5466       call nwmCheck(diagFlag,iret,'ERROR: Unable to close GWOUT file.')
5467    endif
5469    ! Deallocate all memory
5470    if(myId .eq. 0) then
5471       deallocate(varOutReal)
5472       deallocate(varOutInt)
5473    endif
5474    deallocate(g_qin_gwsubbas)
5475    deallocate(g_qout_gwsubbas)
5476    deallocate(g_qloss_gwsubbas)
5477    deallocate(g_z_gwsubbas)
5478    deallocate(g_basnsInd)
5479 end subroutine output_gw_NWM
5481 subroutine postDiagMsg(diagFlag,diagMsg)
5482    implicit none
5484    ! Subroutine arguments.
5485    integer, intent(in) :: diagFlag
5486    character(len=*), intent(in) :: diagMsg
5488    ! Only write out message if the diagnostic WRF_HYDRO_D flag was
5489    ! set to 1
5490    if (diagFlag .eq. 1) then
5491       print*, trim(diagMsg)
5492    end if
5493 end subroutine postDiagMsg
5495 subroutine nwmCheck(diagFlag,iret,msg)
5496    implicit none
5498    ! Subroutine arguments.
5499    integer, intent(in) :: diagFlag,iret
5500    character(len=*), intent(in) :: msg
5502    ! Check status. If status of command is not 0, then post the error message
5503    ! if WRF_HYDRO_D was set to be 1.
5504    if (iret .ne. 0) then
5505       call hydro_stop(trim(msg))
5506    end if
5508 end subroutine nwmCheck
5510 subroutine checkRouteGages(diagFlag,nElements,indexArray)
5511   use config_base, only: nlst
5512   use netcdf
5513   use module_HYDRO_io, only : get_1d_netcdf_text
5514   implicit none
5516    ! Subroutine arguments.
5517    integer, intent(in) :: diagFlag
5518    integer, intent(in) :: nElements
5519    integer, intent(inout), dimension(nElements) :: indexArray
5520    character(len=15), dimension(nElements) :: gages
5522    ! Local variables
5523    integer :: iret, ftnRt, gageVarId
5525    ! This subroutine will check for a Routelink file, then check for a "gages"
5526    ! variable. If any gages are found, the indexArray is updated and passed back
5527    ! to the calling subroutine.
5528    iret = nf90_open(trim(nlst(1)%route_link_f),NF90_NOWRITE,ncid=ftnRt)
5529    if(iret .ne. 0) then
5530       call postDiagMsg(diagFlag,'WARNING: Did not find Routelink file for gage location in output routines.')
5531       ! No Routelink file found. Simply return to the parent calling subroutine.
5532       return
5533    endif
5535    iret = nf90_inq_varid(ftnRt,'gages',gageVarId)
5536    if(iret .ne. 0) then
5537       call postDiagMsg(diagFlag,'WARNING: Did not find gages in Routelink for forecast points output.')
5538       ! No gages variable found. Simply return to the parent calling routine.'
5539       return
5540    endif
5542    call get_1d_netcdf_text(ftnRt, 'gages', gages,  'checkRouteGages',.true.)
5544    ! Loop over gages. If a non-empty string is found, then change the indexArray
5545    ! value for that element from 0 to 1.
5546    where(gages .ne. '               ') indexArray = 1
5547    where(gages .eq. '') indexArray = 0
5549    iret = nf90_close(ftnRt)
5551    if(iret .ne. 0) then
5552       call nwmCheck(diagFlag,iret,'ERROR: Unable to close Routelink file for gages extraction.')
5553    endif
5555 end subroutine checkRouteGages
5557 end module module_NWM_io