From 473d1ae2e976d35b92adda80a3e3b1d0c71bf82d Mon Sep 17 00:00:00 2001
From: kck540 <kyle.klenk@usask.ca>
Date: Wed, 30 Mar 2022 14:03:28 -0400
Subject: [PATCH] new branch for fixing output bottleneck

---
 .../driver/summaActors_wOutputStruc.f90       |  12 +-
 .../file_access_actor/cppwrap_fileAccess.f90  |  41 +++---
 build/source/netcdf/writeOutput.f90           | 138 +++++++++---------
 3 files changed, 90 insertions(+), 101 deletions(-)

diff --git a/build/source/driver/summaActors_wOutputStruc.f90 b/build/source/driver/summaActors_wOutputStruc.f90
index 37c907d..011f845 100644
--- a/build/source/driver/summaActors_wOutputStruc.f90
+++ b/build/source/driver/summaActors_wOutputStruc.f90
@@ -15,10 +15,7 @@ USE globalData,only:noNewFiles
 USE globalData,only:newFileEveryOct1
 USE globalData,only:chunkSize               ! size of chunks to write
 USE globalData,only:outputPrecision         ! data structure for output precision
-
 USE globalData,only:integerMissing            ! missing integer
-
-
 ! metadata
 USE globalData,only:time_meta                 ! metadata on the model time
 USE globalData,only:forc_meta                 ! metadata on the model forcing data
@@ -29,9 +26,6 @@ USE globalData,only:indx_meta                 ! metadata on the model index vari
 USE globalData,only:bvar_meta                 ! metadata on basin-average variables
 USE globalData,only:bpar_meta                 ! basin parameter metadata structure
 USE globalData,only:mpar_meta                 ! local parameter metadata structure
-
-
-
 ! child metadata for stats
 USE globalData,only:statForc_meta             ! child metadata for stats
 USE globalData,only:statProg_meta             ! child metadata for stats
@@ -39,7 +33,6 @@ USE globalData,only:statDiag_meta             ! child metadata for stats
 USE globalData,only:statFlux_meta             ! child metadata for stats
 USE globalData,only:statIndx_meta             ! child metadata for stats
 USE globalData,only:statBvar_meta             ! child metadata for stats
-
 ! index of the child data structure
 USE globalData,only:forcChild_map             ! index of the child data structure: stats forc
 USE globalData,only:progChild_map             ! index of the child data structure: stats prog
@@ -47,9 +40,7 @@ USE globalData,only:diagChild_map             ! index of the child data structur
 USE globalData,only:fluxChild_map             ! index of the child data structure: stats flux
 USE globalData,only:indxChild_map             ! index of the child data structure: stats indx
 USE globalData,only:bvarChild_map             ! index of the child data structure: stats bvar
-
 USE globalData,only:outFreq                   ! output frequencies
-
 ! named variables
 USE var_lookup,only:maxvarFreq                ! maximum number of output files
 USE var_lookup,only:iLookTIME                 ! named variables for time data structure
@@ -57,7 +48,6 @@ USE var_lookup,only:iLookDIAG                 ! named variables for local column
 USE var_lookup,only:iLookPROG                 ! named variables for local column model prognostic variables
 USE var_lookup,only:iLookINDEX                ! named variables for local column index variables
 USE var_lookup,only:iLookFreq                 ! named variables for the frequency structure
-
 USE get_ixname_module,only:get_freqName       ! get name of frequency from frequency index
 
 
