Skip to content

Commit

Permalink
[GH Actions] fprettify source code
Browse files Browse the repository at this point in the history
  • Loading branch information
sunt05 committed Aug 23, 2023
1 parent ba3b6ff commit 2f6231b
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 20 deletions.
20 changes: 9 additions & 11 deletions src/suews/src/suews_ctrl_driver.f95
Original file line number Diff line number Diff line change
Expand Up @@ -2092,9 +2092,8 @@ SUBROUTINE SUEWS_cal_Main_DTS( &
nsh_real => timer%nsh_real, &
tstep_real => timer%tstep_real, &
dectime => timer%dectime, &
dayofWeek_id =>timer%dayofWeek_id, &
dayofWeek_id => timer%dayofWeek_id, &
dls => timer%dls, &

FAI => roughnessState%FAI, &
PAI => roughnessState%PAI, &
Zh => roughnessState%Zh, &
Expand All @@ -2106,7 +2105,7 @@ SUBROUTINE SUEWS_cal_Main_DTS( &
FAIDecTree_use => roughnessState%FAIDecTree_use, &
Ts5mindata_ir => forcing%Ts5mindata_ir, &
sfr_surf => siteInfo%sfr_surf &
&)
)

! WRITE (*, *) "hydroState%state_roof", hydroState%state_roof
! WRITE (*, *) "hydroState%soilstore_roof", hydroState%soilstore_roof
Expand Down Expand Up @@ -12851,15 +12850,14 @@ SUBROUTINE SUEWS_cal_multitsteps( &
timer%nsh, timer%nsh_real, timer%tstep_real) ! output

! calculate dayofweek information
CALL SUEWS_cal_weekday_DTS( &
timer, siteInfo, & !input
timer%dayofWeek_id) !output

! calculate dayofweek information
CALL SUEWS_cal_DLS_DTS( &
timer, ahemisPrm, & !input
timer%DLS) !output
CALL SUEWS_cal_weekday_DTS( &
timer, siteInfo, & !input
timer%dayofWeek_id) !output

! calculate dayofweek information
CALL SUEWS_cal_DLS_DTS( &
timer, ahemisPrm, & !input
timer%DLS) !output

forcing%qn1_obs = MetForcingBlock(ir, 5) !Real values (kind(1d0))
forcing%qs_obs = MetForcingBlock(ir, 8)
Expand Down
16 changes: 7 additions & 9 deletions src/suews/src/suews_ctrl_type.f95
Original file line number Diff line number Diff line change
Expand Up @@ -285,7 +285,7 @@ MODULE SUEWS_DEF_DTS
END TYPE EHC_PRM

TYPE, PUBLIC :: LC_PAVED_PRM
! land cover specific parameters for paved surfaces
! land cover specific parameters for paved surfaces
REAL(KIND(1D0)) :: sfr
REAL(KIND(1D0)) :: emis
TYPE(OHM_PRM) :: ohm
Expand All @@ -298,7 +298,7 @@ MODULE SUEWS_DEF_DTS
END TYPE LC_PAVED_PRM

TYPE, PUBLIC :: LC_BLDG_PRM
! land cover specific parameters for buildings
! land cover specific parameters for buildings
REAL(KIND(1D0)) :: sfr
REAL(KIND(1D0)) :: faibldg
REAL(KIND(1D0)) :: bldgh
Expand All @@ -313,7 +313,7 @@ MODULE SUEWS_DEF_DTS
END TYPE LC_BLDG_PRM

TYPE, PUBLIC :: LC_DECTR_PRM
! land cover specific parameters for deciduous trees
! land cover specific parameters for deciduous trees
REAL(KIND(1D0)) :: sfr
REAL(KIND(1D0)) :: emis
REAL(KIND(1D0)) :: faidectree
Expand All @@ -337,7 +337,7 @@ MODULE SUEWS_DEF_DTS
END TYPE LC_DECTR_PRM

TYPE, PUBLIC :: LC_EVETR_PRM
! land cover specific parameters for evergreen trees
! land cover specific parameters for evergreen trees
REAL(KIND(1D0)) :: sfr !surface cover fraction[-]
REAL(KIND(1D0)) :: emis !Effective surface emissivity[-]
REAL(KIND(1D0)) :: faievetree !frontal area index for evergreen tree [-]
Expand All @@ -357,7 +357,7 @@ MODULE SUEWS_DEF_DTS
END TYPE LC_EVETR_PRM

TYPE, PUBLIC :: LC_GRASS_PRM
! land cover specific parameters for grass
! land cover specific parameters for grass
REAL(KIND(1D0)) :: sfr
REAL(KIND(1D0)) :: emis
REAL(KIND(1D0)) :: alb_min
Expand All @@ -375,7 +375,7 @@ MODULE SUEWS_DEF_DTS
END TYPE LC_GRASS_PRM

TYPE, PUBLIC :: LC_BSOIL_PRM
! land cover specific parameters for bare soil
! land cover specific parameters for bare soil
REAL(KIND(1D0)) :: sfr
REAL(KIND(1D0)) :: emis
TYPE(OHM_PRM) :: ohm
Expand All @@ -387,7 +387,7 @@ MODULE SUEWS_DEF_DTS
END TYPE LC_BSOIL_PRM

TYPE, PUBLIC :: LC_WATER_PRM
! land cover specific parameters for water surface
! land cover specific parameters for water surface
REAL(KIND(1D0)) :: sfr
REAL(KIND(1D0)) :: emis
TYPE(OHM_PRM) :: ohm
Expand Down Expand Up @@ -436,7 +436,6 @@ MODULE SUEWS_DEF_DTS
REAL(KIND(1D0)), DIMENSION(nsurf) :: snowwater ! snow water[mm]
END TYPE SNOW_STATE


TYPE, PUBLIC :: HYDRO_STATE
! REAL(KIND(1D0)) :: runofftowater ! Fraction of above-ground runoff flowing to water surface during flooding
REAL(KIND(1D0)), DIMENSION(nsurf) :: soilstore_surf ! Initial water stored in soil beneath `Bldgs` surface
Expand Down Expand Up @@ -523,7 +522,6 @@ MODULE SUEWS_DEF_DTS

END TYPE SUEWS_TIMER


CONTAINS
SUBROUTINE allocate_hydro_state(self, nlayer)
IMPLICIT NONE
Expand Down

0 comments on commit 2f6231b

Please sign in to comment.