module atm_comp_esmf #ifdef ESMF_INTERFACE use esmf use esmfshr_util_mod use pio , only: file_desc_t, io_desc_t, var_desc_t, pio_double, pio_def_dim, & pio_put_att, pio_enddef, pio_initdecomp, pio_read_darray, pio_freedecomp, & pio_closefile, pio_write_darray, pio_def_var, pio_inq_varid, & pio_noerr, pio_bcast_error, pio_internal_error, pio_seterrorhandling use seq_flds_mod use seq_timemgr_mod use shr_kind_mod , only: r8 => shr_kind_r8, cs=>shr_kind_cs, cl=>shr_kind_cl use shr_file_mod , only: shr_file_getunit, shr_file_freeunit, & shr_file_setLogUnit, shr_file_setLogLevel, & shr_file_getLogUnit, shr_file_getLogLevel, & shr_file_setIO use shr_sys_mod , only: shr_sys_flush, shr_sys_abort use cam_cpl_indices use atm_import_export use cam_comp, only: cam_init, cam_run1, cam_run2, cam_run3, cam_run4, cam_final use cam_instance , only: cam_instance_init, inst_suffix use cam_control_mod , only: initial_run, cam_ctrl_set_orbit use radiation , only: radiation_nextsw_cday use phys_grid , only: get_ncols_p, get_gcol_all_p, get_gcol_p, ngcols, & get_rlat_all_p, get_rlon_all_p, get_area_all_p use ppgrid , only: pcols, begchunk, endchunk use dyn_grid , only: get_horiz_grid_dim_d use camsrfexch , only: cam_out_t, cam_in_t use cam_initfiles , only: cam_initfiles_get_caseid, cam_initfiles_get_restdir use filenames , only: interpret_filename_spec use spmd_utils , only: spmdinit, masterproc use time_manager , only: get_curr_calday, advance_timestep, get_curr_date, get_nstep, & get_step_size use ioFileMod use perf_mod use cam_logfile , only: iulog implicit none save private !-------------------------------------------------------------------------- ! Public interfaces !-------------------------------------------------------------------------- public :: atm_register_esmf public :: atm_init_esmf public :: atm_run_esmf public :: atm_final_esmf !-------------------------------------------------------------------------- ! Private interfaces !-------------------------------------------------------------------------- private :: atm_distgrid_esmf private :: atm_domain_esmf private :: atm_read_srfrest_esmf private :: atm_write_srfrest_esmf !-------------------------------------------------------------------------- ! Private data !-------------------------------------------------------------------------- type(cam_in_t) , pointer :: cam_in(:) type(cam_out_t), pointer :: cam_out(:) integer, parameter :: nlen = 256 ! Length of character strings character(len=nlen) :: fname_srf_cam ! surface restart filename character(len=nlen) :: pname_srf_cam ! surface restart full pathname ! Filename specifier for restart surface file character(len=cl) :: rsfilename_spec_cam integer, pointer :: dof(:) ! needed for pio_init decomp for restarts !================================================================================ CONTAINS !================================================================================ subroutine atm_register_esmf(comp, rc) implicit none type(ESMF_GridComp) :: comp integer, intent(out) :: rc rc = ESMF_SUCCESS ! Register the callback routines. call ESMF_GridCompSetEntryPoint(comp, ESMF_METHOD_INITIALIZE, & atm_init_esmf, phase=1, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_GridCompSetEntryPoint(comp, ESMF_METHOD_RUN, & atm_run_esmf, phase=1, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_GridCompSetEntryPoint(comp, ESMF_METHOD_FINALIZE, & atm_final_esmf, phase=1, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) end subroutine !================================================================================ subroutine atm_init_esmf(comp, import_state, export_state, EClock, rc) !----------------------------------------------------------------------- ! ! Arguments ! implicit none type(ESMF_GridComp) :: comp type(ESMF_State) :: import_state type(ESMF_State) :: export_state type(ESMF_Clock) :: EClock integer, intent(out) :: rc ! ! Locals ! integer :: ATMID ! atm component instance ID integer :: mpicom_atm, mpicom_vm logical :: first_time = .true. logical :: exists integer :: shrlogunit,shrloglev ! save values; restore on return character(len=cs) :: starttype ! infodata start type character(len=cl) :: caseid ! case ID character(len=cl) :: ctitle ! case title logical :: adiabatic ! true => no physics logical :: ideal_phys ! true => run "idealized" model configuration logical :: aqua_planet ! Flag to run model in "aqua planet" mode logical :: brnch_retain_casename! true => branch run may use same caseid as ! the run being branched from logical :: single_column real(r8) :: scmlat,scmlon real(r8) :: eccen real(r8) :: obliqr real(r8) :: lambm0 real(r8) :: mvelpp logical :: perpetual_run ! If in perpetual mode or not integer :: perpetual_ymd ! Perpetual date (YYYYMMDD) real(r8) :: nextsw_cday ! calendar of next atm shortwave integer :: stepno ! time step integer :: dtime ! time step increment (sec) integer :: atm_cpl_dt ! driver atm coupling time step integer :: nstep ! CAM nstep real(r8) :: caldayp1 ! CAM calendar day for for next cam time step integer :: nfields integer :: lbnum integer :: hdim1_d, hdim2_d ! dimensions of rectangular horizontal grid ! data structure, If 1D data structure, then ! hdim2_d == 1. type(ESMF_ArraySpec) :: arrayspec type(ESMF_DistGrid) :: distgrid type(ESMF_Array) :: a2x, x2a, dom type(ESMF_VM) :: vm integer :: nflds, gsize, dsize real(R8), pointer :: fptr(:,:) ! pointer into array data character(ESMF_MAXSTR) :: convCIM, purpComp !----------------------------------------------------------------------- rc = ESMF_SUCCESS ! duplicate the mpi communicator from the current VM call ESMF_VMGetCurrent(vm, rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_VMGet(vm, mpiCommunicator=mpicom_vm, rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call MPI_Comm_dup(mpicom_vm, mpicom_atm, rc) if(rc /= 0) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) if (first_time) then ! Initialize cam id call ESMF_AttributeGet(export_state, name="ID", value=ATMID, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call cam_instance_init(ATMID) ! Set filename specifier for restart surface file ! (%c=caseid, $y=year, $m=month, $d=day, $s=seconds in day) rsfilename_spec_cam = '%c.cam' // trim(inst_suffix) // '.rs.%y-%m-%d-%s.nc' ! Determine attribute vector indices call cam_cpl_indices_set() ! Initialize atm use of MPI call spmdinit(mpicom_atm) #if (defined _MEMTRACE) if(masterproc) then lbnum=1 call memmon_dump_fort('memmon.out','atm_init_esmf:start::',lbnum) endif #endif ! Redirect share output to cam log if (masterproc) then inquire(file='atm_modelio.nml'//trim(inst_suffix), exist=exists) if (exists) then iulog = shr_file_getUnit() call shr_file_setIO('atm_modelio.nml'//trim(inst_suffix), iulog) endif write(iulog,*) "CAM atmosphere model initialization" endif call shr_file_getLogUnit (shrlogunit) call shr_file_getLogLevel(shrloglev) call shr_file_setLogUnit (iulog) ! ! Get attributes from export state ! call ESMF_AttributeGet(export_state, name="case_name", value=caseid, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="case_desc", value=ctitle, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="start_type", value=starttype, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="atm_adiabatic", value=adiabatic, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="atm_ideal_phys", value=ideal_phys, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="aqua_planet", value=aqua_planet, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="brnch_retain_casename", value=brnch_retain_casename, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="single_column", value=single_column, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="scmlat", value=scmlat, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="scmlon", value=scmlon, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="orb_eccen", value=eccen, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="orb_mvelpp", value=mvelpp, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="orb_lambm0", value=lambm0, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="orb_obliqr", value=obliqr, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="perpetual", value=perpetual_run, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="perpetual_ymd", value=perpetual_ymd, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) ! Initialize CAM, allocate cam_in and cam_out and determine ! atm decomposition ! for an initial run, cam_in and cam_out are allocated in cam_init ! for a restart/branch run, cam_in and cam_out are allocated in restart ! call cam_init(EClock, & caseid, ctitle, starttype, brnch_retain_casename, & adiabatic, ideal_phys, aqua_planet, & single_column, scmlat, scmlon, & eccen, obliqr, lambm0, mvelpp, & perpetual_run, perpetual_ymd, & cam_out, cam_in) ! Add gsize attribute to export state call ESMF_AttributeSet(export_state, name="gsize", value=ngcols, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) !----------------------------------------- ! Initialize distgrid !----------------------------------------- distgrid = atm_distgrid_esmf() !----------------------------------------- ! Set arrayspec for dom, a2x and x2a !----------------------------------------- call ESMF_ArraySpecSet(arrayspec, rank=2, typekind=ESMF_TYPEKIND_R8, rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) !----------------------------------------- ! Create dom !----------------------------------------- nfields = shr_string_listGetNum(trim(seq_flds_dom_fields)) dom = ESMF_ArrayCreate(distgrid=distgrid, arrayspec=arrayspec, distgridToArrayMap=(/2/), & undistLBound=(/1/), undistUBound=(/nfields/), name="domain", rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeSet(dom, name="mct_names", value=trim(seq_flds_dom_fields), rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) ! Set values of dom call atm_domain_esmf(dom, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) !----------------------------------------- ! Get dof for pio srf restarts !----------------------------------------- ! set dsize from elementcount call ESMF_DistGridGet(distgrid, localDe=0, elementCount=dsize, rc=rc) if(rc /= 0) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) ! allocate dof allocate(dof(dsize), stat=rc) ! set dof from seqindexlist call ESMF_DistGridGet(distgrid, localDe=0, seqIndexList=dof, rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) !----------------------------------------- ! Create a2x !----------------------------------------- ! 1d undistributed index of fields, 2d is packed data nfields = shr_string_listGetNum(trim(seq_flds_a2x_fields)) a2x = ESMF_ArrayCreate(distgrid=distgrid, arrayspec=arrayspec, distgridToArrayMap=(/2/), & undistLBound=(/1/), undistUBound=(/nfields/), name="d2x", rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeSet(a2x, name="mct_names", value=trim(seq_flds_a2x_fields), rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) !----------------------------------------- ! Create x2a !----------------------------------------- nfields = shr_string_listGetNum(trim(seq_flds_x2a_fields)) x2a = ESMF_ArrayCreate(distgrid=distgrid, arrayspec=arrayspec, distgridToArrayMap=(/2/), & undistLBound=(/1/), undistUBound=(/nfields/), name="x2d", rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeSet(x2a, name="mct_names", value=trim(seq_flds_x2a_fields), rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) !----------------------------------------- ! Add esmf arrays to import and export state !----------------------------------------- call ESMF_StateAdd(export_state, (/dom/), rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_StateAdd(export_state, (/a2x/), rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_StateAdd(import_state, (/x2a/), rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) ! ---- Fill in atm_export state ---- call ESMF_ArrayGet(a2x, localDe=0, farrayPtr=fptr, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call atm_export(cam_out, fptr) ! Set flag to specify that an extra albedo calculation is to be done (i.e. specify active) call ESMF_AttributeSet(export_state, name="atm_prognostic", value=.true., rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call get_horiz_grid_dim_d(hdim1_d, hdim2_d) call ESMF_AttributeSet(export_state, name="atm_nx", value=hdim1_d, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeSet(export_state, name="atm_ny", value=hdim2_d, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) ! Set flag to indicate that CAM will provide carbon and dust deposition fluxes. ! This is now hardcoded to .true. since the ability of CICE to read these ! fluxes from a file has been removed. call ESMF_AttributeSet(export_state, name="atm_aero", value=.true., rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) ! Set time step of radiation computation as the current calday ! This will only be used on the first timestep of an initial run if (initial_run) then nextsw_cday = get_curr_calday() call ESMF_AttributeSet(export_state, name="nextsw_cday", value=nextsw_cday, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) end if ! ---- End redirection of share output to cam log ---- call shr_file_setLogUnit (shrlogunit) call shr_file_setLogLevel(shrloglev) first_time = .false. else ! For initial run, run cam radiation/clouds and return ! For restart run, read restart x2a_a ! Note - a2x_a is computed upon the completion of the previous run - cam_run1 is called ! only for the purposes of finishing the flux averaged calculation to compute a2x_a ! Note - cam_run1 is called on restart only to have cam internal state consistent with the ! a2x_a state sent to the coupler ! Redirect share output to cam log call shr_file_getLogUnit (shrlogunit) call shr_file_getLogLevel(shrloglev) call shr_file_setLogUnit (iulog) call ESMF_StateGet(export_state, itemName="domain", array=dom, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_StateGet(export_state, itemName="d2x", array=a2x, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_StateGet(import_state, itemName="x2d", array=x2a, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call seq_timemgr_EClockGetData(EClock, StepNo=StepNo) if (StepNo == 0) then call ESMF_ArrayGet(x2a, localDe=0, farrayPtr=fptr, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call atm_import(fptr, cam_in) call cam_run1(cam_in, cam_out) call ESMF_ArrayGet(a2x, localDe=0, farrayPtr=fptr, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call atm_export(cam_out, fptr) else call atm_read_srfrest_esmf( EClock, x2a, a2x ) call ESMF_ArrayGet(x2a, localDe=0, farrayPtr=fptr, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call atm_import(fptr, cam_in, restart_init=.true.) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call cam_run1(cam_in, cam_out) end if ! Compute time of next radiation computation, like in run method for exact restart call seq_timemgr_EClockGetData(Eclock,dtime=atm_cpl_dt) dtime = get_step_size() nstep = get_nstep() if (nstep < 1 .or. dtime < atm_cpl_dt) then nextsw_cday = radiation_nextsw_cday() else if (dtime == atm_cpl_dt) then caldayp1 = get_curr_calday(offset=int(dtime)) nextsw_cday = radiation_nextsw_cday() if (caldayp1 /= nextsw_cday) nextsw_cday = -1._r8 else call shr_sys_abort('dtime must be less than or equal to atm_cpl_dt') end if call ESMF_AttributeSet(export_state, name="nextsw_cday", value=nextsw_cday, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) ! End redirection of share output to cam log call shr_file_setLogUnit (shrlogunit) call shr_file_setLogLevel(shrloglev) end if #if (defined _MEMTRACE ) if(masterproc) then lbnum=1 call memmon_reset_addr() endif #endif #ifdef USE_ESMF_METADATA !convCIM = "CIM 1.0" convCIM = "CIM" purpComp = "Model Component Simulation Description" call ESMF_AttributeAdd(comp, & convention=convCIM, purpose=purpComp, rc=rc) call ESMF_AttributeSet(comp, "ShortName", "CAM", & convention=convCIM, purpose=purpComp, rc=rc) call ESMF_AttributeSet(comp, "LongName", & "Community Atmosphere Model", & convention=convCIM, purpose=purpComp, rc=rc) call ESMF_AttributeSet(comp, "Description", & "Version 5.0 of the Community Atmosphere Model (CAM) " // & "is the latest in a series of global atmosphere models " // & "developed primarily at the National Center for " // & "Atmospheric Research (NCAR). CAM 5.0 includes " // & "significant enhancements to the representation of " // & "atmospheric processes resulting in a number of notable " // & "improvements. CAM 4.0 is also available in the CESM " // & "1.0 release. Development of the model was led by the " // & "Atmosphere Model Working Group (AMWG).", & convention=convCIM, purpose=purpComp, rc=rc) call ESMF_AttributeSet(comp, "ReleaseDate", "2010", & convention=convCIM, purpose=purpComp, rc=rc) call ESMF_AttributeSet(comp, "ModelType", "Atmosphere", & convention=convCIM, purpose=purpComp, rc=rc) ! call ESMF_AttributeSet(comp, "Name", "Cecile Hannay", & ! convention=convCIM, purpose=purpComp, rc=rc) ! call ESMF_AttributeSet(comp, "EmailAddress", & ! "hannay@ucar.edu", & ! convention=convCIM, purpose=purpComp, rc=rc) ! call ESMF_AttributeSet(comp, "ResponsiblePartyRole", "contact", & ! convention=convCIM, purpose=purpComp, rc=rc) #endif call shr_sys_flush(iulog) end subroutine atm_init_esmf !================================================================================ subroutine atm_run_esmf(comp, import_state, export_state, EClock, rc) !----------------------------------------------------------------------- ! ! Arguments ! type(ESMF_GridComp) :: comp type(ESMF_State) :: import_state type(ESMF_State) :: export_state type(ESMF_Clock) :: EClock integer, intent(out) :: rc ! ! Local variables ! real(r8) :: eccen real(r8) :: obliqr real(r8) :: lambm0 real(r8) :: mvelpp logical :: dosend ! true => send data back to driver integer :: dtime ! time step increment (sec) integer :: atm_cpl_dt ! driver atm coupling time step integer :: ymd_sync ! Sync date (YYYYMMDD) integer :: yr_sync ! Sync current year integer :: mon_sync ! Sync current month integer :: day_sync ! Sync current day integer :: tod_sync ! Sync current time of day (sec) integer :: ymd ! CAM current date (YYYYMMDD) integer :: yr ! CAM current year integer :: mon ! CAM current month integer :: day ! CAM current day integer :: tod ! CAM current time of day (sec) integer :: nstep ! CAM nstep integer :: shrlogunit ! old value integer :: shrloglev ! old value real(r8):: caldayp1 ! CAM calendar day for for next cam time step real(r8):: nextsw_cday ! calendar of next atm shortwave logical :: rstwr ! .true. ==> write restart file before returning logical :: nlend ! Flag signaling last time-step logical :: rstwr_sync ! .true. ==> write restart file before returning logical :: nlend_sync ! Flag signaling last time-step integer :: lbnum type(ESMF_Array) :: a2x, x2a, dom real(R8), pointer :: fptr(:,:) ! pointer into array data character(len=*), parameter :: subname="atm_run_esmf" !----------------------------------------------------------------------- rc = ESMF_SUCCESS #if (defined _MEMTRACE) if(masterproc) then lbnum=1 call memmon_dump_fort('memmon.out',SubName //':start::',lbnum) endif #endif ! Redirect share output to cam log call shr_file_getLogUnit (shrlogunit) call shr_file_getLogLevel(shrloglev) call shr_file_setLogUnit (iulog) ! Note that sync clock time should match cam time at end of time step/loop not beginning call seq_timemgr_EClockGetData(EClock,curr_ymd=ymd_sync,curr_tod=tod_sync, & curr_yr=yr_sync,curr_mon=mon_sync,curr_day=day_sync) nlend_sync = seq_timemgr_StopAlarmIsOn(EClock) rstwr_sync = seq_timemgr_RestartAlarmIsOn(EClock) ! Map input from Array to cam data structure call ESMF_StateGet(export_state, itemName="domain", array=dom, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_StateGet(export_state, itemName="d2x", array=a2x, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_StateGet(import_state, itemName="x2d", array=x2a, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) !load orbital parameters call ESMF_AttributeGet(export_state, name="orb_eccen", value=eccen, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="orb_mvelpp", value=mvelpp, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="orb_lambm0", value=lambm0, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call ESMF_AttributeGet(export_state, name="orb_obliqr", value=obliqr, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call cam_ctrl_set_orbit(eccen, obliqr, lambm0, mvelpp) call t_startf ('CAM_import') call ESMF_ArrayGet(x2a, localDe=0, farrayPtr=fptr, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call atm_import(fptr, cam_in) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call t_stopf ('CAM_import') ! Cycle over all time steps in the atm coupling interval dosend = .false. do while (.not. dosend) ! Determine if dosend ! When time is not updated at the beginning of the loop - then return only if ! are in sync with clock before time is updated call get_curr_date( yr, mon, day, tod ) ymd = yr*10000 + mon*100 + day tod = tod dosend = (seq_timemgr_EClockDateInSync( EClock, ymd, tod)) ! Determine if time to write cam restart and stop rstwr = .false. if (rstwr_sync .and. dosend) rstwr = .true. nlend = .false. if (nlend_sync .and. dosend) nlend = .true. ! Run CAM (run2, run3, run4) call t_startf ('CAM_run2') call cam_run2( cam_out, cam_in ) call t_stopf ('CAM_run2') call t_startf ('CAM_run3') call cam_run3( cam_out ) call t_stopf ('CAM_run3') call t_startf ('CAM_run4') call cam_run4( cam_out, cam_in, rstwr, nlend, & yr_spec=yr_sync, mon_spec=mon_sync, day_spec=day_sync, sec_spec=tod_sync) call t_stopf ('CAM_run4') ! Advance cam time step call t_startf ('CAM_adv_timestep') call advance_timestep() call t_stopf ('CAM_adv_timestep') ! Run cam radiation/clouds (run1) call t_startf ('CAM_run1') call cam_run1 ( cam_in, cam_out ) call t_stopf ('CAM_run1') ! Map output from cam to Array data structures call t_startf ('CAM_export') call ESMF_ArrayGet(a2x, localDe=0, farrayPtr=fptr, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call atm_export( cam_out, fptr) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call t_stopf ('CAM_export') end do ! Get time of next radiation calculation - albedos will need to be ! calculated by each surface model at this time call seq_timemgr_EClockGetData(Eclock,dtime=atm_cpl_dt) dtime = get_step_size() if (dtime < atm_cpl_dt) then nextsw_cday = radiation_nextsw_cday() else if (dtime == atm_cpl_dt) then caldayp1 = get_curr_calday(offset=int(dtime)) nextsw_cday = radiation_nextsw_cday() if (caldayp1 /= nextsw_cday) nextsw_cday = -1._r8 else call shr_sys_abort('dtime must be less than or equal to atm_cpl_dt') end if call ESMF_AttributeSet(export_state, name="nextsw_cday", value=nextsw_cday, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) ! Write merged surface data restart file if appropriate if (rstwr_sync) then call atm_write_srfrest_esmf( x2a, a2x, & yr_spec=yr_sync, mon_spec=mon_sync, day_spec=day_sync, sec_spec=tod_sync) end if ! Check for consistency of internal cam clock with master sync clock dtime = get_step_size() call get_curr_date( yr, mon, day, tod, offset=-dtime ) ymd = yr*10000 + mon*100 + day tod = tod if ( .not. seq_timemgr_EClockDateInSync( EClock, ymd, tod ) )then call seq_timemgr_EClockGetData(EClock, curr_ymd=ymd_sync, curr_tod=tod_sync ) write(iulog,*)' cam ymd=',ymd ,' cam tod= ',tod write(iulog,*)'sync ymd=',ymd_sync,' sync tod= ',tod_sync call shr_sys_abort( subname//': CAM clock is not in sync with master Sync Clock' ) end if ! End redirection of share output to cam log call shr_file_setLogUnit (shrlogunit) call shr_file_setLogLevel(shrloglev) #if (defined _MEMTRACE) if(masterproc) then lbnum=1 call memmon_dump_fort('memmon.out',SubName //':end::',lbnum) call memmon_reset_addr() endif #endif end subroutine atm_run_esmf !================================================================================ subroutine atm_final_esmf(comp, import_state, export_state, EClock, rc) !----- arguments ----- implicit none type(ESMF_GridComp) :: comp type(ESMF_State) :: import_state type(ESMF_State) :: export_state type(ESMF_Clock) :: EClock integer, intent(out) :: rc ! local type(ESMF_Array) :: a2x_a, x2a_a type(ESMF_DistGrid) :: distgrid_ref !---------------------------------------------------------------------------- ! Finalize routine !---------------------------------------------------------------------------- rc = ESMF_SUCCESS call cam_final( cam_out, cam_in ) ! Destroy ESMF objects call esmfshr_util_StateArrayDestroy(export_state,"d2x",rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call esmfshr_util_StateArrayDestroy(export_state,"domain",rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) call esmfshr_util_StateArrayDestroy(import_state,"x2d",rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) end subroutine atm_final_esmf !================================================================================ type(ESMF_DistGrid) function atm_distgrid_esmf() !------------------------------------------------------------------- ! ! Local variables ! integer, allocatable :: gindex(:) integer :: i, n, c, ncols, sizebuf, rc !------------------------------------------------------------------- ! Determine global index space rc = ESMF_SUCCESS sizebuf=0 do c = begchunk, endchunk ncols = get_ncols_p(c) do i = 1,ncols sizebuf = sizebuf+1 end do end do allocate(gindex(sizebuf)) n=0 do c = begchunk, endchunk ncols = get_ncols_p(c) do i = 1,ncols n = n+1 gindex(n) = get_gcol_p(c,i) end do end do atm_distgrid_esmf = ESMF_DistGridCreate(arbSeqIndexList=gindex, rc=rc) if (rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) deallocate(gindex) end function atm_DistGrid_esmf !=============================================================================== subroutine atm_domain_esmf( dom, rc) !------------------------------------------------------------------- ! ! Arguments ! type(ESMF_Array), intent(inout) :: dom integer, intent(out) :: rc ! ! Local Variables ! integer :: n,i,c,ncols ! indices real(r8) :: lats(pcols) ! array of chunk latitudes real(r8) :: lons(pcols) ! array of chunk longitude real(r8) :: area(pcols) ! area in radians squared for each grid point real(r8), parameter:: radtodeg = 180.0_r8/SHR_CONST_PI real(R8), pointer :: fptr (:,:) integer :: klon,klat,karea,kmask,kfrac ! domain fields !------------------------------------------------------------------- rc = ESMF_SUCCESS !------------------------------------------------------------------- call ESMF_ArrayGet(dom, localDe=0, farrayPtr=fptr, rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) ! Fill in correct values for domain components klon = esmfshr_util_ArrayGetIndex(dom,'lon ',rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) klat = esmfshr_util_ArrayGetIndex(dom,'lat ',rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) karea = esmfshr_util_ArrayGetIndex(dom,'area',rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) kmask = esmfshr_util_ArrayGetIndex(dom,'mask',rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) kfrac = esmfshr_util_ArrayGetIndex(dom,'frac',rc=rc) if(rc /= ESMF_SUCCESS) call ESMF_Finalize(rc=rc, endflag=ESMF_END_ABORT) fptr(:,:) = -9999.0_R8 n=0 do c = begchunk, endchunk ncols = get_ncols_p(c) call get_rlat_all_p(c, ncols, lats) call get_rlon_all_p(c, ncols, lons) call get_area_all_p(c, ncols, area) do i=1,ncols n = n+1 fptr(klat,n) = lats(i)*radtodeg fptr(klon,n) = lons(i)*radtodeg fptr(karea,n) = area(i) fptr(kmask,n) = 1.0_r8 fptr(kfrac,n) = 1.0_r8 end do end do end subroutine atm_domain_esmf !=============================================================================== subroutine atm_read_srfrest_esmf( EClock, x2a, a2x) !----------------------------------------------------------------------- use cam_pio_utils ! ! Arguments ! type(ESMF_Clock),intent(in) :: EClock type(ESMF_Array),intent(inout) :: x2a type(ESMF_Array),intent(inout) :: a2x ! ! Local variables ! integer :: rcode,rc ! return error code integer :: yr_spec ! Current year integer :: mon_spec ! Current month integer :: day_spec ! Current day integer :: sec_spec ! Current time of day (sec) real(r8),pointer :: fptr (:,:) integer :: nf_x2a, nf_a2x, k real(r8), allocatable :: tmp(:) type(file_desc_t) :: file type(io_desc_t) :: iodesc type(var_desc_t) :: varid character(CL) :: itemc ! string converted to char !----------------------------------------------------------------------- ! Determine and open surface restart dataset call seq_timemgr_EClockGetData( EClock, curr_yr=yr_spec,curr_mon=mon_spec, & curr_day=day_spec, curr_tod=sec_spec ) fname_srf_cam = interpret_filename_spec( rsfilename_spec_cam, case=cam_initfiles_get_caseid(), & yr_spec=yr_spec, mon_spec=mon_spec, day_spec=day_spec, sec_spec= sec_spec ) pname_srf_cam = trim(cam_initfiles_get_restdir() )//fname_srf_cam call getfil(pname_srf_cam, fname_srf_cam) call cam_pio_openfile(File, fname_srf_cam, 0) call pio_initdecomp(pio_subsystem, pio_double, (/ngcols/), dof, iodesc) allocate(tmp(size(dof))) call esmfshr_util_ArrayGetSize(x2a,lsize1=nf_x2a) call esmfshr_util_ArrayGetSize(a2x,lsize1=nf_a2x) call ESMF_ArrayGet(x2a, localDe=0, farrayPtr=fptr, rc=rc) do k=1,nf_x2a call esmfshr_util_ArrayGetName(x2a,k,itemc) call pio_seterrorhandling(File, pio_bcast_error) rcode = pio_inq_varid(File,'x2a_'//trim(itemc) ,varid) if (rcode == pio_noerr) then call pio_read_darray(File, varid, iodesc, tmp, rcode) fptr(k,:) = tmp(:) else if (masterproc) then write(iulog,*)'srfrest warning: field ',trim(itemc),' is not on restart file' write(iulog,*)'for backwards compatibility will set it to 0' end if fptr(k,:) = 0._r8 end if call pio_seterrorhandling(File, pio_internal_error) end do call ESMF_ArrayGet(a2x, localDe=0, farrayPtr=fptr, rc=rc) do k=1,nf_a2x call esmfshr_util_ArrayGetName(a2x,k,itemc) rcode = pio_inq_varid(File,'a2x_'//trim(itemc) ,varid) call pio_read_darray(File, varid, iodesc, tmp, rcode) fptr(k,:) = tmp(:) end do call pio_freedecomp(File,iodesc) call pio_closefile(File) deallocate(tmp) end subroutine atm_read_srfrest_esmf !=========================================================================================== subroutine atm_write_srfrest_esmf(x2a, a2x, & yr_spec, mon_spec, day_spec, sec_spec) !----------------------------------------------------------------------- use cam_pio_utils, only: cam_pio_createfile, cam_pio_closefile, pio_subsystem use cam_history_support, only: fillvalue ! ! Arguments ! type(ESMF_Array),intent(inout) :: x2a type(ESMF_Array),intent(inout) :: a2x integer , intent(in) :: yr_spec ! Simulation year integer , intent(in) :: mon_spec ! Simulation month integer , intent(in) :: day_spec ! Simulation day integer , intent(in) :: sec_spec ! Seconds into current simulation day ! ! Local variables ! integer :: rcode,rc ! return error code integer :: nf_x2a, nf_a2x, dimid(1), k real(R8), pointer :: fptr(:,:) type(file_desc_t) :: file type(var_desc_t), pointer :: varid_x2a(:), varid_a2x(:) type(io_desc_t) :: iodesc character(CL) :: itemc ! string converted to char !----------------------------------------------------------------------- ! Determine and open surface restart dataset fname_srf_cam = interpret_filename_spec( rsfilename_spec_cam, & yr_spec=yr_spec, mon_spec=mon_spec, day_spec=day_spec, sec_spec= sec_spec ) call cam_pio_createfile(File, fname_srf_cam, 0) call pio_initdecomp(pio_subsystem, pio_double, (/ngcols/), dof, iodesc) call esmfshr_util_ArrayGetSize(x2a,lsize1=nf_x2a) call esmfshr_util_ArrayGetSize(a2x,lsize1=nf_a2x) allocate(varid_x2a(nf_x2a)) allocate(varid_a2x(nf_a2x)) rcode = pio_def_dim(File,'x2a_nx',ngcols,dimid(1)) do k = 1,nf_x2a call esmfshr_util_ArrayGetName(x2a,k,itemc) rcode = pio_def_var(File,'x2a_'//trim(itemc),PIO_DOUBLE,dimid,varid_x2a(k)) rcode = pio_put_att(File,varid_x2a(k),"_fillvalue",fillvalue) enddo rcode = pio_def_dim(File,'a2x_nx',ngcols,dimid(1)) do k = 1,nf_a2x call esmfshr_util_ArrayGetName(a2x,k,itemc) rcode = PIO_def_var(File,'a2x_'//trim(itemc),PIO_DOUBLE,dimid,varid_a2x(k)) rcode = PIO_put_att(File,varid_a2x(k),"_fillvalue",fillvalue) enddo rcode = pio_enddef(File) ! don't check return code, might be enddef already call ESMF_ArrayGet(x2a, localDe=0, farrayPtr=fptr, rc=rc) do k=1,nf_x2a call pio_write_darray(File, varid_x2a(k), iodesc, fptr(k,:), rcode) end do call ESMF_ArrayGet(a2x, localDe=0, farrayPtr=fptr, rc=rc) do k=1,nf_a2x call pio_write_darray(File, varid_a2x(k), iodesc, fptr(k,:), rcode) end do deallocate(varid_x2a, varid_a2x) call pio_freedecomp(File,iodesc) call pio_closefile(file) end subroutine atm_write_srfrest_esmf #endif end module atm_comp_esmf