@@ -162,7 +152,7 @@ subroutine summaActors_writeToOutputStruc(&
   type(flagVec),intent(inout)              :: finalizeStats   ! flags to finalize statistics
   type(var_i),intent(inout)                :: finshTime       ! end time for the model simulation
   type(var_i),intent(inout)                :: oldTime         !
-  integer(i4b),intent(in)               :: outputStep      ! index into the outputStructure
+  integer(i4b),intent(in)                  :: outputStep      ! index into the outputStructure
   integer(i4b),intent(inout)               :: forcingStep     ! index of current time step in current forcing file 
   ! run time variables
   integer(i4b),intent(out)                 :: err
diff --git a/build/source/interface/file_access_actor/cppwrap_fileAccess.f90 b/build/source/interface/file_access_actor/cppwrap_fileAccess.f90
index 93eefa6..1c7592c 100644
--- a/build/source/interface/file_access_actor/cppwrap_fileAccess.f90
+++ b/build/source/interface/file_access_actor/cppwrap_fileAccess.f90
@@ -185,14 +185,14 @@ subroutine FileAccessActor_ReadForcing(handle_forcFileInfo, currentFile, stepsIn
 end subroutine FileAccessActor_ReadForcing
 
 subroutine FileAccessActor_WriteOutput(&
-                                handle_ncid,      &
-                                outputFileExists, &
+                                handle_ncid,      & ! ncid of the output file
+                                outputFileExists, & ! flag to check if the output file exsists
                                 nSteps,           & ! number of steps to write
-                                startGRU,         &
-                                numGRU,           &
-                                hruFileInit,      &
-                                indxGRU,          &
-                                indxHRU,          &
+                                startGRU,         & ! startGRU for the entire job (for file creation)
+                                numGRU,           & ! numGRUs for the entire job (for file creation)
+                                hruFileInit,      & ! flag to check if specific hru params have been written
+                                indxGRU,          & ! index of GRU we are currently writing for
+                                indxHRU,          & ! index of HRU we are currently writing for
                                 err) bind(C, name="FileAccessActor_WriteOutput")
   USE globalData,only:fileout
   USE summaActors_FileManager,only:OUTPUT_PATH,OUTPUT_PREFIX         ! define output file
@@ -216,18 +216,19 @@ subroutine FileAccessActor_WriteOutput(&
   USE netcdf
 
   implicit none
-  type(c_ptr),intent(in), value        :: handle_ncid
-  logical(c_bool),intent(inout)        :: outputFileExists
-  integer(c_int),intent(in)            :: nSteps
-  integer(c_int),intent(in)            :: startGRU
-  integer(c_int),intent(in)            :: numGRU
-  logical(c_bool),intent(inout)        :: hruFileInit
-  integer(c_int),intent(in)            :: indxGRU
-  integer(c_int),intent(in)            :: indxHRU
-  integer(c_int),intent(inout)         :: err
+  ! dummy variables
+  type(c_ptr),intent(in), value        :: handle_ncid       ! ncid of the output file
+  logical(c_bool),intent(inout)        :: outputFileExists  ! flag to check if the output file exsists
+  integer(c_int),intent(in)            :: nSteps            ! number of steps to write
+  integer(c_int),intent(in)            :: startGRU          ! startGRU for the entire job (for file creation)
+  integer(c_int),intent(in)            :: numGRU            ! numGRUs for the entire job (for file creation)
+  logical(c_bool),intent(inout)        :: hruFileInit       ! flag to check if specific hru params have been written
+  integer(c_int),intent(in)            :: indxGRU           ! index of GRU we are currently writing for
+  integer(c_int),intent(in)            :: indxHRU           ! index of HRU we are currently writing for
+  integer(c_int),intent(inout)         :: err               ! Error code
+  
+  ! local variables 
   type(var_i),pointer                  :: ncid
-
-  ! local variables
   character(LEN=256)                   :: startGRUString
   character(LEN=256)                   :: numGRUString
   character(LEN=256)                   :: message
@@ -237,8 +238,9 @@ subroutine FileAccessActor_WriteOutput(&
   integer(i4b)                         :: iStep
   integer(i4b)                         :: iFreq
 
-
   call c_f_pointer(handle_ncid, ncid)
+
+
   ! check if we have created the file, if no create it
   if(.not.outputFileExists)then
     ! allocate space for the output file ID array
@@ -263,7 +265,6 @@ subroutine FileAccessActor_WriteOutput(&
     fileout = trim(OUTPUT_PATH)//trim(OUTPUT_PREFIX)//"GRU"&
                 //trim(adjustl(startGRUString))//"-"//trim(adjustl(numGRUString))
 
-
     ! def_output call will need to change to allow for numHRUs in future
     ! NA_Domain numGRU = numHRU, this is why we pass numGRU twice
     call def_output("summaVersion","buildTime","gitBranch","gitHash",numGRU,numGRU,&
diff --git a/build/source/netcdf/writeOutput.f90 b/build/source/netcdf/writeOutput.f90
index d6e141a..363a63c 100644
--- a/build/source/netcdf/writeOutput.f90
+++ b/build/source/netcdf/writeOutput.f90
@@ -168,7 +168,7 @@ integer(i4b)  ,intent(inout)     :: outputTimestep(:) ! output time step
 integer(i4b)  ,intent(in)        :: nHRUrun           ! number of HRUs in the run domain
 integer(i4b)  ,intent(in)        :: maxLayers         ! maximum number of layers
 integer(i4b)  ,intent(in)        :: iGRU
-integer(i4b)  ,intent(in)        :: iStep            ! number of timeSteps
+integer(i4b)  ,intent(in)        :: iStep             ! number of timeSteps
 type(var_info),intent(in)        :: meta(:)           ! meta data
 class(*)      ,intent(in)        :: stat              ! stats data
 class(*)      ,intent(in)        :: dat               ! timestep data
@@ -208,6 +208,7 @@ do iFreq=1,maxvarFreq
 
   ! loop through model variables
   do iVar = 1,size(meta)
+    
     ! handle time first
     if (meta(iVar)%varName=='time')then
       ! get variable index
@@ -216,9 +217,6 @@ do iFreq=1,maxvarFreq
       ! define HRUs and GRUs (only write once)
       ! data bound write
         if(structName == "forc")then
-          ! if(iGRU == 3 .and. iFreq == 4)then
-          !   print*, "timeOutput = ", outputStructure(1)%forcStruct(1)%gru(iGRU)%hru(1)%var(iVar)%tim(iStep), "Step", iStep, "OutputStep = ", outputTimestep(4)
-          ! endif
           timeVal = outputStructure(1)%forcStruct(1)%gru(iGRU)%hru(1)%var(iVar)%tim(iStep)
           err = nf90_put_var(ncid%var(iFreq),ncVarID,(/timeVal/),start=(/outputTimestep(iFreq)/),count=(/1/))
           call netcdf_err(err,message); if (err/=0)then; print*, "err"; return; endif
@@ -308,74 +306,74 @@ end do ! iFreq
 
 end subroutine writeData
 
-    ! **************************************************************************************
-    ! public subroutine writeBasin: write basin-average variables
-    ! **************************************************************************************
+! **************************************************************************************
+! public subroutine writeBasin: write basin-average variables
+! **************************************************************************************
 subroutine writeBasin(ncid,iGRU,outputTimestep,iStep,meta,stat,dat,map,err,message)
-USE data_types,only:var_info                       ! metadata type
-USE var_lookup,only:maxVarStat                     ! index into stats structure
-USE var_lookup,only:iLookVarType                   ! index into type structure
-USE globalData,only:outFreq                        ! output file information
-USE get_ixName_module,only:get_varTypeName         ! to access type strings for error messages
-USE get_ixName_module,only:get_statName            ! to access type strings for error messages
-implicit none
-
-! declare dummy variables
-type(var_i)   ,intent(in)     :: ncid              ! file ids
-integer(i4b)  ,intent(in)     :: iGRU              ! GRU index
-integer(i4b)  ,intent(inout)  :: outputTimestep(:) ! output time step
-integer(i4b)  ,intent(in)     :: iStep            ! number of steps in forcing file
-type(var_info),intent(in)     :: meta(:)           ! meta data
-type(time_dlength),intent(in) :: stat(:)           ! stats data
-type(time_dlength),intent(in) :: dat(:)            ! timestep data
-integer(i4b)  ,intent(in)     :: map(:)            ! map into stats child struct
-integer(i4b)  ,intent(out)    :: err               ! error code
-character(*)  ,intent(out)    :: message           ! error message
-! local variables
-integer(i4b)                  :: iVar              ! variable index
-integer(i4b)                  :: iStat             ! statistics index
-integer(i4b)                  :: iFreq             ! frequency index
-! initialize error control
-err=0;message="f-writeBasin/"
-
-! loop through output frequencies
-do iFreq=1,maxvarFreq
-
-  ! skip frequencies that are not needed
-  if(.not.outFreq(iFreq)) cycle
-
-  ! check that we have finalized statistics for a given frequency
-  if(.not.outputStructure(1)%finalizeStats(1)%gru(1)%hru(1)%tim(iStep)%dat(iFreq)) cycle
-
-  ! loop through model variables
-  do iVar = 1,size(meta)
-    ! define the statistics index
-    iStat = meta(iVar)%statIndex(iFreq)
-
-    ! check that the variable is desired
-    if (iStat==integerMissing.or.trim(meta(iVar)%varName)=='unknown') cycle
-
-    
-    ! stats/data output - select data type
-    select case (meta(iVar)%varType)
-
-      case (iLookVarType%scalarv)
-        err = nf90_put_var(ncid%var(iFreq),meta(iVar)%ncVarID(iFreq),(/stat(map(iVar))%tim(iStep)%dat(iFreq)/),start=(/iGRU,outputTimestep(iFreq)/),count=(/1,1/))
-
-      case (iLookVarType%routing)
-        if (iFreq==1 .and. outputTimestep(iFreq)==1) then
-          err = nf90_put_var(ncid%var(iFreq),meta(iVar)%ncVarID(iFreq),(/dat(iVar)%tim(iStep)%dat/),start=(/1/),count=(/1000/))
-        end if
-      case default
-        err=40; message=trim(message)//"unknownVariableType[name='"//trim(meta(iVar)%varName)//"';type='"//trim(get_varTypeName(meta(iVar)%varType))//    "']"; return
-    end select ! variable type
-
-    ! process error code
-    if (err.ne.0) message=trim(message)//trim(meta(iVar)%varName)//'_'//trim(get_statName(iStat))
-    call netcdf_err(err,message); if (err/=0) return
+  USE data_types,only:var_info                       ! metadata type
+  USE var_lookup,only:maxVarStat                     ! index into stats structure
+  USE var_lookup,only:iLookVarType                   ! index into type structure
+  USE globalData,only:outFreq                        ! output file information
+  USE get_ixName_module,only:get_varTypeName         ! to access type strings for error messages
+  USE get_ixName_module,only:get_statName            ! to access type strings for error messages
+  implicit none
+
+  ! declare dummy variables
+  type(var_i)   ,intent(in)     :: ncid              ! file ids
+  integer(i4b)  ,intent(in)     :: iGRU              ! GRU index
+  integer(i4b)  ,intent(inout)  :: outputTimestep(:) ! output time step
+  integer(i4b)  ,intent(in)     :: iStep            ! number of steps in forcing file
+  type(var_info),intent(in)     :: meta(:)           ! meta data
+  type(time_dlength),intent(in) :: stat(:)           ! stats data
+  type(time_dlength),intent(in) :: dat(:)            ! timestep data
+  integer(i4b)  ,intent(in)     :: map(:)            ! map into stats child struct
+  integer(i4b)  ,intent(out)    :: err               ! error code
+  character(*)  ,intent(out)    :: message           ! error message
+  ! local variables
+  integer(i4b)                  :: iVar              ! variable index
+  integer(i4b)                  :: iStat             ! statistics index
+  integer(i4b)                  :: iFreq             ! frequency index
+  ! initialize error control
+  err=0;message="f-writeBasin/"
+
+  ! loop through output frequencies
+  do iFreq=1,maxvarFreq
+
+    ! skip frequencies that are not needed
+    if(.not.outFreq(iFreq)) cycle
+
+    ! check that we have finalized statistics for a given frequency
+    if(.not.outputStructure(1)%finalizeStats(1)%gru(1)%hru(1)%tim(iStep)%dat(iFreq)) cycle
+
+    ! loop through model variables
+    do iVar = 1,size(meta)
+
+      ! define the statistics index
+      iStat = meta(iVar)%statIndex(iFreq)
+
+      ! check that the variable is desired
+      if (iStat==integerMissing.or.trim(meta(iVar)%varName)=='unknown') cycle
+
+      ! stats/data output - select data type
+      select case (meta(iVar)%varType)
+
+        case (iLookVarType%scalarv)
+          err = nf90_put_var(ncid%var(iFreq),meta(iVar)%ncVarID(iFreq),(/stat(map(iVar))%tim(iStep)%dat(iFreq)/),start=(/iGRU,outputTimestep(iFreq)/),count=(/1,1/))
+
+        case (iLookVarType%routing)
+          if (iFreq==1 .and. outputTimestep(iFreq)==1) then
+            err = nf90_put_var(ncid%var(iFreq),meta(iVar)%ncVarID(iFreq),(/dat(iVar)%tim(iStep)%dat/),start=(/1/),count=(/1000/))
+          end if
+        case default
+          err=40; message=trim(message)//"unknownVariableType[name='"//trim(meta(iVar)%varName)//"';type='"//trim(get_varTypeName(meta(iVar)%varType))//    "']"; return
+      end select ! variable type
+
+      ! process error code
+      if (err.ne.0) message=trim(message)//trim(meta(iVar)%varName)//'_'//trim(get_statName(iStat))
+      call netcdf_err(err,message); if (err/=0) return
 
-  end do ! iVar
-end do ! iFreq
+    end do ! iVar
+  end do ! iFreq
 
 end subroutine writeBasin
 
-- 
GitLab