Skip to content
Snippets Groups Projects
Commit efe6b41f authored by Fuchs, Niels's avatar Fuchs, Niels
Browse files

add T2m to boundflux 2 if necessary to determine precip phase

parent 7f0871f0
Branches
No related tags found
No related merge requests found
...@@ -331,8 +331,8 @@ CONTAINS ...@@ -331,8 +331,8 @@ CONTAINS
SUBROUTINE sub_input(length_input, timestep_data, T_top_input, T2m_input, T_bottom_input, S_bu_bottom_input, & SUBROUTINE sub_input(length_input, timestep_data, T_top_input, T2m_input, T_bottom_input, S_bu_bottom_input, &
& fl_q_bottom_input, time_input,fl_sw_input, fl_lw_input, fl_lat_input, fl_sen_input, precip_l_input, & & fl_q_bottom_input, time_input,fl_sw_input, fl_lw_input, fl_lat_input, fl_sen_input, precip_l_input, &
& precip_s_input, boundflux_flag) & precip_s_input, boundflux_flag, precip_flag)
INTEGER, INTENT(in) :: length_input, boundflux_flag INTEGER, INTENT(in) :: length_input, boundflux_flag, precip_flag
REAL(wp), INTENT(in) :: timestep_data REAL(wp), INTENT(in) :: timestep_data
INTEGER :: k INTEGER :: k
REAL(wp), DIMENSION(:), allocatable, INTENT(out) :: T_top_input, T2m_input, T_bottom_input, S_bu_bottom_input, & REAL(wp), DIMENSION(:), allocatable, INTENT(out) :: T_top_input, T2m_input, T_bottom_input, S_bu_bottom_input, &
...@@ -343,7 +343,6 @@ CONTAINS ...@@ -343,7 +343,6 @@ CONTAINS
& fl_q_bottom_input(Length_Input), fl_sw_input(Length_Input), fl_lw_input(Length_Input), & & fl_q_bottom_input(Length_Input), fl_sw_input(Length_Input), fl_lw_input(Length_Input), &
& fl_lat_input(Length_Input), fl_sen_input(Length_Input), precip_l_input(Length_Input), & & fl_lat_input(Length_Input), fl_sen_input(Length_Input), precip_l_input(Length_Input), &
& precip_s_input(Length_Input)) & precip_s_input(Length_Input))
IF (boundflux_flag == 1) THEN IF (boundflux_flag == 1) THEN
OPEN(1234, file = 'input/T_top.txt', status = 'old') OPEN(1234, file = 'input/T_top.txt', status = 'old')
READ(1234, *)T_top_input READ(1234, *)T_top_input
...@@ -361,6 +360,11 @@ CONTAINS ...@@ -361,6 +360,11 @@ CONTAINS
OPEN(1234, file = 'input/fl_sen.txt', status = 'old') OPEN(1234, file = 'input/fl_sen.txt', status = 'old')
READ(1234, *)fl_sen_input READ(1234, *)fl_sen_input
CLOSE(1234) CLOSE(1234)
IF (precip_flag == 1) THEN
OPEN(1234, file = 'input/T2m.txt', status = 'old')
READ(1234, *)T2m_input
CLOSE(1234)
END IF
ELSE IF (boundflux_flag == 3) THEN ELSE IF (boundflux_flag == 3) THEN
OPEN(1234, file = 'input/T_top.txt', status = 'old') OPEN(1234, file = 'input/T_top.txt', status = 'old')
READ(1234, *)T_top_input READ(1234, *)T_top_input
......
...@@ -98,7 +98,7 @@ CONTAINS ...@@ -98,7 +98,7 @@ CONTAINS
!Time settings needed when input is given !Time settings needed when input is given
!************************************************************************************************************************* !*************************************************************************************************************************
CALL json%get('length_input', length_input, is_found) CALL json%get('length_input', length_input, is_found)
IF (.not. is_found) THEN; PRINT*, 'length_input not found'; STOP; END IF IF (.not. is_found) THEN; PRINT*, 'n_time_output not found'; STOP; END IF
CALL json%get('timestep_data', timestep_data, is_found) CALL json%get('timestep_data', timestep_data, is_found)
IF (.not. is_found) THEN; PRINT*, 'timestep_data not found'; STOP; END IF IF (.not. is_found) THEN; PRINT*, 'timestep_data not found'; STOP; END IF
...@@ -180,7 +180,7 @@ CONTAINS ...@@ -180,7 +180,7 @@ CONTAINS
time_counter = 1 time_counter = 1
CALL sub_input(length_input, timestep_data, T_top_input, T2m_input, T_bottom_input, S_bu_bottom_input, & CALL sub_input(length_input, timestep_data, T_top_input, T2m_input, T_bottom_input, S_bu_bottom_input, &
& fl_q_bottom_input, time_input,fl_sw_input, fl_lw_input, fl_lat_input, fl_sen_input, precip_l_input, & & fl_q_bottom_input, time_input,fl_sw_input, fl_lw_input, fl_lat_input, fl_sen_input, precip_l_input, &
& precip_s_input, boundflux_flag) & precip_s_input, boundflux_flag, precip_flag)
! Unpack first values of inputs used for each boundflux_flag. The initial values are used to initialize the sea ice ! Unpack first values of inputs used for each boundflux_flag. The initial values are used to initialize the sea ice
! which is done before they are read in in the first tie step in mo_grotz, which is why we unpack them here. ! which is done before they are read in in the first tie step in mo_grotz, which is why we unpack them here.
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment