diff --git a/mo_functions.f90 b/mo_functions.f90
index 54143fe172cba011105956c7eccb3a9dd2cf6ba8..e0f958cf55180a34943c0ec8214739aea042621b 100644
--- a/mo_functions.f90
+++ b/mo_functions.f90
@@ -331,8 +331,8 @@ CONTAINS
 
     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, &
-            & precip_s_input, boundflux_flag)
-        INTEGER, INTENT(in) :: length_input, boundflux_flag
+            & precip_s_input, boundflux_flag, precip_flag)
+        INTEGER, INTENT(in) :: length_input, boundflux_flag, precip_flag
         REAL(wp), INTENT(in) :: timestep_data
         INTEGER :: k
         REAL(wp), DIMENSION(:), allocatable, INTENT(out) :: T_top_input, T2m_input, T_bottom_input, S_bu_bottom_input, &
@@ -343,7 +343,6 @@ CONTAINS
                 & 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), &
                 & precip_s_input(Length_Input))
-
         IF (boundflux_flag == 1) THEN
             OPEN(1234, file = 'input/T_top.txt', status = 'old')
             READ(1234, *)T_top_input
@@ -361,6 +360,11 @@ CONTAINS
             OPEN(1234, file = 'input/fl_sen.txt', status = 'old')
             READ(1234, *)fl_sen_input
             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
             OPEN(1234, file = 'input/T_top.txt', status = 'old')
             READ(1234, *)T_top_input
diff --git a/mo_init.f90 b/mo_init.f90
index 52ee594c421f17567638c7c7b8917215611b974f..24e78fc4c06972dc0f37f3da19d52961e36740da 100644
--- a/mo_init.f90
+++ b/mo_init.f90
@@ -98,7 +98,7 @@ CONTAINS
         !Time settings needed when input is given
         !*************************************************************************************************************************
         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)
         IF (.not. is_found) THEN; PRINT*, 'timestep_data not found'; STOP; END IF
 
@@ -180,7 +180,7 @@ CONTAINS
         time_counter = 1
         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, &
-                & 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
         ! which is done before they are read in in the first tie step in mo_grotz, which is why we unpack them here.