My Project
open_all.f90
Go to the documentation of this file.
1 
2 
3 
4 
5 
6 
7 
8 
9 
10 
11 
12 !/===========================================================================/
13 ! Copyright (c) 2007, The University of Massachusetts Dartmouth
14 ! Produced at the School of Marine Science & Technology
15 ! Marine Ecosystem Dynamics Modeling group
16 ! All rights reserved.
17 !
18 ! FVCOM has been developed by the joint UMASSD-WHOI research team. For
19 ! details of authorship and attribution of credit please see the FVCOM
20 ! technical manual or contact the MEDM group.
21 !
22 !
23 ! This file is part of FVCOM. For details, see http://fvcom.smast.umassd.edu
24 ! The full copyright notice is contained in the file COPYRIGHT located in the
25 ! root directory of the FVCOM code. This original header must be maintained
26 ! in all distributed versions.
27 !
28 ! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
29 ! AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO,
30 ! THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
31 ! PURPOSE ARE DISCLAIMED.
32 !
33 !/---------------------------------------------------------------------------/
34 ! CVS VERSION INFORMATION
35 ! $Id$
36 ! $Name$
37 ! $Revision$
38 !/===========================================================================/
39 
40 SUBROUTINE open_all
41 !===============================================================================!
42 ! OPEN FILES
43 ! UNLESS OTHERWISE SPECIFED THE ROUTINES CALLED HERE ARE IN mod_input.F
44 !===============================================================================!
45  USE control
46  USE mod_input
47  USE mod_nesting
48  IMPLICIT NONE
49  CHARACTER(LEN=160) :: FNAME
50  LOGICAL :: FEXIST
51 
52 
54 
55  SELECT CASE(startup_type)
56  !=================================================
57  ! HOTSTART
59  !=================================================
60  if(dbg_set(dbg_log)) then
61  WRITE(ipt,*)'! OPEN INIT FILES FOR HOTSTART !'
62  WRITE(ipt,*)'! !'
63  end if
64 
65  CALL check_io_dirs
66 
68 
69  CALL open_forcing
70 
71  CALL open_new_output
72 
74 
75  !=================================================
76  ! CRASHSTART
78  !=================================================
79  if(dbg_set(dbg_log)) then
80  WRITE(ipt,*)'! OPENING FILES FOR CRASHRESTART !'
81  WRITE(ipt,*)'! !'
82  end if
83 
84  CALL check_io_dirs
85 
86  CALL open_crashstart
87 
88  CALL open_forcing
89 
91 
92  !=================================================
93  ! COLDSTART
95  !=================================================
96  if(dbg_set(dbg_log)) then
97  WRITE(ipt,*)'! OPENING FILES FOR COLDSTART !'
98  WRITE(ipt,*)'! !'
99  end if
100 
101 
102  CALL check_io_dirs
103 
104  ! MAKE SURE THE RUN FILE DOES NOT REQUEST A START FILE
105 
106 
108  CALL open_startup_file
109 
110  ELSE IF (startup_ts_type .eq. startup_type_setvalues) THEN
111  CALL open_startup_file
112 
113  ELSE IF (startup_uv_type .eq. startup_type_setvalues) THEN
114  CALL open_startup_file
115 
116  ELSE IF (startup_turb_type .eq. startup_type_setvalues) THEN
117  CALL open_startup_file
118  ELSE
119  if(dbg_set(dbg_log)) write(ipt,*) "! No Startup file needed fo&
120  &r this cold start"
121 
122  END IF
123 
124  ! OPEN THE OTHER COLD START FILES (GRID,DEPTH SPONGE, ETC)
125  IF (msr) CALL open_coldstart ! ONLY MASTER READS THESE FILES
126 
127  CALL open_forcing
128 
129  CALL open_new_output
130 
132 
133  END SELECT
134 
135 
136 
137 END SUBROUTINE open_all
logical msr
Definition: mod_main.f90:101
character(len=80) startup_ts_type
Definition: mod_main.f90:143
subroutine open_crashstart
Definition: mod_input.f90:1051
character(len=80), parameter startup_type_hotstart
Definition: mod_main.f90:155
character(len=80) startup_type
Definition: mod_main.f90:141
character(len=80) startup_uv_type
Definition: mod_main.f90:144
subroutine open_coldstart
Definition: mod_input.f90:1156
subroutine open_all
Definition: open_all.f90:41
character(len=80) startup_turb_type
Definition: mod_main.f90:145
character(len=80), parameter startup_type_coldstart
Definition: mod_main.f90:154
subroutine nullify_file_pointers
Definition: mod_input.f90:979
character(len=80), parameter startup_type_crashrestart
Definition: mod_main.f90:156
logical nesting_on
subroutine open_forcing
Definition: mod_input.f90:1312
subroutine open_nesting_file
subroutine open_new_output
Definition: mod_input.f90:1247
subroutine check_io_dirs
Definition: mod_input.f90:884
integer ipt
Definition: mod_main.f90:922
subroutine open_startup_file
Definition: mod_input.f90:1019
character(len=80), parameter startup_type_setvalues
Definition: mod_main.f90:165
character(len=80), parameter startup_type_observed
Definition: mod_main.f90:164