Skip to content

Commit

Permalink
more updates
Browse files Browse the repository at this point in the history
  • Loading branch information
bbakernoaa committed Nov 20, 2024
1 parent c004ddc commit f5af65f
Show file tree
Hide file tree
Showing 4 changed files with 120 additions and 239 deletions.
158 changes: 22 additions & 136 deletions src/core/config_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -38,13 +38,12 @@ MODULE Config_Mod
!!
!! \ingroup core_modules
!!!>
SUBROUTINE Read_Input_File( Config , GridState, EmisState, ChemState, RC, ConfigFilename )
SUBROUTINE Read_Input_File( Config, EmisState, ChemState, RC, ConfigFilename )
!
! !USES:
!
USE Error_Mod
USE Config_Opt_Mod, ONLY : ConfigType
USE GridState_Mod, ONLY : GridStateType
use ChemState_Mod, only : ChemStateType
use EmisState_Mod, only : EmisStateType

Expand All @@ -54,7 +53,6 @@ SUBROUTINE Read_Input_File( Config , GridState, EmisState, ChemState, RC, Config
! !INPUT/OUTPUT PARAMETERS:
!
TYPE(ConfigType), INTENT(INOUT) :: Config ! Input options
TYPE(GridStateType), INTENT(INOUT) :: GridState ! Grid State object
TYPE(ChemStateType), INTENT(inout) :: ChemState ! Chemical State
TYPE(EmisStateType), INTENT(inout) :: EmisState ! Emission State
!
Expand Down Expand Up @@ -120,23 +118,23 @@ SUBROUTINE Read_Input_File( Config , GridState, EmisState, ChemState, RC, Config
RETURN
ENDIF

!========================================================================
! Get grid settings from the YAML Config object
!========================================================================

! Grid config settings
CALL Config_Grid( ConfigInput, GridState, RC )
IF ( RC /= CC_SUCCESS ) THEN
errMsg = 'Error in "Config_Grid"!'
CALL CC_Error( errMsg, RC, thisLoc )
CALL QFYAML_CleanUp( ConfigInput )
CALL QFYAML_CleanUp( ConfigAnchored )
RETURN
ENDIF

! !========================================================================
! ! Config processes
! ! Get grid settings from the YAML Config object
! !========================================================================

! ! Grid config settings
! CALL Config_Grid( ConfigInput, GridState, RC )
! IF ( RC /= CC_SUCCESS ) THEN
! errMsg = 'Error in "Config_Grid"!'
! CALL CC_Error( errMsg, RC, thisLoc )
! CALL QFYAML_CleanUp( ConfigInput )
! CALL QFYAML_CleanUp( ConfigAnchored )
! RETURN
! ENDIF

!========================================================================
! Config processes
!========================================================================
call Config_Process_SeaSalt(ConfigInput, Config, RC)
IF ( RC /= CC_SUCCESS ) THEN
errMsg = 'Error in "Config_Process_SeaSalt"!'
Expand Down Expand Up @@ -214,15 +212,13 @@ END SUBROUTINE Read_Input_File
!! \param RC Return code
!!
!!!>
SUBROUTINE Config_Chem_State( filename, GridState, ChemState, RC )
SUBROUTINE Config_Chem_State( filename, ChemState, RC )
USE ChemState_Mod, ONLY : ChemStateType, Find_Number_of_Species, Find_Index_of_Species
use Config_Opt_Mod, ONLY : ConfigType
USE Error_Mod
USE GridState_Mod, ONLY : GridStateType

CHARACTER(LEN=*), INTENT(IN) :: filename
TYPE(ChemStateType), INTENT(INOUT) :: ChemState
TYPE(GridStateType), INTENT(IN) :: GridState
INTEGER, INTENT(INOUT) :: RC

TYPE(QFYAML_t) :: ConfigInput, ConfigAnchored
Expand Down Expand Up @@ -539,10 +535,10 @@ SUBROUTINE Config_Chem_State( filename, GridState, ChemState, RC )
ChemState%ChemSpecies(n)%viscosity = v_real
write(*,*) '| viscosity: ', ChemState%ChemSpecies(n)%viscosity

!---------------------------------------
! Allocate initial Species Concentration
!---------------------------------------
ALLOCATE(ChemState%ChemSpecies(n)%conc(GridState%number_of_levels), STAT=RC)
! !---------------------------------------
! ! Allocate initial Species Concentration
! !---------------------------------------
! ALLOCATE(ChemState%ChemSpecies(n)%conc(GridState%number_of_levels), STAT=RC)

enddo ! n

Expand Down Expand Up @@ -578,7 +574,6 @@ SUBROUTINE Config_Emis_State( filename, EmisState, RC )
USE EmisState_Mod, ONLY : EmisStateType
use Config_Opt_Mod, ONLY : ConfigType
USE Error_Mod
USE GridState_Mod, ONLY : GridStateType

CHARACTER(LEN=*), INTENT(IN) :: filename
! TYPE(ChemStateType), INTENT(INOUT) :: ChemState
Expand Down Expand Up @@ -853,14 +848,8 @@ SUBROUTINE Config_Simulation( ConfigInput, Config, RC )
! !LOCAL VARIABLES:
!
! Scalars
! REAL(fp) :: JulianDateStart, JulianDateEnd

! Strings
! CHARACTER(LEN=6) :: timeStr
! CHARACTER(LEN=8) :: dateStr
! CHARACTER(LEN=12) :: met
! CHARACTER(LEN=15) :: verboseMsg
! CHARACTER(LEN=24) :: sim
CHARACTER(LEN=255) :: thisLoc
CHARACTER(LEN=512) :: errMsg
CHARACTER(LEN=QFYAML_NamLen) :: key
Expand Down Expand Up @@ -915,109 +904,6 @@ SUBROUTINE Config_Simulation( ConfigInput, Config, RC )

END SUBROUTINE Config_Simulation

!> \brief Process grid configuration
!!
!! This function processes the grid configuration and performs the necessary actions based on the configuration.
!!
!! \param[in] ConfigInput The YAML configuration object
!! \param[inout] Config The configuration object
!! \param[out] RC The return code
!!
!! \ingroup core_modules
!!!>
SUBROUTINE Config_Grid( ConfigInput, GridState, RC )
!
! !USES:
!
USE CharPak_Mod, ONLY : StrSplit
USE Error_Mod
USE Config_Opt_Mod, ONLY : ConfigType
USE GridState_Mod, ONLY : GridStateType
!
! !INPUT/OUTPUT PARAMETERS:
!
TYPE(QFYAML_t), INTENT(INOUT) :: ConfigInput ! YAML Config object
! TYPE(ConfigType), INTENT(INOUT) :: Config ! Input options
TYPE(GridStateType), INTENT(INOUT) :: GridState ! Grid State
!
! !OUTPUT PARAMETERS:
!
INTEGER, INTENT(OUT) :: RC ! Success or failure
!
! !LOCAL VARIABLES:
!
! Scalars
! LOGICAL :: v_bool
INTEGER :: v_int

! Strings
CHARACTER(LEN=255) :: thisLoc
CHARACTER(LEN=512) :: errMsg
CHARACTER(LEN=QFYAML_StrLen) :: key

!========================================================================
! Config_Grid begins here!
!========================================================================

! Initialize
RC = CC_SUCCESS
errMsg = ''
thisLoc = ' -> at Config_Grid (in CATChem/src/core/input_mod.F90)'

!------------------------------------------------------------------------
! Level range
!------------------------------------------------------------------------
key = "grid%number_of_levels"
v_int = MISSING_INT
CALL QFYAML_Add_Get( ConfigInput, TRIM( key ), v_int, "", RC )
IF ( RC /= CC_SUCCESS ) THEN
errMsg = 'Error parsing ' // TRIM( key ) // '!'
CALL CC_Error( errMsg, RC, thisLoc )
RETURN
ENDIF
GridState%number_of_levels = v_int

!------------------------------------------------------------------------
! number of soil layers range
!------------------------------------------------------------------------
key = "grid%number_of_soil_layers"
v_int = MISSING_INT
CALL QFYAML_Add_Get( ConfigInput, TRIM( key ), v_int, "", RC )
IF ( RC /= CC_SUCCESS ) THEN
errMsg = 'Error parsing ' // TRIM( key ) // '!'
CALL CC_Error( errMsg, RC, thisLoc )
RETURN
ENDIF
GridState%number_of_soil_layers = v_int

!------------------------------------------------------------------------
! number of x and y dimensions (nx and ny)
!------------------------------------------------------------------------
key = "grid%nx"
v_int = MISSING_INT
CALL QFYAML_Add_Get( ConfigInput, TRIM( key ), v_int, "", RC )
IF ( RC /= CC_SUCCESS ) THEN
errMsg = 'Error parsing ' // TRIM( key ) // '!'
CALL CC_Error( errMsg, RC, thisLoc )
RETURN
ENDIF
GridState%NX = v_int

key = "grid%ny"
v_int = MISSING_INT
CALL QFYAML_Add_Get( ConfigInput, TRIM( key ), v_int, "", RC )
IF ( RC /= CC_SUCCESS ) THEN
errMsg = 'Error parsing ' // TRIM( key ) // '!'
CALL CC_Error( errMsg, RC, thisLoc )
RETURN
ENDIF
GridState%NY = v_int

! Return success
RC = CC_SUCCESS

END SUBROUTINE Config_Grid

!> \brief Process dust configuration
!!
!! This function processes the dust configuration and performs the necessary actions based on the configuration.
Expand Down Expand Up @@ -1179,7 +1065,7 @@ SUBROUTINE Config_Process_SeaSalt( ConfigInput, Config, RC )
RC = CC_SUCCESS
thisLoc = ' -> at Config_Process_SeaSalt (in CATChem/src/core/config_mod.F90)'
errMsg = ''

key = "process%seasalt%activate"
v_bool = MISSING_BOOL
CALL QFYAML_Add_Get( ConfigInput, TRIM( key ), v_bool, "", RC )
Expand Down
98 changes: 98 additions & 0 deletions src/core/error_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ MODULE Error_Mod
PUBLIC :: CC_Error
PUBLIC :: CC_Warning
PUBLIC :: CC_CheckVar
PUBLIC :: CC_CheckDeallocate
!
! !DEFINED PARAMETERS:
!
Expand Down Expand Up @@ -212,5 +213,102 @@ SUBROUTINE CC_CheckVar( Variable, Operation, RC )
ENDIF

END SUBROUTINE CC_CheckVar

!<
!! \brief Check and perform array allocation
!!
!! \param array Array to allocate
!! \param size Size of array to allocate
!! \param varName Variable name for error messages
!!
!! \return RC Return code (CC_SUCCESS or error)
!!!>
FUNCTION CC_CheckAllocate(array, size, varName) RESULT(RC)
!
! !INPUT PARAMETERS:
!
CLASS(*), ALLOCATABLE, INTENT(INOUT) :: array(:) !< Array to allocate
INTEGER, INTENT(IN) :: size !< Size to allocate
CHARACTER(LEN=*), INTENT(IN) :: varName !< Variable name for messages
!
! !RETURN VALUE:
!
INTEGER :: RC
!
! !LOCAL VARIABLES:
!
INTEGER :: stat
CHARACTER(LEN=255) :: ErrMsg, ThisLoc

!=========================================================================
! Initialize
!=========================================================================
RC = CC_SUCCESS
stat = 0
ThisLoc = ' -> at CC_CheckAllocate (in Headers/error_mod.F90)'

!=========================================================================
! Perform allocation if array is not already allocated
!=========================================================================
IF (.NOT. ALLOCATED(array)) THEN
ALLOCATE(array(size), STAT=stat)

IF (stat /= 0) THEN
ErrMsg = 'Failed to allocate ' // TRIM(varName)
CALL CC_Error(ErrMsg, RC, ThisLoc)
RETURN
ENDIF
ENDIF

END FUNCTION CC_CheckAllocate

!>
!! \brief CC_CheckDeallocate
!!
!! This function safely deallocates arrays and returns appropriate error codes
!!
!! \param array Array to deallocate
!! \param varName Name of the variable being deallocated (for error messages)
!! \return RC Return code (CC_SUCCESS or CC_FAILURE)
!!
!! \ingroup core_modules
!!!>
FUNCTION CC_CheckDeallocate(array, varName) RESULT(RC)
!
! !INPUT PARAMETERS:
!
CLASS(*), ALLOCATABLE, INTENT(INOUT) :: array !< Array to deallocate
CHARACTER(LEN=*), INTENT(IN) :: varName !< Variable name for messages
!
! !RETURN VALUE:
!
INTEGER :: RC
!
! !LOCAL VARIABLES:
!
INTEGER :: stat
CHARACTER(LEN=255) :: ErrMsg, ThisLoc

!=========================================================================
! Initialize
!=========================================================================
RC = CC_SUCCESS
stat = 0
ThisLoc = ' -> at CC_CheckDeallocate (in Headers/error_mod.F90)'

!=========================================================================
! Perform deallocation if array is allocated
!=========================================================================
IF (ALLOCATED(array)) THEN
DEALLOCATE(array, STAT=stat)

IF (stat /= 0) THEN
ErrMsg = 'Failed to deallocate ' // TRIM(varName)
CALL CC_Error(ErrMsg, RC, ThisLoc)
RETURN
ENDIF
ENDIF

END FUNCTION CC_CheckDeallocate
!EOC
END MODULE Error_Mod
Loading

0 comments on commit f5af65f

Please sign in to comment.