My Project
Functions/Subroutines
startup_type.f90 File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine set_startup_type
 

Function/Subroutine Documentation

◆ set_startup_type()

subroutine set_startup_type ( )

Definition at line 41 of file startup_type.f90.

41  USE control
42  USE mod_utils
43  IMPLICIT NONE
44  INTEGER :: II
45 
47  forecast_mode = .true.
48 
49  IF (dbg_set(dbg_log)) then
50  WRITE(ipt,*) "! ======================================================="
51  WRITE(ipt,*) "!!!!!! STARTING FVCOM FORECAST MODE !!!!!"
52  WRITE(ipt,*) "! ======================================================="
53  END IF
55 
56 
57  ELSE
58  forecast_mode = .false.
59  END IF
60 
61 
62 
63  IF(cmdln_restart)THEN
64 
65  IF (forecast_mode) THEN
66  CALL warning("CRASH RESTART DOES NOT WORK IN FORECAST MODE!")
67 
68  ELSE
69  IF (dbg_set(dbg_log)) then
70  WRITE(ipt,*) "! ======================================================="
71  WRITE(ipt,*) "!!!!!!OVER RIDING NAMELIST WITH COMMAND LINE RESTART!!!!!"
72  WRITE(ipt,*) "! ======================================================="
73  END IF
75  END IF
76  END IF
77 
78 
79 
80  SELECT CASE(startup_type)
81  !=================================================
82  ! HOTSTART
84  !=================================================
85  if(dbg_set(dbg_log)) then
86  WRITE(ipt,*)'! RUNNING HOTSTART !'
87  WRITE(ipt,*)'! !'
88  end if
89 
90 
91  !=================================================
92  ! CRASHSTART
94  !=================================================
95 
96  IF (.not. forecast_mode) THEN
97  if(dbg_set(dbg_log)) then
98  WRITE(ipt,*)'! RUNNING CRASHRESTART !'
99  WRITE(ipt,*)'! !'
100  end if
101  END IF
102 
106 
107  !=================================================
108  ! COLDSTART
110  !=================================================
111  if(dbg_set(dbg_log)) then
112  WRITE(ipt,*)'! RUNNING COLDSTART !'
113  WRITE(ipt,*)'! !'
114  end if
115 
116 
117  END SELECT
118 
119  ! CHECK FOR UNKNOW STARTUP TYPES
120 
121 
122  SELECT CASE (startup_uv_type)
123  CASE (startup_type_observed)
124  CALL fatal_error("I DON'T KNOW HOW TO DO THAT KIND OF STARTUP")
125  CASE(startup_type_linear)
126  CALL fatal_error("I DON'T KNOW HOW TO DO THAT KIND OF STARTUP")
128  !OKAY
129  !CALL FATAL_ERROR("I DON'T KNOW HOW TO DO THAT KIND OF STARTUP")
131  ! OKAY
133  ! OKAY
134  CASE DEFAULT
135  CALL fatal_error("UNKNOWN STARTUP_UV_TYPE")
136  END SELECT
137 
138 
139 
140  SELECT CASE(startup_turb_type)
141  CASE(startup_type_observed)
142  CALL fatal_error("I DON'T KNOW HOW TO DO THAT KIND OF STARTUP")
143  CASE(startup_type_linear)
144  CALL fatal_error("I DON'T KNOW HOW TO DO THAT KIND OF STARTUP")
146  CALL fatal_error("I DON'T KNOW HOW TO DO THAT KIND OF STARTUP")
148  ! OKAY
150  ! OKAY
151  CASE DEFAULT
152  CALL fatal_error("UNKNOWN STARTUP_TURB_TYPE")
153  END SELECT
154 
155 
156  SELECT CASE(startup_ts_type)
157  CASE(startup_type_observed)
158  IF(barotropic) CALL fatal_error("CAN'T SET OBSERVERD TS VALUES IN BAROTROPIC MODE!")
159  ! OKAY
160  CASE(startup_type_linear)
161  IF(barotropic) CALL fatal_error("CAN'T SET LINEAR TS VALUES IN BAROTROPIC MODE!")
162  ! OKAY
163  IF (startup_t_vals(1) == -99.0_sp) CALL fatal_error("STARTUP_T_VAL not set in run file",&
164  & "two values required for linear startup (default is -99.0)")
165  IF (startup_t_vals(2) == -99.0_sp)CALL fatal_error("STARTUP_T_VAL not set in run file",&
166  & "two values required for linear startup (default is -99.0)")
167 
168  IF (startup_s_vals(1) == -99.0_sp)CALL fatal_error("STARTUP_S_VAL not set in run file",&
169  & "two values required for linear startup (default is -99.0)")
170  IF (startup_s_vals(2) == -99.0_sp)CALL fatal_error("STARTUP_S_VAL not set in run file",&
171  & "two values required for linear startup (default is -99.0)")
172 
173  IF (startup_dmax == -99.0_sp)CALL fatal_error("STARTUP_DMAX not set in run file",&
174  & "two values required for linear startup (default is -99.0)")
175 
176 
178  ! OKAY
179  IF (startup_t_vals(1) == -99.0_sp)CALL fatal_error("STARTUP_T_VAL not set in run file",&
180  & "one values required for constant startup (default is -99.0)")
181  IF (startup_t_vals(2) /= -99.0_sp)CALL fatal_error("STARTUP_T_VAL is incorrect run file:",&
182  & "only allowed for constant startup!")
183 
184  IF (startup_s_vals(1) == -99.0_sp) CALL fatal_error("STARTUP_S_VAL not set in run file",&
185  & "one values required for constant startup (default is -99.0)")
186  IF (startup_s_vals(2) /= -99.0_sp)CALL fatal_error("STARTUP_S_VAL is incorrect run file:",&
187  & "only allowed for constant startup!")
188 
190  CALL fatal_error("I DON'T KNOW HOW TO DO THAT KIND OF STARTUP")
192  IF(barotropic) CALL warning("YOU ARE RESTARTING A BAROTROPIC CASE&
193  &: T&S BETTER BE CONSTANT IN THE RESTART FILE!")
194  ! OKAY
195  CASE DEFAULT
196  CALL fatal_error("UNKNOWN STARTUP_TS_TYPE")
197  END SELECT
198 
199 
200 
201 
202 
character(len=80) startup_ts_type
Definition: mod_main.f90:143
logical barotropic
Definition: mod_main.f90:381
logical function dbg_set(vrb)
Definition: mod_utils.f90:182
character(len=80), parameter startup_type_hotstart
Definition: mod_main.f90:155
character(len=80), parameter startup_type_linear
Definition: mod_main.f90:163
character(len=80) startup_type
Definition: mod_main.f90:141
character(len=80) startup_uv_type
Definition: mod_main.f90:144
logical forecast_mode
Definition: mod_main.f90:159
character(len=80), parameter startup_type_constant
Definition: mod_main.f90:162
character(len=80) startup_turb_type
Definition: mod_main.f90:145
character(len=80), parameter startup_type_coldstart
Definition: mod_main.f90:154
character(len=80), parameter startup_type_crashrestart
Definition: mod_main.f90:156
character(len=80), parameter startup_type_default
Definition: mod_main.f90:161
real(sp), dimension(2) startup_s_vals
Definition: mod_main.f90:147
logical cmdln_restart
Definition: mod_main.f90:152
subroutine warning(ER1, ER2, ER3, ER4)
Definition: mod_utils.f90:251
real(sp), dimension(2) startup_t_vals
Definition: mod_main.f90:146
character(len=80), parameter startup_type_forecast
Definition: mod_main.f90:157
subroutine fatal_error(ER1, ER2, ER3, ER4)
Definition: mod_utils.f90:230
real(sp) startup_dmax
Definition: mod_main.f90:150
integer ipt
Definition: mod_main.f90:922
character(len=80), parameter startup_type_setvalues
Definition: mod_main.f90:165
integer, parameter dbg_log
Definition: mod_utils.f90:65
character(len=80), parameter startup_type_observed
Definition: mod_main.f90:164
Here is the call graph for this function:
Here is the caller graph for this function: