Line data Source code
1 : module cam_initfiles
2 : !---------------------------------------------------------------------------------------
3 : !
4 : ! Open, close, and provide access to the initial, topography, and primary restart files.
5 : !
6 : !---------------------------------------------------------------------------------------
7 :
8 : use shr_kind_mod, only: r8=>shr_kind_r8, cl=>shr_kind_cl
9 : use spmd_utils, only: masterproc
10 : use cam_control_mod, only: initial_run, restart_run, branch_run, caseid, brnch_retain_casename
11 : use ioFileMod, only: getfil, opnfil
12 : use cam_pio_utils, only: cam_pio_openfile
13 : use pio, only: file_desc_t, pio_offset_kind, pio_global, &
14 : pio_inq_att, pio_get_att, pio_nowrite, &
15 : pio_closefile
16 : use cam_logfile, only: iulog
17 : use cam_abortutils, only: endrun
18 :
19 : implicit none
20 : private
21 : save
22 :
23 : ! Public methods
24 :
25 : public :: &
26 : cam_initfiles_readnl, &! read namelist
27 : cam_initfiles_open, &! open initial and topo files
28 : initial_file_get_id, &! returns filehandle for initial file
29 : topo_file_get_id, &! returns filehandle for topo file
30 : cam_initfiles_get_caseid, &! return caseid from initial restart file
31 : cam_initfiles_get_restdir, &! return caseid from initial restart file
32 : cam_initfiles_close ! close initial and topo files
33 :
34 : ! Namelist inputs
35 : logical :: use_topo_file = .true.
36 : character(len=cl), public, protected :: ncdata = 'ncdata' ! full pathname for initial dataset
37 : character(len=cl), public, protected :: bnd_topo = 'bnd_topo' ! full pathname for topography dataset
38 :
39 : real(r8), public, protected :: pertlim = 0.0_r8 ! maximum abs value of scale factor used to perturb
40 : ! initial values
41 : character(len=cl) :: cam_branch_file = ' ' ! Filepath of primary restart file for a branch run
42 :
43 : real(r8), public, protected :: scale_dry_air_mass = 0.0_r8 ! Toggle and target avg air mass for MPAS dycore
44 :
45 : ! Filename for initial restart file.
46 : character(len=cl) :: restart_file = ' '
47 :
48 : ! case name read from initial restart file. This case name matches the caseid
49 : ! which is embedded in the filename.
50 : character(len=cl) :: caseid_prev = ' '
51 :
52 : type(file_desc_t), pointer :: fh_ini => null()
53 : type(file_desc_t), pointer :: fh_topo => null()
54 : type(file_desc_t), target :: fh_restart
55 :
56 : !========================================================================================
57 : contains
58 : !========================================================================================
59 :
60 2304 : subroutine cam_initfiles_readnl(nlfile)
61 :
62 : use namelist_utils, only: find_group_name
63 : use units, only: getunit, freeunit
64 : use spmd_utils, only: mpicom, mstrid=>masterprocid, mpir8=>mpi_real8, &
65 : mpichar=>mpi_character, mpi_logical
66 : use cam_instance, only: inst_suffix
67 : use filenames, only: interpret_filename_spec
68 :
69 : character(len=*), intent(in) :: nlfile ! filepath for file containing namelist input
70 :
71 : ! Local variables
72 : integer :: unitn, ierr
73 : character(len=cl) :: locfn
74 : logical :: filefound
75 : integer :: xtype
76 : integer(pio_offset_kind) :: slen
77 : logical :: found
78 :
79 : ! The restart pointer file contains name of most recently written primary restart file.
80 : character(len=cl) :: rest_pfile
81 :
82 : character(len=*), parameter :: sub = 'cam_initfiles_readnl'
83 :
84 : namelist /cam_initfiles_nl/ ncdata, use_topo_file, bnd_topo, pertlim, &
85 : cam_branch_file, scale_dry_air_mass
86 : !-----------------------------------------------------------------------------
87 :
88 1536 : if (masterproc) then
89 2 : unitn = getunit()
90 2 : open( unitn, file=trim(nlfile), status='old' )
91 2 : call find_group_name(unitn, 'cam_initfiles_nl', status=ierr)
92 2 : if (ierr == 0) then
93 2 : read(unitn, cam_initfiles_nl, iostat=ierr)
94 2 : if (ierr /= 0) then
95 0 : call endrun(sub // ': ERROR: reading namelist')
96 : end if
97 : end if
98 2 : close(unitn)
99 2 : call freeunit(unitn)
100 : end if
101 :
102 1536 : call mpi_bcast(ncdata, len(ncdata), mpichar, mstrid, mpicom, ierr)
103 1536 : if (ierr /= 0) call endrun(sub//": ERROR: mpi_bcast: ncdata")
104 1536 : call mpi_bcast(use_topo_file, 1, mpi_logical, mstrid, mpicom, ierr)
105 1536 : if (ierr /= 0) call endrun(sub//": ERROR: mpi_bcast: use_topo_file")
106 1536 : call mpi_bcast(bnd_topo, len(bnd_topo), mpichar, mstrid, mpicom, ierr)
107 1536 : if (ierr /= 0) call endrun(sub//": ERROR: mpi_bcast: bnd_topo")
108 1536 : call mpi_bcast(pertlim, 1, mpir8, mstrid, mpicom, ierr)
109 1536 : if (ierr /= 0) call endrun(sub//": ERROR: mpi_bcast: pertlim")
110 1536 : call mpi_bcast(cam_branch_file, len(cam_branch_file), mpichar, mstrid, mpicom, ierr)
111 1536 : if (ierr /= 0) call endrun(sub//": ERROR: mpi_bcast: cam_branch_file")
112 1536 : call mpi_bcast(scale_dry_air_mass, 1, mpir8, mstrid, mpicom, ierr)
113 1536 : if (ierr /= 0) call endrun(sub//": ERROR: mpi_bcast: scale_dry_air_mass")
114 :
115 : ! Set name of primary restart file
116 1536 : if (restart_run) then
117 : ! Read name of restart file from pointer file
118 768 : if (masterproc) then
119 1 : rest_pfile = interpret_filename_spec("rpointer.cam"//trim(inst_suffix)//".%y-%m-%d-%s", prev=.true.)
120 1 : inquire(file=trim(rest_pfile),exist=found)
121 1 : if(.not. found) then
122 0 : write(iulog, "INFO : rpointer file "//trim(rest_pfile)//" not found.")
123 0 : rest_pfile = "rpointer.cam"//trim(inst_suffix)
124 0 : write(iulog, " Try looking for "//trim(rest_pfile)//" ...")
125 0 : inquire(file=trim(rest_pfile),exist=found)
126 0 : if(.not. found) then
127 0 : call endrun(sub // ': ERROR: rpointer file: '//trim(rest_pfile) // ' not found')
128 : endif
129 : endif
130 1 : unitn = getunit()
131 1 : call opnfil(rest_pfile, unitn, 'f', status="old")
132 1 : read (unitn, '(a)', iostat=ierr) restart_file
133 1 : if (ierr /= 0) then
134 0 : call endrun(sub // ': ERROR: reading rpointer file: '//trim(rest_pfile))
135 : end if
136 1 : close(unitn)
137 1 : call freeunit(unitn)
138 : end if
139 :
140 768 : call mpi_bcast(restart_file, len(restart_file), mpichar, mstrid, mpicom, ierr)
141 768 : if (ierr /= 0) call endrun(sub//": ERROR: mpi_bcast: restart_file")
142 :
143 768 : else if (branch_run) then
144 : ! use namelist input
145 0 : restart_file = trim(cam_branch_file)
146 : end if
147 :
148 : ! Get caseid from restart or branch file.
149 1536 : if (restart_run .or. branch_run) then
150 :
151 768 : call getfil(restart_file, locfn)
152 768 : inquire(file=trim(locfn), exist=filefound)
153 768 : if (.not.filefound) then
154 0 : call endrun(sub//': ERROR: could not find restart file '//trim(locfn))
155 : end if
156 :
157 768 : call cam_pio_openfile(fh_restart, trim(locfn), pio_nowrite)
158 :
159 768 : ierr = pio_inq_att(fh_restart, pio_global, 'caseid', xtype, slen)
160 768 : ierr = pio_get_att(fh_restart, pio_global, 'caseid', caseid_prev)
161 768 : caseid_prev(slen+1:len(caseid_prev)) = ' '
162 :
163 768 : if (branch_run .and. caseid_prev==caseid .and. .not.brnch_retain_casename) then
164 0 : write(iulog,*) sub//': Must change case name on branch run'
165 0 : write(iulog,*) 'Prev case = ',caseid_prev,' current case = ',caseid
166 0 : call endrun(sub//': ERROR: Must change case name on branch run')
167 : end if
168 : end if
169 :
170 1536 : if (masterproc) then
171 2 : write(iulog,*) sub//' options:'
172 :
173 2 : if (initial_run) then
174 :
175 1 : write(iulog,*)' Initial run will start from: ', trim(ncdata)
176 :
177 1 : if (use_topo_file) then
178 1 : write(iulog,*) ' Topography dataset is: ', trim(bnd_topo)
179 : else
180 0 : write(iulog,*) ' Topography dataset not used: PHIS, SGH, SGH30, LANDM_COSLAT set to zero'
181 : end if
182 :
183 1 : else if (restart_run) then
184 1 : write(iulog,*)' Continuation of case: ', trim(caseid_prev)
185 1 : write(iulog,*)' Restart run will start from file: ', trim(restart_file)
186 0 : else if (branch_run) then
187 0 : write(iulog,*)' Continuation of case: ', trim(caseid_prev)
188 0 : write(iulog,*)' Branch run will start from file: ', trim(restart_file)
189 : end if
190 :
191 : write(iulog,*) &
192 2 : ' Maximum abs value of scale factor used to perturb initial conditions, pertlim= ', pertlim
193 2 : if (scale_dry_air_mass > 0) then
194 : write(iulog,*) &
195 2 : ' Initial condition dry mass will be scaled to: ',scale_dry_air_mass,' Pa'
196 : else
197 : write(iulog,*) &
198 0 : ' Initial condition dry mass will not be scaled.'
199 : end if
200 :
201 : #ifdef PERGRO
202 : write(iulog,*)' The PERGRO CPP token is defined.'
203 : #endif
204 :
205 : end if
206 :
207 1536 : end subroutine cam_initfiles_readnl
208 :
209 : !=======================================================================
210 :
211 1536 : subroutine cam_initfiles_open()
212 :
213 : ! Open the initial conditions and topography files.
214 :
215 : character(len=256) :: ncdata_loc ! filepath of initial file on local disk
216 : character(len=256) :: bnd_topo_loc ! filepath of topo file on local disk
217 : !-----------------------------------------------------------------------
218 :
219 : ! Open initial dataset
220 :
221 1536 : if (initial_run) then
222 :
223 768 : call getfil(ncdata, ncdata_loc)
224 768 : allocate(fh_ini)
225 768 : call cam_pio_openfile(fh_ini, ncdata_loc, pio_nowrite)
226 :
227 : else
228 768 : fh_ini => fh_restart
229 : end if
230 :
231 : ! Open topography dataset if used.
232 :
233 1536 : if (use_topo_file) then
234 :
235 1536 : if (trim(bnd_topo) /= 'bnd_topo' .and. len_trim(bnd_topo) > 0) then
236 1536 : allocate(fh_topo)
237 1536 : call getfil(bnd_topo, bnd_topo_loc)
238 1536 : call cam_pio_openfile(fh_topo, bnd_topo_loc, pio_nowrite)
239 : else
240 : ! Allow topography data to be read from the initial file if topo file name
241 : ! is not provided.
242 0 : fh_topo => fh_ini
243 : end if
244 : else
245 0 : nullify(fh_topo)
246 : end if
247 :
248 1536 : end subroutine cam_initfiles_open
249 :
250 : !=======================================================================
251 :
252 3840 : function initial_file_get_id()
253 : type(file_desc_t), pointer :: initial_file_get_id
254 3840 : initial_file_get_id => fh_ini
255 3840 : end function initial_file_get_id
256 :
257 : !=======================================================================
258 :
259 6144 : function topo_file_get_id()
260 : type(file_desc_t), pointer :: topo_file_get_id
261 6144 : topo_file_get_id => fh_topo
262 6144 : end function topo_file_get_id
263 :
264 : !=======================================================================
265 :
266 768 : subroutine cam_initfiles_close()
267 :
268 768 : if (associated(fh_ini)) then
269 :
270 768 : if (associated(fh_topo)) then
271 :
272 768 : if (.not. associated(fh_ini, target=fh_topo)) then
273 : ! if fh_ini and fh_topo point to different objects then close fh_topo
274 768 : call pio_closefile(fh_topo)
275 768 : deallocate(fh_topo)
276 : end if
277 : ! if fh_topo is associated, but points to the same object as fh_ini
278 : ! then it just needs to be nullified.
279 768 : nullify(fh_topo)
280 : end if
281 :
282 768 : call pio_closefile(fh_ini)
283 768 : deallocate(fh_ini)
284 : nullify(fh_ini)
285 :
286 : end if
287 768 : end subroutine cam_initfiles_close
288 :
289 : !=======================================================================
290 :
291 768 : character(len=cl) function cam_initfiles_get_caseid()
292 :
293 : ! Return the caseid of the previous case (i.e., the one read from the restart file)
294 :
295 : character(len=*), parameter :: sub = 'cam_initfiles_get_caseid'
296 : !---------------------------------------------------------------------------
297 :
298 768 : if (initial_run) then
299 0 : call endrun (sub//': ERROR: caseid not read from restart file?')
300 : end if
301 768 : cam_initfiles_get_caseid = caseid_prev
302 :
303 768 : end function cam_initfiles_get_caseid
304 :
305 : !=======================================================================
306 :
307 768 : character(len=cl) function cam_initfiles_get_restdir()
308 :
309 : ! Return directory containing initial restart file
310 :
311 : use filenames, only: get_dir
312 :
313 : character(len=*), parameter :: sub = 'cam_initfiles_get_restdir'
314 : !---------------------------------------------------------------------------
315 :
316 768 : if (initial_run) then
317 0 : call endrun (sub//': ERROR: No restart file available')
318 : end if
319 :
320 768 : cam_initfiles_get_restdir = get_dir(restart_file)
321 :
322 768 : end function cam_initfiles_get_restdir
323 :
324 : !=========================================================================================
325 :
326 : end module cam_initfiles
|