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