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 : ! The restart pointer file contains name of most recently written primary restart file.
46 : ! The contents of this file are updated by cam_write_restart as new restart files are written.
47 : character(len=cl), public, protected :: rest_pfile
48 :
49 : ! Filename for initial restart file.
50 : character(len=cl) :: restart_file = ' '
51 :
52 : ! case name read from initial restart file. This case name matches the caseid
53 : ! which is embedded in the filename.
54 : character(len=cl) :: caseid_prev = ' '
55 :
56 : type(file_desc_t), pointer :: fh_ini => null()
57 : type(file_desc_t), pointer :: fh_topo => null()
58 : type(file_desc_t), target :: fh_restart
59 :
60 : !========================================================================================
61 : contains
62 : !========================================================================================
63 :
64 2304 : subroutine cam_initfiles_readnl(nlfile)
65 :
66 : use namelist_utils, only: find_group_name
67 : use units, only: getunit, freeunit
68 : use spmd_utils, only: mpicom, mstrid=>masterprocid, mpir8=>mpi_real8, &
69 : mpichar=>mpi_character, mpi_logical
70 : use cam_instance, only: inst_suffix
71 :
72 : character(len=*), intent(in) :: nlfile ! filepath for file containing namelist input
73 :
74 : ! Local variables
75 : integer :: unitn, ierr
76 :
77 : character(len=cl) :: locfn
78 : logical :: filefound
79 : integer :: xtype
80 : integer(pio_offset_kind) :: slen
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 pointer file name based on instance suffix
116 1536 : rest_pfile = './rpointer.atm' // trim(inst_suffix)
117 :
118 : ! Set name of primary restart file
119 1536 : if (restart_run) then
120 : ! Read name of restart file from pointer file
121 768 : if (masterproc) then
122 1 : unitn = getunit()
123 1 : call opnfil(rest_pfile, unitn, 'f', status="old")
124 1 : read (unitn, '(a)', iostat=ierr) restart_file
125 1 : if (ierr /= 0) then
126 0 : call endrun(sub // ': ERROR: reading rpointer file')
127 : end if
128 1 : close(unitn)
129 1 : call freeunit(unitn)
130 : end if
131 :
132 768 : call mpi_bcast(restart_file, len(restart_file), mpichar, mstrid, mpicom, ierr)
133 768 : if (ierr /= 0) call endrun(sub//": ERROR: mpi_bcast: restart_file")
134 :
135 768 : else if (branch_run) then
136 : ! use namelist input
137 0 : restart_file = trim(cam_branch_file)
138 : end if
139 :
140 : ! Get caseid from restart or branch file.
141 1536 : if (restart_run .or. branch_run) then
142 :
143 768 : call getfil(restart_file, locfn)
144 768 : inquire(file=trim(locfn), exist=filefound)
145 768 : if (.not.filefound) then
146 0 : call endrun(sub//': ERROR: could not find restart file '//trim(locfn))
147 : end if
148 :
149 768 : call cam_pio_openfile(fh_restart, trim(locfn), pio_nowrite)
150 :
151 768 : ierr = pio_inq_att(fh_restart, pio_global, 'caseid', xtype, slen)
152 768 : ierr = pio_get_att(fh_restart, pio_global, 'caseid', caseid_prev)
153 768 : caseid_prev(slen+1:len(caseid_prev)) = ' '
154 :
155 768 : if (branch_run .and. caseid_prev==caseid .and. .not.brnch_retain_casename) then
156 0 : write(iulog,*) sub//': Must change case name on branch run'
157 0 : write(iulog,*) 'Prev case = ',caseid_prev,' current case = ',caseid
158 0 : call endrun(sub//': ERROR: Must change case name on branch run')
159 : end if
160 : end if
161 :
162 1536 : if (masterproc) then
163 2 : write(iulog,*) sub//' options:'
164 :
165 2 : if (initial_run) then
166 :
167 1 : write(iulog,*)' Initial run will start from: ', trim(ncdata)
168 :
169 1 : if (use_topo_file) then
170 0 : write(iulog,*) ' Topography dataset is: ', trim(bnd_topo)
171 : else
172 1 : write(iulog,*) ' Topography dataset not used: PHIS, SGH, SGH30, LANDM_COSLAT set to zero'
173 : end if
174 :
175 1 : else if (restart_run) then
176 1 : write(iulog,*)' Continuation of case: ', trim(caseid_prev)
177 1 : write(iulog,*)' Restart run will start from file: ', trim(restart_file)
178 0 : else if (branch_run) then
179 0 : write(iulog,*)' Continuation of case: ', trim(caseid_prev)
180 0 : write(iulog,*)' Branch run will start from file: ', trim(restart_file)
181 : end if
182 :
183 : write(iulog,*) &
184 2 : ' Maximum abs value of scale factor used to perturb initial conditions, pertlim= ', pertlim
185 2 : if (scale_dry_air_mass > 0) then
186 : write(iulog,*) &
187 2 : ' Initial condition dry mass will be scaled to: ',scale_dry_air_mass,' Pa'
188 : else
189 : write(iulog,*) &
190 0 : ' Initial condition dry mass will not be scaled.'
191 : end if
192 :
193 : #ifdef PERGRO
194 : write(iulog,*)' The PERGRO CPP token is defined.'
195 : #endif
196 :
197 : end if
198 :
199 1536 : end subroutine cam_initfiles_readnl
200 :
201 : !=======================================================================
202 :
203 1536 : subroutine cam_initfiles_open()
204 :
205 : ! Open the initial conditions and topography files.
206 :
207 : character(len=256) :: ncdata_loc ! filepath of initial file on local disk
208 : character(len=256) :: bnd_topo_loc ! filepath of topo file on local disk
209 : !-----------------------------------------------------------------------
210 :
211 : ! Open initial dataset
212 :
213 1536 : if (initial_run) then
214 :
215 768 : call getfil(ncdata, ncdata_loc)
216 768 : allocate(fh_ini)
217 768 : call cam_pio_openfile(fh_ini, ncdata_loc, pio_nowrite)
218 :
219 : else
220 768 : fh_ini => fh_restart
221 : end if
222 :
223 : ! Open topography dataset if used.
224 :
225 1536 : if (use_topo_file) then
226 :
227 0 : if (trim(bnd_topo) /= 'bnd_topo' .and. len_trim(bnd_topo) > 0) then
228 0 : allocate(fh_topo)
229 0 : call getfil(bnd_topo, bnd_topo_loc)
230 0 : call cam_pio_openfile(fh_topo, bnd_topo_loc, pio_nowrite)
231 : else
232 : ! Allow topography data to be read from the initial file if topo file name
233 : ! is not provided.
234 0 : fh_topo => fh_ini
235 : end if
236 : else
237 1536 : nullify(fh_topo)
238 : end if
239 :
240 1536 : end subroutine cam_initfiles_open
241 :
242 : !=======================================================================
243 :
244 3840 : function initial_file_get_id()
245 : type(file_desc_t), pointer :: initial_file_get_id
246 3840 : initial_file_get_id => fh_ini
247 3840 : end function initial_file_get_id
248 :
249 : !=======================================================================
250 :
251 3072 : function topo_file_get_id()
252 : type(file_desc_t), pointer :: topo_file_get_id
253 3072 : topo_file_get_id => fh_topo
254 3072 : end function topo_file_get_id
255 :
256 : !=======================================================================
257 :
258 768 : subroutine cam_initfiles_close()
259 :
260 768 : if (associated(fh_ini)) then
261 :
262 768 : if (associated(fh_topo)) then
263 :
264 0 : if (.not. associated(fh_ini, target=fh_topo)) then
265 : ! if fh_ini and fh_topo point to different objects then close fh_topo
266 0 : call pio_closefile(fh_topo)
267 0 : deallocate(fh_topo)
268 : end if
269 : ! if fh_topo is associated, but points to the same object as fh_ini
270 : ! then it just needs to be nullified.
271 0 : nullify(fh_topo)
272 : end if
273 :
274 768 : call pio_closefile(fh_ini)
275 768 : deallocate(fh_ini)
276 : nullify(fh_ini)
277 :
278 : end if
279 768 : end subroutine cam_initfiles_close
280 :
281 : !=======================================================================
282 :
283 768 : character(len=cl) function cam_initfiles_get_caseid()
284 :
285 : ! Return the caseid of the previous case (i.e., the one read from the restart file)
286 :
287 : character(len=*), parameter :: sub = 'cam_initfiles_get_caseid'
288 : !---------------------------------------------------------------------------
289 :
290 768 : if (initial_run) then
291 0 : call endrun (sub//': ERROR: caseid not read from restart file?')
292 : end if
293 768 : cam_initfiles_get_caseid = caseid_prev
294 :
295 768 : end function cam_initfiles_get_caseid
296 :
297 : !=======================================================================
298 :
299 768 : character(len=cl) function cam_initfiles_get_restdir()
300 :
301 : ! Return directory containing initial restart file
302 :
303 : use filenames, only: get_dir
304 :
305 : character(len=*), parameter :: sub = 'cam_initfiles_get_restdir'
306 : !---------------------------------------------------------------------------
307 :
308 768 : if (initial_run) then
309 0 : call endrun (sub//': ERROR: No restart file available')
310 : end if
311 :
312 768 : cam_initfiles_get_restdir = get_dir(restart_file)
313 :
314 768 : end function cam_initfiles_get_restdir
315 :
316 : !=========================================================================================
317 :
318 : end module cam_initfiles
|