Skip to content

Commit

Permalink
[GH Actions] fprettify source code
Browse files Browse the repository at this point in the history
  • Loading branch information
lyy committed Jul 20, 2023
1 parent e0adea2 commit f98d805
Showing 1 changed file with 6 additions and 6 deletions.
12 changes: 6 additions & 6 deletions src/suews/src/suews_phys_ehc.f95
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ SUBROUTINE heatcond1d_CN(T, Qs, Tsfc, dx, dt, k, rhocp, bc, bctype, debug)
REAL(KIND(1D0)), ALLOCATABLE :: T_tmp(:), k_itf(:)
REAL(KIND(1D0)), ALLOCATABLE :: T_in(:), T_out(:)
REAL(KIND(1D0)), ALLOCATABLE :: vec_lw(:), vec_up(:), vec_diag(:), vec_rhs(:)

REAL(KIND(1D0)) :: dt_remain
REAL(KIND(1D0)) :: dt_step
REAL(KIND(1D0)) :: dt_step_cfl
Expand Down Expand Up @@ -153,7 +153,7 @@ SUBROUTINE heatcond1d_CN(T, Qs, Tsfc, dx, dt, k, rhocp, bc, bctype, debug)
END DO

dt_remain = dt
dt_step_cfl = 0.002 * MINVAL(dx**2/(k/rhocp))
dt_step_cfl = 0.002*MINVAL(dx**2/(k/rhocp))
!PRINT *, 'dt_step_cfl: ', dt_step_cfl
DO WHILE (dt_remain > 1E-10)
dt_step = MIN(dt_step_cfl, dt_remain)
Expand Down Expand Up @@ -200,11 +200,11 @@ SUBROUTINE heatcond1d_CN(T, Qs, Tsfc, dx, dt, k, rhocp, bc, bctype, debug)
Tsfc = T_out(1)
T = T_out

if (debug) then
IF (debug) THEN
PRINT *, "T_up: ", T_up, "T_lw: ", T_lw
PRINT *, "T_out: ", T_out
PRINT *, "T_in: ", T_in
end if
END IF

! new way for calcualating heat storage
! Qs = SUM( &
Expand All @@ -214,10 +214,10 @@ SUBROUTINE heatcond1d_CN(T, Qs, Tsfc, dx, dt, k, rhocp, bc, bctype, debug)
! Qs = SUM( &
! (T_out - T_in) & ! initial temperature
! *rhocp*dx/dt)
! ---Here we use the outermost surface temperatures to calculate
! ---Here we use the outermost surface temperatures to calculate
! ------the heat flux from the surface as the change of Qs for SEB
! ------considering there might be fluxes going out from the lower boundary
Qs = (T_up - T_out(1)) * k(1) / (dx(1) * 0.5)
Qs = (T_up - T_out(1))*k(1)/(dx(1)*0.5)
! Qs = (T_out(1) - T_out(2)) * k(1) / dx(1)
END SUBROUTINE heatcond1d_CN

Expand Down

0 comments on commit f98d805

Please sign in to comment.