Skip to content

Commit 7e24753

Browse files
authored
Merge branch 'iulian787/erp_fixes_moab' (PR #7731)
Do not write restart files using mct data; use only moab and remove "moab" from the name. mct parts of frankencoupler still needs to read the restart file though (written by moab) [BFB]
2 parents 965ddad + afb8760 commit 7e24753

File tree

4 files changed

+49
-52
lines changed

4 files changed

+49
-52
lines changed

components/eam/src/cpl/atm_comp_mct.F90

Lines changed: 19 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -90,13 +90,13 @@ module atm_comp_mct
9090

9191
private :: atm_setgsmap_mct
9292
private :: atm_domain_mct
93-
private :: atm_read_srfrest_mct
94-
private :: atm_write_srfrest_mct
9593
#ifdef HAVE_MOAB
9694
private :: atm_read_srfrest_moab
9795
private :: atm_write_srfrest_moab
96+
#else
97+
private :: atm_read_srfrest_mct
98+
private :: atm_write_srfrest_mct
9899
#endif
99-
100100
!--------------------------------------------------------------------------
101101
! Private data
102102
!--------------------------------------------------------------------------
@@ -107,10 +107,7 @@ module atm_comp_mct
107107
integer, parameter :: nlen = 256 ! Length of character strings
108108
character(len=nlen) :: fname_srf_cam ! surface restart filename
109109
character(len=nlen) :: pname_srf_cam ! surface restart full pathname
110-
#ifdef HAVE_MOAB
111-
character(len=nlen) :: moab_fname_srf_cam ! surface restart filename
112-
character(len=nlen) :: moab_pname_srf_cam ! surface restart full pathname
113-
#endif
110+
114111
! Filename specifier for restart surface file
115112
character(len=cl) :: rsfilename_spec_cam
116113

@@ -507,12 +504,12 @@ subroutine atm_init_mct( EClock, cdata_a, x2a_a, a2x_a, NLFilename )
507504
call atm_export_moab(Eclock, cam_out)
508505
#endif
509506
else ! if (StepNo != 0) then
510-
511507
call t_startf('atm_read_srfrest_mct')
512508
call atm_read_srfrest_mct( EClock, x2a_a, a2x_a )
513509
call t_stopf('atm_read_srfrest_mct')
514510
#ifdef HAVE_MOAB
515511
call atm_read_srfrest_moab ( EClock )
512+
516513
#endif
517514

518515
! Sent .true. as an optional argument so that restart_init is set to .true. in atm_import
@@ -767,13 +764,15 @@ subroutine atm_run_mct( EClock, cdata_a, x2a_a, a2x_a)
767764
! Write merged surface data restart file if appropriate
768765

769766
if (rstwr_sync) then
767+
768+
#ifdef HAVE_MOAB
769+
call atm_write_srfrest_moab(yr_spec=yr_sync, &
770+
mon_spec=mon_sync, day_spec=day_sync, sec_spec=tod_sync)
771+
#else
770772
call t_startf('atm_write_srfrest_mct')
771773
call atm_write_srfrest_mct( x2a_a, a2x_a, &
772774
yr_spec=yr_sync, mon_spec=mon_sync, day_spec=day_sync, sec_spec=tod_sync)
773775
call t_stopf('atm_write_srfrest_mct')
774-
#ifdef HAVE_MOAB
775-
call atm_write_srfrest_moab(yr_spec=yr_sync, &
776-
mon_spec=mon_sync, day_spec=day_sync, sec_spec=tod_sync)
777776
#endif
778777
end if
779778

@@ -1011,11 +1010,11 @@ subroutine atm_read_srfrest_moab( EClock )
10111010
curr_day=day_spec, curr_tod=sec_spec )
10121011
fname_srf_cam = interpret_filename_spec( rsfilename_spec_cam, case=get_restcase(), &
10131012
yr_spec=yr_spec, mon_spec=mon_spec, day_spec=day_spec, sec_spec= sec_spec )
1014-
moab_fname_srf_cam = 'moab_'//trim(fname_srf_cam)
1015-
moab_pname_srf_cam = trim(get_restartdir() )//trim(moab_fname_srf_cam)
1016-
call getfil(moab_pname_srf_cam, moab_fname_srf_cam)
10171013

1018-
call cam_pio_openfile(File, moab_fname_srf_cam, 0)
1014+
pname_srf_cam = trim(get_restartdir() )//trim(fname_srf_cam)
1015+
call getfil(pname_srf_cam, fname_srf_cam)
1016+
1017+
call cam_pio_openfile(File, fname_srf_cam, 0)
10191018

