72    class(*), 
target, 
intent(in) :: data
 
   73    real(kind=
rp), 
intent(in), 
optional :: t
 
   75    character(len=5) :: id_str
 
   76    character(len=1024) :: fname
 
   77    integer :: ierr, suffix_pos, optional_fields
 
   78    type(
field_t), 
pointer :: u, v, w, p, s
 
   79    type(
field_t), 
pointer :: abx1,abx2
 
   80    type(
field_t), 
pointer :: aby1,aby2
 
   81    type(
field_t), 
pointer :: abz1,abz2
 
   82    type(
field_t), 
pointer :: abs1,abs2
 
   87    real(kind=
rp), 
pointer :: dtlag(:), tlag(:)
 
   88    type(
mesh_t), 
pointer :: msh
 
   89    type(mpi_status) :: status
 
   91    integer (kind=MPI_OFFSET_KIND) :: mpi_offset, byte_offset
 
   92    integer(kind=i8) :: n_glb_dofs, dof_offset
 
   93    logical :: write_lag, write_scalar, write_dtlag, write_scalarlag, write_abvel
 
  105       if ( .not. 
associated(data%u) .or. &
 
  106            .not. 
associated(data%v) .or. &
 
  107            .not. 
associated(data%w) .or. &
 
  108            .not. 
associated(data%p) ) 
then 
  120       if (
associated(data%ulag)) 
then 
  125          optional_fields = optional_fields + 1
 
  130       if (
associated(data%s)) 
then 
  132          write_scalar = .true.
 
  133          optional_fields = optional_fields + 2
 
  135          write_scalar = .false.
 
  138       if (
associated(data%tlag)) 
then 
  142          optional_fields = optional_fields + 4
 
  144          write_dtlag = .false.
 
  146       write_abvel = .false.
 
  147       if (
associated(data%abx1)) 
then 
  154          optional_fields = optional_fields + 8
 
  157       write_scalarlag = .false.
 
  158       if (
associated(data%abs1)) 
then 
  162          optional_fields = optional_fields + 16
 
  163          write_scalarlag = .true.
 
  171    write(id_str, 
'(i5.5)') this%counter
 
  172    fname = trim(this%fname(1:suffix_pos-1))//id_str//
'.chkp' 
  175    dof_offset = int(msh%offset_el, 
i8) * int(u%Xh%lx * u%Xh%ly * u%Xh%lz, 
i8)
 
  176    n_glb_dofs = int(u%Xh%lx * u%Xh%ly * u%Xh%lz, 
i8) * int(msh%glb_nelv, 
i8)
 
  178    call mpi_file_open(
neko_comm, trim(fname), &
 
  179         mpi_mode_wronly + mpi_mode_create, mpi_info_null, fh, ierr)
 
  180    call mpi_file_write_all(fh, msh%glb_nelv, 1, mpi_integer, status, ierr)
 
  181    call mpi_file_write_all(fh, msh%gdim, 1, mpi_integer, status, ierr)
 
  182    call mpi_file_write_all(fh, u%Xh%lx, 1, mpi_integer, status, ierr)
 
  183    call mpi_file_write_all(fh, optional_fields, 1, mpi_integer, status, ierr)
 
  184    call mpi_file_write_all(fh, time, 1, mpi_double_precision, status, ierr)
 
  193    byte_offset = byte_offset + &
 
  195    call mpi_file_write_at_all(fh, byte_offset,u%x, u%dof%size(), &
 
  198    mpi_offset = mpi_offset +&
 
  201    byte_offset = mpi_offset + &
 
  203    call mpi_file_write_at_all(fh, byte_offset, v%x, v%dof%size(), &
 
  207    byte_offset = mpi_offset + &
 
  209    call mpi_file_write_at_all(fh, byte_offset, w%x, w%dof%size(), &
 
  213    byte_offset = mpi_offset + &
 
  215    call mpi_file_write_at_all(fh, byte_offset, p%x, p%dof%size(), &
 
  225       do i = 1, ulag%size()
 
  226          byte_offset = mpi_offset + &
 
  231          associate(x => ulag%lf(i)%x)
 
  232            call mpi_file_write_at_all(fh, byte_offset, x, &
 
  238       do i = 1, vlag%size()
 
  239          byte_offset = mpi_offset + &
 
  244          associate(x => vlag%lf(i)%x)
 
  245            call mpi_file_write_at_all(fh, byte_offset, x, &
 
  248          mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  251       do i = 1, wlag%size()
 
  252          byte_offset = mpi_offset + &
 
  253               dof_offset * int(mpi_real_prec_size, i8)
 
  257          associate(x => wlag%lf(i)%x)
 
  258            call mpi_file_write_at_all(fh, byte_offset, x, &
 
  259                 wlag%lf(i)%dof%size(), mpi_real_precision, status, ierr)
 
  261          mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  266    if (write_scalar) 
then 
  267       byte_offset = mpi_offset + &
 
  268            dof_offset * int(mpi_real_prec_size, i8)
 
  269       call mpi_file_write_at_all(fh, byte_offset, s%x, p%dof%size(), &
 
  270            mpi_real_precision, status, ierr)
 
  271       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  274    if (write_dtlag) 
then 
  275       call mpi_file_write_at_all(fh, mpi_offset, tlag, 10, mpi_real_precision, status, ierr)
 
  276       mpi_offset = mpi_offset + 10_i8 * int(mpi_real_prec_size, i8)
 
  277       call mpi_file_write_at_all(fh, mpi_offset, dtlag, 10, mpi_real_precision, status, ierr)
 
  278       mpi_offset = mpi_offset + 10_i8 * int(mpi_real_prec_size, i8)
 
  281    if (write_abvel) 
then 
  282       byte_offset = mpi_offset + &
 
  283            dof_offset * int(mpi_real_prec_size, i8)
 
  284       call mpi_file_write_at_all(fh, byte_offset, abx1%x, abx1%dof%size(), &
 
  285            mpi_real_precision, status, ierr)
 
  286       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  287       byte_offset = mpi_offset + &
 
  288            dof_offset * int(mpi_real_prec_size, i8)
 
  289       call mpi_file_write_at_all(fh, byte_offset, abx2%x, abx1%dof%size(), &
 
  290            mpi_real_precision, status, ierr)
 
  291       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  292       byte_offset = mpi_offset + &
 
  293            dof_offset * int(mpi_real_prec_size, i8)
 
  294       call mpi_file_write_at_all(fh, byte_offset, aby1%x, abx1%dof%size(), &
 
  295            mpi_real_precision, status, ierr)
 
  296       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  297       byte_offset = mpi_offset + &
 
  298            dof_offset * int(mpi_real_prec_size, i8)
 
  299       call mpi_file_write_at_all(fh, byte_offset, aby2%x, abx1%dof%size(), &
 
  300            mpi_real_precision, status, ierr)
 
  301       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  302       byte_offset = mpi_offset + &
 
  303            dof_offset * int(mpi_real_prec_size, i8)
 
  304       call mpi_file_write_at_all(fh, byte_offset, abz1%x, abx1%dof%size(), &
 
  305            mpi_real_precision, status, ierr)
 
  306       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  307       byte_offset = mpi_offset + &
 
  308            dof_offset * int(mpi_real_prec_size, i8)
 
  309       call mpi_file_write_at_all(fh, byte_offset, abz2%x, abx1%dof%size(), &
 
  310            mpi_real_precision, status, ierr)
 
  311       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  314    if (write_scalarlag) 
then 
  315       do i = 1, slag%size()
 
  316          byte_offset = mpi_offset + &
 
  317               dof_offset * int(mpi_real_prec_size, i8)
 
  321          associate(x => slag%lf(i)%x)
 
  322            call mpi_file_write_at_all(fh, byte_offset, x, &
 
  323                 slag%lf(i)%dof%size(), mpi_real_precision, status, ierr)
 
  325          mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  328       byte_offset = mpi_offset + &
 
  329            dof_offset * int(mpi_real_prec_size, i8)
 
  330       call mpi_file_write_at_all(fh, byte_offset, abs1%x, abx1%dof%size(), &
 
  331            mpi_real_precision, status, ierr)
 
  332       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  333       byte_offset = mpi_offset + &
 
  334            dof_offset * int(mpi_real_prec_size, i8)
 
  335       call mpi_file_write_at_all(fh, byte_offset, abs2%x, abx1%dof%size(), &
 
  336            mpi_real_precision, status, ierr)
 
  337       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  340    call mpi_file_close(fh, ierr)
 
  342    this%counter = this%counter + 1
 
 
  349    class(*), 
target, 
intent(inout) :: data
 
  350    type(chkp_t), 
pointer :: chkp
 
  351    character(len=5) :: id_str
 
  352    character(len=1024) :: fname
 
  353    integer :: ierr, suffix_pos
 
  354    type(field_t), 
pointer :: u, v, w, p, s
 
  355    type(field_series_t), 
pointer :: ulag => null()
 
  356    type(field_series_t), 
pointer :: vlag => null()
 
  357    type(field_series_t), 
pointer :: wlag => null()
 
  358    type(field_series_t), 
pointer :: slag => null()
 
  359    type(mesh_t), 
pointer :: msh
 
  360    type(mpi_status) :: status
 
  362    type(field_t), 
pointer :: abx1,abx2
 
  363    type(field_t), 
pointer :: aby1,aby2
 
  364    type(field_t), 
pointer :: abz1,abz2
 
  365    type(field_t), 
pointer :: abs1,abs2
 
  366    real(kind=rp), 
allocatable :: x_coord(:,:,:,:)
 
  367    real(kind=rp), 
allocatable :: y_coord(:,:,:,:)
 
  368    real(kind=rp), 
allocatable :: z_coord(:,:,:,:)
 
  369    real(kind=rp), 
pointer :: dtlag(:), tlag(:)
 
  370    integer (kind=MPI_OFFSET_KIND) :: mpi_offset, byte_offset
 
  371    integer(kind=i8) :: n_glb_dofs, dof_offset
 
  372    integer :: glb_nelv, gdim, lx, have_lag, have_scalar, nel, optional_fields, have_dtlag
 
  373    integer :: have_abvel, have_scalarlag
 
  374    logical :: read_lag, read_scalar, read_dtlag, read_abvel, read_scalarlag
 
  376    real(kind=rp) :: center_x, center_y, center_z
 
  378    type(dofmap_t) :: dof
 
  380    call this%check_exists()
 
  385       if ( .not. 
associated(data%u) .or. &
 
  386            .not. 
associated(data%v) .or. &
 
  387            .not. 
associated(data%w) .or. &
 
  388            .not. 
associated(data%p) ) 
then 
  389          call neko_error(
'Checkpoint not initialized')
 
  396       this%chkp_Xh => data%previous_Xh
 
  398       if (
allocated(data%previous_mesh%elements)) 
then 
  399          msh => data%previous_mesh
 
  400          this%mesh2mesh = .true.
 
  401          tol = data%mesh2mesh_tol
 
  404          this%mesh2mesh = .false.
 
  407       if (
associated(data%ulag)) 
then 
  416       if (
associated(data%s)) 
then 
  420          read_scalar = .false.
 
  422       if (
associated(data%dtlag)) 
then 
  430       if (
associated(data%abx1)) 
then 
  439       read_scalarlag = .false.
 
  440       if (
associated(data%abs1)) 
then 
  444          read_scalarlag = .true.
 
  450       call neko_error(
'Invalid data')
 
  455    call mpi_file_open(neko_comm, trim(this%fname), &
 
  456         mpi_mode_rdonly, mpi_info_null, fh, ierr)
 
  457    call mpi_file_read_all(fh, glb_nelv, 1, mpi_integer, status, ierr)
 
  458    call mpi_file_read_all(fh, gdim, 1, mpi_integer, status, ierr)
 
  459    call mpi_file_read_all(fh, lx, 1, mpi_integer, status, ierr)
 
  460    call mpi_file_read_all(fh, optional_fields, 1, mpi_integer, status, ierr)
 
  461    call mpi_file_read_all(fh, chkp%t, 1, mpi_double_precision, status, ierr)
 
  463    have_lag = mod(optional_fields,2)/1
 
  464    have_scalar = mod(optional_fields,4)/2
 
  465    have_dtlag = mod(optional_fields,8)/4
 
  466    have_abvel = mod(optional_fields,16)/8
 
  467    have_scalarlag = mod(optional_fields,32)/16
 
  469    if ( ( glb_nelv .ne. msh%glb_nelv ) .or. &
 
  470         ( gdim .ne. msh%gdim) .or. &
 
  471         ( (have_lag .eq. 0) .and. (read_lag) ) .or. &
 
  472        ( (have_scalar .eq. 0) .and. (read_scalar) ) ) 
then 
  473       call neko_error(
'Checkpoint does not match case')
 
  477    if (gdim .eq. 3) 
then 
  478       call this%chkp_Xh%init(gll, lx, lx, lx)
 
  480       call this%chkp_Xh%init(gll, lx, lx)
 
  482    if (this%mesh2mesh) 
then 
  483       call dof%init(msh, this%chkp_Xh)
 
  484       allocate(x_coord(u%Xh%lx,u%Xh%ly,u%Xh%lz,u%msh%nelv))
 
  485       allocate(y_coord(u%Xh%lx,u%Xh%ly,u%Xh%lz,u%msh%nelv))
 
  486       allocate(z_coord(u%Xh%lx,u%Xh%ly,u%Xh%lz,u%msh%nelv))
 
  491       do e = 1, u%dof%msh%nelv
 
  495          do i = 1,u%dof%Xh%lxyz
 
  496             center_x = center_x + u%dof%x(i,1,1,e)
 
  497             center_y = center_y + u%dof%y(i,1,1,e)
 
  498             center_z = center_z + u%dof%z(i,1,1,e)
 
  500          center_x = center_x/u%Xh%lxyz
 
  501          center_y = center_y/u%Xh%lxyz
 
  502          center_z = center_z/u%Xh%lxyz
 
  503          do i = 1,u%dof%Xh%lxyz
 
  504             x_coord(i,1,1,e) = u%dof%x(i,1,1,e) - tol*(u%dof%x(i,1,1,e)-center_x)
 
  505             y_coord(i,1,1,e) = u%dof%y(i,1,1,e) - tol*(u%dof%y(i,1,1,e)-center_y)
 
  506             z_coord(i,1,1,e) = u%dof%z(i,1,1,e) - tol*(u%dof%z(i,1,1,e)-center_z)
 
  509       call this%global_interp%init(dof,tol=tol)
 
  510       call this%global_interp%find_points(x_coord,y_coord,z_coord,u%dof%size())
 
  515       call this%space_interp%init(this%sim_Xh, this%chkp_Xh)
 
  517    dof_offset = int(msh%offset_el, i8) * int(this%chkp_Xh%lxyz, i8)
 
  518    n_glb_dofs = int(this%chkp_Xh%lxyz, i8) * int(msh%glb_nelv, i8)
 
  524    byte_offset = 4_i8 * int(mpi_integer_size,i8) + int(mpi_double_precision_size,i8)
 
  525    byte_offset = byte_offset + &
 
  526         dof_offset * int(mpi_real_prec_size, i8)
 
  527    call this%read_field(fh, byte_offset, u%x, nel)
 
  528    mpi_offset = 4_i8 * int(mpi_integer_size,i8) + int(mpi_double_precision_size,i8)
 
  529    mpi_offset = mpi_offset +&
 
  530         n_glb_dofs * int(mpi_real_prec_size, i8)
 
  532    byte_offset = mpi_offset + &
 
  533         dof_offset * int(mpi_real_prec_size, i8)
 
  534    call this%read_field(fh, byte_offset, v%x, nel)
 
  535    mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  537    byte_offset = mpi_offset + &
 
  538         dof_offset * int(mpi_real_prec_size, i8)
 
  539    call this%read_field(fh, byte_offset, w%x, nel)
 
  540    mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  542    byte_offset = mpi_offset + &
 
  543         dof_offset * int(mpi_real_prec_size, i8)
 
  544    call this%read_field(fh, byte_offset, p%x, nel)
 
  545    mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  552       do i = 1, ulag%size()
 
  553          byte_offset = mpi_offset + &
 
  554               dof_offset * int(mpi_real_prec_size, i8)
 
  555          call this%read_field(fh, byte_offset, ulag%lf(i)%x, nel)
 
  556          mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  559       do i = 1, vlag%size()
 
  560          byte_offset = mpi_offset + &
 
  561               dof_offset * int(mpi_real_prec_size, i8)
 
  562          call this%read_field(fh, byte_offset, vlag%lf(i)%x, nel)
 
  563          mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  566       do i = 1, wlag%size()
 
  567          byte_offset = mpi_offset + &
 
  568               dof_offset * int(mpi_real_prec_size, i8)
 
  569          call this%read_field(fh, byte_offset, wlag%lf(i)%x, nel)
 
  570          mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  574    if (read_scalar) 
then 
  575       byte_offset = mpi_offset + &
 
  576            dof_offset * int(mpi_real_prec_size, i8)
 
  577       call this%read_field(fh, byte_offset, s%x, nel)
 
  578       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  581    if (read_dtlag .and. have_dtlag .eq. 1) 
then 
  582       call mpi_file_read_at_all(fh, mpi_offset, tlag, 10, mpi_real_precision, status, ierr)
 
  583       mpi_offset = mpi_offset + 10_i8 * int(mpi_real_prec_size, i8)
 
  584       call mpi_file_read_at_all(fh, mpi_offset, dtlag, 10, mpi_real_precision, status, ierr)
 
  585       mpi_offset = mpi_offset + 10_i8 * int(mpi_real_prec_size, i8)
 
  588    if (read_abvel .and. have_abvel .eq. 1) 
then 
  589       byte_offset = mpi_offset + &
 
  590            dof_offset * int(mpi_real_prec_size, i8)
 
  591       call this%read_field(fh, byte_offset, abx1%x, nel)
 
  592       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  593       byte_offset = mpi_offset + &
 
  594            dof_offset * int(mpi_real_prec_size, i8)
 
  595       call this%read_field(fh, byte_offset, abx2%x, nel)
 
  596       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  597       byte_offset = mpi_offset + &
 
  598            dof_offset * int(mpi_real_prec_size, i8)
 
  599       call this%read_field(fh, byte_offset, aby1%x, nel)
 
  600       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  601       byte_offset = mpi_offset + &
 
  602            dof_offset * int(mpi_real_prec_size, i8)
 
  603       call this%read_field(fh, byte_offset, aby2%x, nel)
 
  604       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  605       byte_offset = mpi_offset + &
 
  606            dof_offset * int(mpi_real_prec_size, i8)
 
  607       call this%read_field(fh, byte_offset, abz1%x, nel)
 
  608       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  609       byte_offset = mpi_offset + &
 
  610            dof_offset * int(mpi_real_prec_size, i8)
 
  611       call this%read_field(fh, byte_offset, abz2%x, nel)
 
  612       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  614    if (read_scalarlag .and. have_scalarlag .eq. 1) 
then 
  615       do i = 1, slag%size()
 
  616          byte_offset = mpi_offset + &
 
  617               dof_offset * int(mpi_real_prec_size, i8)
 
  618          call this%read_field(fh, byte_offset, slag%lf(i)%x, nel)
 
  619          mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  621       byte_offset = mpi_offset + &
 
  622            dof_offset * int(mpi_real_prec_size, i8)
 
  623       call this%read_field(fh, byte_offset, abs1%x, nel)
 
  624       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  625       byte_offset = mpi_offset + &
 
  626            dof_offset * int(mpi_real_prec_size, i8)
 
  627       call this%read_field(fh, byte_offset, abs2%x, nel)
 
  628       mpi_offset = mpi_offset + n_glb_dofs * int(mpi_real_prec_size, i8)
 
  631    call mpi_file_close(fh, ierr)
 
  633    call this%global_interp%free()
 
  634    call this%space_interp%free()