10201019
call pio_initdecomp(pio_subsystem, pio_double, (/ngcols/), global_ids, iodesc)
10211020

@@ -1125,13 +1124,12 @@ subroutine atm_write_srfrest_moab( yr_spec, mon_spec, day_spec, sec_spec )
11251124

11261125
! Determine and open surface restart dataset
11271126

1128-
! Determine and open surface restart dataset
1127+
fname_srf_cam = interpret_filename_spec( rsfilename_spec_cam, &
1128+
yr_spec=yr_spec, mon_spec=mon_spec, day_spec=day_spec, sec_spec= sec_spec )
11291129

1130-
moab_fname_srf_cam = 'moab_'//trim(fname_srf_cam)
1131-
1132-
call cam_pio_createfile(File, trim(moab_fname_srf_cam))
1130+
call cam_pio_createfile(File, trim(fname_srf_cam))
11331131
if (masterproc) then
1134-
write(iulog,*)'create file :', trim(moab_fname_srf_cam)
1132+
write(iulog,*)'create file :', trim(fname_srf_cam)
11351133
end if
11361134

11371135
call pio_initdecomp(pio_subsystem, pio_double, (/ngcols/), global_ids, iodesc)
@@ -1239,7 +1237,6 @@ subroutine atm_read_srfrest_mct( EClock, x2a_a, a2x_a)
12391237
yr_spec=yr_spec, mon_spec=mon_spec, day_spec=day_spec, sec_spec= sec_spec )
12401238
pname_srf_cam = trim(get_restartdir() )//fname_srf_cam
12411239
call getfil(pname_srf_cam, fname_srf_cam)
1242-
12431240
call cam_pio_openfile(File, fname_srf_cam, 0)
12441241
call pio_initdecomp(pio_subsystem, pio_double, (/ngcols/), dof, iodesc)
12451242
allocate(tmp(size(dof)))
@@ -1309,6 +1306,7 @@ subroutine atm_write_srfrest_mct( x2a_a, a2x_a, &
13091306
type(io_desc_t) :: iodesc
13101307
character(CL) :: itemc ! string converted to char
13111308
type(mct_string) :: mstring ! mct char type
1309+
character(len=nlen) :: tmp_fname_srf_cam
13121310
!-----------------------------------------------------------------------
13131311

13141312
! Determine and open surface restart dataset

driver-moab/main/cime_comp_mod.F90

Lines changed: 1 addition & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -5376,7 +5376,6 @@ subroutine cime_run_write_restart(drv_pause, write_restart, drv_resume_file)
53765376
logical , intent(in) :: drv_pause
53775377
logical , intent(in) :: write_restart
53785378
character(len=*), intent(inout) :: drv_resume_file ! Driver resets state from restart file
5379-
character(len=CL) :: drv_moab_resume_file ! use a different file for moab; do not overwrite the regular name
53805379

53815380
103 format( 5A )
53825381
104 format( A, i10.8, i8)
@@ -5393,21 +5392,13 @@ subroutine cime_run_write_restart(drv_pause, write_restart, drv_resume_file)
53935392
call shr_sys_flush(logunit)
53945393
endif
53955394

5396-
call t_startf('CPL:seq_rest_write')
5397-
call seq_rest_write(EClock_d, seq_SyncClock, infodata, &
5398-
atm, lnd, ice, ocn, rof, glc, wav, esp, iac, &
5399-
fractions_ax, fractions_lx, fractions_ix, fractions_ox, &
5400-
fractions_rx, fractions_gx, fractions_wx, fractions_zx, &
5401-
trim(cpl_inst_tag), drv_resume_file)
5402-
call t_stopf('CPL:seq_rest_write')
5403-
54045395
#ifdef MOABDEBUG
54055396
call write_moab_state( .true. )
54065397
#endif
54075398
call t_startf('CPL:seq_rest_mb_write')
54085399
call seq_rest_mb_write(EClock_d, seq_SyncClock, infodata, &
54095400
atm, lnd, ice, ocn, rof, glc, wav, esp, iac, &
5410-
trim(cpl_inst_tag), samegrid_al, samegrid_lr, drv_moab_resume_file)
5401+
trim(cpl_inst_tag), samegrid_al, samegrid_lr, drv_resume_file)
54115402
call t_stopf('CPL:seq_rest_mb_write')
54125403

54135404
if (iamroot_CPLID) then

driver-moab/main/component_mod.F90

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -788,7 +788,7 @@ subroutine component_init_areacor_moab (comp, mbccid, mbcxid, seq_flds_c2x_fluxe
788788
! get areas
789789
tagname='area:aream:mask'//C_NULL_CHAR
790790
arrsize = 3 * lsize
791-
ierr = iMOAB_GetDoubleTagStorage ( mbccid, tagname, arrsize , comp(1)%mbGridType, areas )
791+
ierr = iMOAB_GetDoubleTagStorage ( mbccid, tagname, arrsize , comp(1)%mbGridType, areas(1,1) )
792792
if (ierr .ne. 0) then
793793
call shr_sys_abort(subname//' cannot get areas ')
794794
endif
@@ -820,7 +820,7 @@ subroutine component_init_areacor_moab (comp, mbccid, mbcxid, seq_flds_c2x_fluxe
820820
call shr_sys_abort(subname//' cannot define correction tags')
821821
endif
822822
arrsize = 2 * lsize
823-
ierr = iMOAB_SetDoubleTagStorage( mbccid, tagname, arrsize , comp(1)%mbGridType, factors)
823+
ierr = iMOAB_SetDoubleTagStorage( mbccid, tagname, arrsize , comp(1)%mbGridType, factors(1,1))
824824
if (ierr .ne. 0) then
825825
call shr_sys_abort(subname//' cannot set correction area factors ')
826826
endif
@@ -854,7 +854,7 @@ subroutine component_init_areacor_moab (comp, mbccid, mbcxid, seq_flds_c2x_fluxe
854854
allocate(vals(lsize, nfields))
855855
tagname = trim(seq_flds_c2x_fluxes)//C_NULL_CHAR
856856
arrsize = lsize * nfields
857-
ierr = iMOAB_GetDoubleTagStorage( mbccid, tagname, arrsize, comp(1)%mbGridType, vals )
857+
ierr = iMOAB_GetDoubleTagStorage( mbccid, tagname, arrsize, comp(1)%mbGridType, vals(1,1) )
858858
if (ierr .ne. 0) then
859859
call shr_sys_abort(subname//' cannot get flux values: '//tagname)
860860
endif
@@ -868,7 +868,7 @@ subroutine component_init_areacor_moab (comp, mbccid, mbcxid, seq_flds_c2x_fluxe
868868
enddo
869869
endif
870870
enddo
871-
ierr = iMOAB_SetDoubleTagStorage( mbccid, tagname, arrsize, comp(1)%mbGridType, vals)
871+
ierr = iMOAB_SetDoubleTagStorage( mbccid, tagname, arrsize, comp(1)%mbGridType, vals(1,1))
872872
if (ierr .ne. 0) then
873873
call shr_sys_abort(subname//' cannot set new flux values ')
874874
endif
@@ -1267,7 +1267,7 @@ subroutine factor_moab_comp(comp, type, seq_flds_fluxes, mask_spval)
12671267
! get vals, multiply, then reset them again
12681268
tagname = trim(seq_flds_fluxes)//C_NULL_CHAR
12691269
arrsize = comp%mblsize * nfields
1270-
ierr = iMOAB_GetDoubleTagStorage( comp%mbApCCid, tagname, arrsize , comp%mbGridType, vals)
1270+
ierr = iMOAB_GetDoubleTagStorage( comp%mbApCCid, tagname, arrsize , comp%mbGridType, vals(1,1))
12711271
if (ierr .ne. 0) then
12721272
call shr_sys_abort(subname//' cannot get fluxes ' //trim(type))
12731273
endif

driver-moab/main/seq_rest_mod.F90

Lines changed: 24 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -398,7 +398,8 @@ subroutine seq_rest_mb_read(rest_file, infodata, samegrid_al, samegrid_lr)
398398
!
399399
!-------------------------------------------------------------------------------
400400
! actual moab name is
401-
moab_rest_file = 'moab_'//trim(rest_file)
401+
!moab_rest_file = 'moab_'//trim(rest_file)
402+
moab_rest_file = trim(rest_file)
402403
!----------------------------------------------------------------------------
403404
! get required infodata
404405
!----------------------------------------------------------------------------
@@ -641,7 +642,7 @@ subroutine seq_rest_write(EClock_d, seq_SyncClock, infodata, &
641642
atm, lnd, ice, ocn, rof, glc, wav, esp, iac, &
642643
fractions_ax, fractions_lx, fractions_ix, fractions_ox, &
643644
fractions_rx, fractions_gx, fractions_wx, fractions_zx, &
644-
tag, rest_file)
645+
tag, rest_file_org)
645646

646647
implicit none
647648

@@ -666,7 +667,9 @@ subroutine seq_rest_write(EClock_d, seq_SyncClock, infodata, &
666667
type(mct_aVect) , intent(inout) :: fractions_wx(:) ! Fractions on wav grid/decomp
667668
type(mct_aVect) , intent(inout) :: fractions_zx(:) ! Fractions on iac grid/decomp
668669
character(len=*) , intent(in) :: tag
669-
character(len=CL) , intent(out) :: rest_file ! Restart filename
670+
character(len=CL) , intent(out) :: rest_file_org ! Restart filename
671+
672+
character(len=CL) :: rest_file ! pre-pend with mct_
670673

671674
integer(IN) :: n,n1,n2,n3,fk
672675
integer(IN) :: curr_ymd ! Current date YYYYMMDD
@@ -736,9 +739,13 @@ subroutine seq_rest_write(EClock_d, seq_SyncClock, infodata, &
736739
call seq_timemgr_EClockGetData( EClock_d, curr_ymd=curr_ymd, curr_tod=curr_tod)
737740
call shr_cal_date2ymd(curr_ymd,yy,mm,dd)
738741
write(year_char,'(i6.4)') yy
739-
write(rest_file,"(4a,i2.2,a,i2.2,a,i5.5,a)") &
742+
write(rest_file_org,"(4a,i2.2,a,i2.2,a,i5.5,a)") &
740743
trim(case_name), '.cpl'//trim(tag)//'.r.',trim(adjustl(year_char)),'-',mm,'-',dd,'-',curr_tod,'.nc'
741744

745+
rest_file = 'mct_'//trim(rest_file_org) ! will actually write here, and return the original name
746+
! moab will write the original one, and read the original one; mct will read the original too
747+
! for the time being, read twice, the same file;; comapre mct_ one with original one to see how different
748+
! they are ! tehy should be no different
742749
! Write driver data to restart file
743750

744751
if (iamin_CPLID) then
@@ -785,7 +792,7 @@ subroutine seq_rest_write(EClock_d, seq_SyncClock, infodata, &
785792
if (loglevel > 0) write(logunit,"(3A)") subname," write rpointer file ", &
786793
trim(cvar)
787794
open(iun, file=cvar, form='FORMATTED')
788-
write(iun,'(a)') rest_file
795+
write(iun,'(a)') rest_file_org ! will write to rpointer file the origname, not the one with mct in it
789796
close(iun)
790797
call shr_file_freeUnit( iun )
791798
endif
@@ -1061,7 +1068,8 @@ subroutine seq_rest_mb_write(EClock_d, seq_SyncClock, infodata, &
10611068
call shr_cal_date2ymd(curr_ymd,yy,mm,dd)
10621069
write(year_char,'(i6.4)') yy
10631070
write(rest_file,"(4a,i2.2,a,i2.2,a,i5.5,a)") &
1064-
'moab_'//trim(case_name), '.cpl'//trim(tag)//'.r.',trim(adjustl(year_char)),'-',mm,'-',dd,'-',curr_tod,'.nc'
1071+
trim(case_name), '.cpl'//trim(tag)//'.r.',trim(adjustl(year_char)),'-',mm,'-',dd,'-',curr_tod,'.nc'
1072+
! 'moab_'//trim(case_name), '.cpl'//trim(tag)//'.r.',trim(adjustl(year_char)),'-',mm,'-',dd,'-',curr_tod,'.nc'
10651073

10661074
! Write driver data to restart file
10671075

@@ -1103,16 +1111,16 @@ subroutine seq_rest_mb_write(EClock_d, seq_SyncClock, infodata, &
11031111
enddo
11041112
endif
11051113

1106-
! if (cplroot) then
1107-
! iun = shr_file_getUnit()
1108-
! call seq_infodata_GetData(infodata,restart_pfile=cvar)
1109-
! if (loglevel > 0) write(logunit,"(3A)") subname," write rpointer file ", &
1110-
! trim(cvar)
1111-
! open(iun, file=cvar, form='FORMATTED')
1112-
! write(iun,'(a)') rest_file
1113-
! close(iun)
1114-
! call shr_file_freeUnit( iun )
1115-
! endif
1114+
if (cplroot) then
1115+
iun = shr_file_getUnit()
1116+
call seq_infodata_GetData(infodata,restart_pfile=cvar)
1117+
if (loglevel > 0) write(logunit,"(3A)") subname," write rpointer file ", &
1118+
trim(cvar)
1119+
open(iun, file=cvar, form='FORMATTED')
1120+
write(iun,'(a)') rest_file
1121+
close(iun)
1122+
call shr_file_freeUnit( iun )
1123+
endif
11161124

11171125
call shr_mpi_bcast(rest_file,mpicom_CPLID)
11181126
call seq_io_wopen(rest_file,clobber=.true., model_doi_url=model_doi_url)

0 commit comments

Comments
 (0)