TABLE OF CONTENTS


ABINIT/abinit [ Programs ]

[ Top ] [ Programs ]

NAME

 abinit

FUNCTION

 Main routine for conducting Density-Functional Theory calculations or Many-Body Perturbation Theory calculations.

COPYRIGHT

 Copyright (C) 1998-2024 ABINIT group (DCA, XG, GMR, MKV, MT)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .
 For the initials of contributors, see ~abinit/doc/developers/contributors.txt .

NOTES

 The new user is strongly adviced to read the
 latest version of the file ~abinit/doc/users/new_user_guide.html
 before trying to modify or even use the code.
 Even experienced users of the code should also be careful in coding,
 please read the latest version of the file ~abinit/doc/developers/rules_coding

 The present main routine drives the following operations :

 1) Eventually initialize MPI
 2) Initialize overall timing of run
 3) Print greeting for interactive user and
    Read names of files (input, output, rootinput, rootoutput, roottemporaries),
    create the name of the status file, initialize the status subroutine.
 4) Open output file and print herald at top of output and log files
 5) Read the input file, and store the information in a long string of characters
 6) Take ndtset from the input string, then allocate
    the arrays whose dimensions depends only on ndtset
 7) Continue to analyze the input string, and allocate the remaining arrays.
    Also modulate the timing according to timopt.
 8) Finish to read the "file" file completely,
    and also initialize pspheads (the pseudopotential header information)
 9) Provide defaults for the variables that have not yet been initialized.
 10) Perform some global initialization, depending on the value of
 pseudopotentials, parallelism variables, or macro input variables
 11) Call the main input routine.
 12) Echo input data to output file and log file
 13) Perform additional checks on input data
  At this stage, all the information from the "files" file and "input" file
  have been read and checked.
 14) Print more information, and activate GPU
 ___________________________________________
 15) Perform main calculation  (call driver)
 -------------------------------------------

 16) Give final echo of coordinates, etc.
 17) Timing analysis
 18) Bibliographical recommendations
 19) Delete the status file, and, for build-in tests, analyse the correctness of results
 20) Write the final timing, close the output file, and write a final line to the log file
 21) Eventual cleaning of MPI run

INPUTS

  (main routine)

OUTPUT

  (main routine)

SOURCE

 65 #if defined HAVE_CONFIG_H
 66 #include "config.h"
 67 #endif
 68 
 69 #include "abi_common.h"
 70 #include "nvtx_macros.h"
 71 
 72 program abinit
 73 
 74  use defs_basis
 75  use m_cppopts_dumper
 76  use m_optim_dumper
 77  use m_abicore
 78  use m_dtset
 79  use m_results_out
 80  use m_xmpi
 81  use m_xomp
 82  use m_xpapi
 83  use m_errors
 84  use m_argparse
 85  use m_nctk
 86 #if defined HAVE_MPI2
 87  use mpi
 88 #endif
 89 
 90  use defs_datatypes,only : pspheader_type
 91  use defs_abitypes, only : MPI_type
 92  use m_build_info,  only : abinit_version, dump_config
 93  use m_parser,      only : ab_dimensions
 94  use m_time ,       only : asctime, sec2str, timein, time_set_papiopt, timab
 95  use m_fstrings,    only : sjoin, strcat, itoa, yesno, ljust
 96  use m_io_tools,    only : flush_unit, delete_file
 97  use m_specialmsg,  only : specialmsg_getcount, herald
 98  use m_exit,        only : get_timelimit_string
 99  use m_atomdata,    only : znucl2symbol
100  use m_libpaw_tools,only : libpaw_spmsg_getcount
101  use m_mpinfo,      only : destroy_mpi_enreg, clnmpi_img, clnmpi_grid, clnmpi_atom, clnmpi_pert
102  use m_memeval,     only : memory_eval
103  use m_chkinp,      only : chkinp
104  use m_dtfil,       only : iofn1
105  use m_outxml,      only : outxml_open, outxml_finalise
106  use m_out_acknowl, only : out_acknowl
107  use m_timana,      only : timana
108  use m_builtin_tests, only : testfi
109  use m_mpi_setup,     only : mpi_setup
110  use m_outvars,       only : outvars
111  use m_out_spg_anal,  only : out_spg_anal
112  use m_driver,        only : driver
113 
114 #ifdef HAVE_GPU
115  use m_gpu_toolbox
116 #endif
117 
118 #ifdef HAVE_GPU_CUDA
119  use m_manage_cuda
120 #endif
121 
122 #if defined(HAVE_GPU) && defined(HAVE_GPU_MARKERS)
123  use m_nvtx_data
124 #endif
125 
126 #if defined HAVE_BIGDFT
127  use BigDFT_API,    only : bigdft_init_errors,bigdft_init_timing_categories,&
128  &                         f_timing_initialize,f_timing_reset,wvl_timing => timing
129 #endif
130 
131  use m_common, only : get_dtsets_pspheads
132 
133  implicit none
134 
135 #if defined HAVE_MPI1
136  include 'mpif.h'
137 #endif
138 
139 !Arguments -----------------------------------
140 !Local variables-------------------------------
141 !
142 !===============================================================================
143 !  abinit_version designate overall code version
144 !  mpw=maximum number of planewaves in basis sphere
145 !  unit numbers (ab_in,ab_out,std_out,tmp_unit) have been defined in defs_basis.f .
146 !  The array filnam is used for the name of input and output files,
147 !  and roots for generic input, output or temporary files.
148 !  Pseudopotential file names are set in iofn2, and are contained in pspheads.
149 !  The name filstat will be needed beyond gstate to check
150 !  the appearance of the "exit" flag, to make a hasty exit, as well as
151 !  in order to output the status of the computation.
152 !==============================================================================
153 ! Declarations
154 ! Define "level of the routine", for debugging purposes
155  integer,parameter :: level=1
156  integer :: choice,dmatpuflag,ierr,ii,iounit,ios
157  integer :: lenstr,me,print_mem_report
158  integer :: mu,natom,ncomment,ncomment_paw,ndtset
159  integer :: ndtset_alloc,nexit,nexit_paw,nfft,nkpt,npsp
160  integer :: nsppol,nwarning,nwarning_paw,prtvol,timopt,gpu_option
161  integer,allocatable :: nband(:),npwtot(:)
162  real(dp) :: etotal, tcpui, twalli
163  real(dp) :: strten(6),tsec(2)
164  real(dp),allocatable :: gred(:,:),xred(:,:)
165  character(len=24) :: codename
166  character(len=24) :: start_datetime
167  character(len=5000) :: msg
168  character(len=strlen) :: string
169  character(len=fnlen) :: filstat
170  character(len=fnlen) :: filnam(5)
171  type(args_t) :: args
172  type(dataset_type),allocatable  :: dtsets(:)
173  type(MPI_type),allocatable :: mpi_enregs(:)
174  type(pspheader_type),allocatable :: pspheads(:)
175  type(results_out_type),allocatable,target :: results_out(:)
176  type(results_out_type),pointer :: results_out_all(:)
177  type(ab_dimensions) :: mx
178  logical :: test_img,test_exit,use_results_all,xml_output=.false.
179  integer :: values(8)
180  character(len=5) :: strzone
181  character(len=8) :: strdat
182  character(len=10) :: strtime
183  character(len=13) :: warn_fmt
184  integer :: gpu_devices(12)
185 
186 !******************************************************************
187 
188 !0) Change communicator for I/O (mandatory!)
189  call abi_io_redirect(new_io_comm=xmpi_world)
190  !call xlf_set_sighandler()
191 
192 !------------------------------------------------------------------------------
193 
194 !1) Eventually initialize MPI. Pay attention: me and comm may be initialzed again in finddistrproc
195  call xmpi_init()
196  me = xmpi_comm_rank(xmpi_world)
197 
198  ! Parse command line arguments.
199  args = args_parser(); if (args%exit /= 0) goto 100
200 
201  ! Initialize memory profiling if activated at configure time.
202  ! if a full report is desired, set the argument of abimem_init to "2" instead of "0" via the command line.
203  ! note that the file can easily be multiple GB in size so don't use this option normally
204 #ifdef HAVE_MEM_PROFILING
205  call abimem_init(args%abimem_level, limit_mb=args%abimem_limit_mb)
206 #endif
207 
208 !------------------------------------------------------------------------------
209 
210  ! 2) Initialize overall timing of run:
211  call xpapi_init()
212  call xpapi_show_info(unit=std_out,mode_paral="COLL")
213 
214  start_datetime = asctime()
215  call timein(tcpui,twalli)
216  call timab(1,0,tsec)
217 
218  ! Start to accumulate time for the entire run. The end of accumulation is in timana.f
219  call timab(1,1,tsec)
220 
221 !------------------------------------------------------------------------------
222 
223 !3) Print greeting for interactive user,
224 !read names of files (input, output, rootinput, rootoutput, roottemporaries),
225 !create the name of the status file, initialize the status subroutine.
226 
227  call timab(101,3,tsec)
228  call iofn1(args%input_path, filnam, filstat, xmpi_world)
229 
230 !------------------------------------------------------------------------------
231 
232 !4) Open output file and print herald at top of output and log files
233 
234  if (me==0) then
235 #ifdef FC_NAG
236    open(unit=ab_out,file=filnam(2),form='formatted',status='new', action="write", recl=ABI_RECL, iomsg=msg, iostat=ios)
237 #else
238    open(unit=ab_out,file=filnam(2),form='formatted',status='new', action="write", iomsg=msg, iostat=ios)
239 #endif
240    ABI_CHECK(ios == 0, msg)
241 !  rewind (unit=ab_out)
242    codename='ABINIT'//repeat(' ',18)
243    call herald(codename,abinit_version,ab_out)
244    call herald(codename,abinit_version,std_out)
245    call dump_config(std_out)
246    call dump_optim(std_out)
247    call dump_cpp_options(std_out)
248    ! Write names of files
249    write(msg, '(a,a,a,a,a,a,a,a,a,a,a,a)' )&
250     '- input  file    -> ',trim(filnam(1)),ch10,&
251     '- output file    -> ',trim(filnam(2)),ch10,&
252     '- root for input  files -> ',trim(filnam(3)),ch10,&
253     '- root for output files -> ',trim(filnam(4)),ch10
254    call wrtout([std_out, ab_out], msg)
255  end if
256 
257  ! Test if the netcdf library supports MPI-IO
258  call nctk_test_mpiio()
259 
260  call timab(101,2,tsec)
261 
262  call get_dtsets_pspheads(args%input_path, filnam(1), ndtset, lenstr, string, &
263                           timopt, dtsets, pspheads, mx, dmatpuflag, xmpi_world)
264 
265  call timab(103,1,tsec)
266 
267  ndtset_alloc = size(dtsets) - 1
268  npsp = size(pspheads)
269 
270 #if defined HAVE_BIGDFT
271  call f_lib_initialize()
272  call bigdft_init_errors()
273  call bigdft_init_timing_categories()
274  if (timopt==10) then
275    call delete_file('wvl_timings.yaml',ierr)
276    call f_timing_reset(filename='wvl_time.yaml',master=me==0,verbose_mode=.false.)
277  end if
278 #endif
279 
280  ABI_MALLOC(mpi_enregs, (0:max(1,ndtset)))
281  call mpi_setup(dtsets,filnam,lenstr,mpi_enregs,ndtset,ndtset_alloc,string)
282 
283  call memory_eval(dtsets,ab_out,mpi_enregs,ndtset,ndtset_alloc,npsp,pspheads)
284 
285 !------------------------------------------------------------------------------
286 
287 !12) Echo input data to output file and log file
288 
289  ! For evolving variables, and results
290  ABI_MALLOC(results_out, (0:ndtset_alloc))
291 
292  ! Initialize results_out datastructure
293  call init_results_out(dtsets,1,1,mpi_enregs, mx%natom, mx%mband_upper, mx%nkpt,npsp,&
294   mx%nsppol, mx%ntypat, results_out)
295 
296  ! Gather contributions to results_out from images of the cell, if needed
297  test_img = (mx%nimage/=1.and.maxval(dtsets(:)%npimage)>1)
298  use_results_all=.false.
299  if (test_img) then
300    use_results_all=(me==0)
301    if (use_results_all) then
302      ABI_MALLOC(results_out_all, (0:ndtset_alloc))
303    end if
304 
305    call gather_results_out(dtsets,mpi_enregs,results_out,results_out_all,use_results_all, allgather=.false.,master=0)
306 
307  else
308    results_out_all => results_out
309  end if
310 
311  if (me == 0) then
312    ! Echo input to output file on unit ab_out, and to log file on unit 06 :
313    choice=1
314    do ii=1,2
315      if(ii==1)iounit=ab_out
316      if(ii==2)iounit=std_out
317 
318      call outvars(choice,dmatpuflag,dtsets, filnam(4), iounit, mx, ndtset,ndtset_alloc,npsp,results_out_all,timopt)
319    end do
320 
321    if (dtsets(1)%prtxml == 1) then
322      call outxml_open(trim(filnam(4)))
323      call date_and_time(strdat,strtime,strzone,values)
324      xml_output = .true.
325    else
326      xml_output = .false.
327    end if
328 
329  end if ! me==0
330 
331  ! Clean memory
332  if (test_img.and.me==0) then
333    call destroy_results_out(results_out_all)
334    ABI_FREE(results_out_all)
335  end if
336 
337 !This synchronization is not strictly needed, but without it,
338 !there are problems with Tv1#93 in parallel, PGI compiler, on Intel/PC
339  call abi_io_redirect(new_io_comm=xmpi_world)
340 
341  call timab(103,2,tsec)
342  call timab(104,3,tsec)
343 
344 !------------------------------------------------------------------------------
345 
346 !13) Perform additional checks on input data
347 
348  call chkinp(dtsets, ab_out, mpi_enregs, ndtset, ndtset_alloc, npsp, pspheads, xmpi_world)
349 
350  ! Check whether the string only contains valid keywords
351  call chkvars(string)
352 
353 !At this stage, all the information from the "files" file and "input" file have been read and checked.
354 
355 !------------------------------------------------------------------------------
356 
357 !14) Print more information, and activate GPU
358 
359  if (me == 0) then
360    call print_kinds(std_out)     ! Printout of kinds and precisions.
361    call xomp_show_info(std_out)  ! Info on the openMP environment.
362    call xmpi_show_info(std_out)  ! Info on the MPI environment.
363  end if
364 
365 !Activate GPU is required
366  gpu_option=ABI_GPU_DISABLED
367  gpu_devices(:)=-1
368  do ii=1,ndtset_alloc
369    if (dtsets(ii)%gpu_option/=ABI_GPU_DISABLED) then
370      gpu_option=dtsets(ii)%gpu_option
371      gpu_devices(:)=dtsets(ii)%gpu_devices(:)
372    end if
373  end do
374 #ifdef HAVE_GPU
375  call setdevice_cuda(gpu_devices,gpu_option)
376 #else
377  if (gpu_option/=ABI_GPU_DISABLED) then
378    write(msg,'(a)')ch10,'Use of GPU is requested but ABINIT was not built with GPU support.'
379    ABI_ERROR(msg)
380  end if
381 #endif
382 
383 !Enable GPU markers (NVTX/ROCTX) if required
384 #if defined(HAVE_GPU) && defined(HAVE_GPU_MARKERS)
385  NVTX_INIT()
386 #endif
387 
388 !------------------------------------------------------------------------------
389 
390 !15) Perform main calculation
391  call timab(104,2,tsec)
392 
393  test_exit=.false.
394  prtvol=dtsets(1)%prtvol
395  if (prtvol == -level .or. prtvol == -2 .or. args%dry_run /= 0) then
396    write(msg,'(a,a,i0,a)')ch10,' abinit : before driver, prtvol=',prtvol,', debugging mode => will skip driver '
397    call wrtout([std_out, ab_out], msg)
398    test_exit=.true.
399  end if
400 
401  if(.not.test_exit)then
402    ABI_NVTX_START_RANGE(NVTX_MAIN_COMPUTATION)
403    call driver(abinit_version,tcpui,dtsets,filnam,filstat, mpi_enregs,ndtset,ndtset_alloc,npsp,pspheads,results_out)
404    ABI_NVTX_END_RANGE()
405  end if
406 
407 !------------------------------------------------------------------------------
408 
409  ! 16) Give final echo of coordinates, etc.
410  call timab(105,1,tsec)
411 
412  write(msg,'(a,a,a,62a,80a)') ch10,'== END DATASET(S) ',('=',mu=1,62),ch10,('=',mu=1,80)
413  call wrtout([std_out, ab_out], msg)
414 
415  ! Gather contributions to results_out from images of the cell, if needed
416  if (test_img) then
417    if (use_results_all)  then
418      ABI_MALLOC(results_out_all,(0:ndtset_alloc))
419    end if
420 
421    call gather_results_out(dtsets,mpi_enregs,results_out,results_out_all,use_results_all,allgather=.false.,master=0)
422  end if
423 
424  if(me==0) then
425    if(test_exit)then
426      write(msg,'(a,a,i0,a)')ch10,' abinit : before driver, prtvol=',prtvol,', debugging mode => will skip outvars '
427      call wrtout([std_out, ab_out], msg)
428    else
429      ! Echo input to output file on unit ab_out, and to log file on unit std_out.
430      ! (Well, this might make sense for outvars, but not so much for out_spg_anal 
431      !  so there is only one call to the latter, for both units)
432      ! both 
433      choice=2
434      do ii=1,2
435        if(ii==1)iounit=ab_out
436        if(ii==2)iounit=std_out
437        write(iounit,*)' '
438        call outvars (choice,dmatpuflag,dtsets, filnam(4), iounit,mx,ndtset,ndtset_alloc,npsp,results_out_all,timopt)
439        if(ii==2)call out_spg_anal (dtsets,(ii-1),ab_out,ndtset,ndtset_alloc,results_out_all)
440        if(ii==2)write(std_out,*)' '
441      end do
442    end if
443  end if ! me==0
444 
445  ! Clean memory
446  if (test_img.and.me==0) then
447    call destroy_results_out(results_out_all)
448    ABI_FREE(results_out_all)
449  else
450    nullify(results_out_all)
451  end if
452 
453  ! In prevision of the next two calls, some variables need to be transfered.
454  ! They concern the case ndtset<2, and nimage=1 so take first value.
455  natom=dtsets(1)%natom ; nkpt=dtsets(1)%nkpt ; nsppol=dtsets(1)%nsppol
456  nfft=dtsets(1)%nfft
457 
458  ABI_MALLOC(nband,(nkpt*nsppol))
459  ABI_MALLOC(npwtot,(nkpt))
460  ABI_MALLOC(gred,(3,natom))
461  ABI_MALLOC(xred,(3,natom))
462 
463  etotal=results_out(1)%etotal(1)
464  gred(:,:)  =results_out(1)%gred(:,1:natom,1)
465  nband(:)   =dtsets(1)%nband(1:nkpt*nsppol)
466  npwtot(:)  =results_out(1)%npwtot(1:nkpt,1)
467  strten(:)  =results_out(1)%strten(:,1)
468  xred(:,:)  =results_out(1)%xred(:,1:natom,1)
469 
470  call timab(105,2,tsec)
471 
472 !------------------------------------------------------------------------------
473 
474  ! 17) Timing analysis
475  if(mod(timopt,10)/=0)then
476    call timana (mpi_enregs(1), natom, nband, ndtset, nfft, nkpt, npwtot, nsppol, timopt)
477  else
478 #if defined HAVE_MPI
479    if(me==0)then ! This is for the automatic tests
480      write(ab_out,'(5a)')ch10,ch10,'- Timing analysis has been suppressed with timopt=0',ch10,ch10
481    end if
482 #endif
483  end if
484 
485 !------------------------------------------------------------------------------
486 
487  ! 18) Bibliographical recommendations
488  if (me == 0) then
489    if (test_exit) then
490      write(msg,'(a,a,i0,a)')ch10,' abinit : before driver, prtvol=',prtvol,', debugging mode => will skip acknowledgments'
491      call wrtout([std_out, ab_out], msg)
492    else
493      call out_acknowl(dtsets, ab_out, ndtset_alloc, npsp, pspheads)
494    end if
495  end if
496 
497 !------------------------------------------------------------------------------
498 
499  ! 19) Delete the status file, and, for build-in tests, analyse the correctness of results.
500  if (ndtset == 0 .and. me == 0 .and. dtsets(1)%builtintest /= 0) then
501    call testfi(dtsets(1)%builtintest,etotal,filstat,gred,natom,strten,xred)
502  end if
503 
504  ! One should have here the explicit deallocation of all arrays
505  call destroy_results_out(results_out)
506 
507  ABI_FREE(gred)
508  ABI_FREE(nband)
509  ABI_FREE(npwtot)
510  ABI_FREE(results_out)
511  ABI_FREE(xred)
512 
513  ! 20) Write the final timing, close the output file, and write a final line to the log file
514  call timein(tsec(1),tsec(2))
515  tsec(1)=tsec(1)-tcpui
516  tsec(2)=tsec(2)-twalli
517 
518  ! Get number of comments/warnings
519  call specialmsg_getcount(ncomment,nwarning,nexit)
520  call libpaw_spmsg_getcount(ncomment_paw,nwarning_paw,nexit_paw)
521  ncomment=ncomment+ncomment_paw;nwarning=nwarning+nwarning_paw;nexit=nexit+nexit_paw
522  warn_fmt='(a,i6,a,i6,a)'
523  if (nwarning<10000.and.ncomment<10000) warn_fmt='(a,i5,a,i5,a)'
524  if (nwarning<1000 .and.ncomment<1000 ) warn_fmt='(a,i4,a,i4,a)'
525 
526 #if defined HAVE_MPI
527  write(std_out,'(a,i4,a,f13.1,a,f13.1)')' Proc.',mpi_enregs(1)%me,' individual time (sec): cpu=',tsec(1),'  wall=',tsec(2)
528  if(me==0)then
529    write(ab_out,'(3a,i4,a,f13.1,a,f13.1)')'-',ch10,'- Proc.',me,' individual time (sec): cpu=',tsec(1),'  wall=',tsec(2)
530  end if
531  call xmpi_sum(tsec, xmpi_world, ierr)
532 #else
533  write(ab_out, '(a,a,a,f13.1,a,f13.1)' )'-',ch10,'- Proc.   0 individual time (sec): cpu=',tsec(1),'  wall=',tsec(2)
534 #endif
535 
536  write(msg,'(a,80a,a,a,a)' ) ch10,('=',mu=1,80),ch10,ch10,' Calculation completed.'
537  call wrtout(ab_out, msg)
538  write(msg,fmt=warn_fmt) '.Delivered',nwarning,' WARNINGs and',ncomment,' COMMENTs to log file.'
539  if (nexit/=0) write(msg,'(3a)') trim(msg),ch10,' Note : exit requested by the user.'
540  call wrtout(ab_out, msg)
541 
542  if (me==0) then
543    write(ab_out, '(a,f13.1,a,f13.1)' )'+Overall time at end (sec) : cpu=',tsec(1),'  wall=',tsec(2)
544    write(msg, '(a,a)' ) ch10,' Calculation completed.'
545    call wrtout(std_out, msg)
546    write(msg,fmt=warn_fmt) '.Delivered',nwarning,' WARNINGs and',ncomment,' COMMENTs to log file.'
547    if (nexit/=0) write(msg,'(3a)') trim(msg),ch10,' Note : exit requested by the user.'
548    call wrtout(std_out, msg)
549  end if
550 
551  if (me==0) then
552    ! Write YAML document with the final summary.
553    ! We use this doc to test whether the calculation is completed.
554    write(std_out,"(a)")
555    write(std_out,"(a)")"--- !FinalSummary"
556    write(std_out,"(a)")"program: abinit"
557    write(std_out,"(2a)")"version: ",trim(abinit_version)
558    write(std_out,"(2a)")"start_datetime: ",start_datetime
559    write(std_out,"(2a)")"end_datetime: ",asctime()
560    write(std_out,"(a,f13.1)")"overall_cpu_time: ",tsec(1)
561    write(std_out,"(a,f13.1)")"overall_wall_time: ",tsec(2)
562    write(std_out,"(2a)")"exit_requested_by_user: ",yesno(nexit /= 0)
563    write(std_out,"(2a)")"timelimit: ",trim(get_timelimit_string())
564    write(std_out,"(a)")"pseudos: "
565    do ii=1,npsp
566      write(std_out,"(4a)")"    ",ljust(znucl2symbol(pspheads(ii)%znuclpsp), 4),": ",trim(pspheads(ii)%md5_checksum)
567    end do
568    write(std_out,"(a,i0)")"usepaw: ",dtsets(1)%usepaw
569    write(std_out,"(a,i0)")"mpi_procs: ",xmpi_comm_size(xmpi_world)
570    write(std_out,"(a,i0)")"omp_threads: ",xomp_get_num_threads(open_parallel=.True.)
571    write(std_out,"(a,i0)")"num_warnings: ",nwarning
572    write(std_out,"(a,i0)")"num_comments: ",ncomment
573    write(std_out,"(a)")"..."
574    call flush_unit(std_out)
575  end if
576 
577  if (me==0) then
578    if (xml_output) call outxml_finalise(tsec, values)
579 #ifndef HAVE_MEM_PROFILING
580    close(unit=ab_out)
581 #endif
582  end if
583 
584  ! 21) Eventual cleaning of MPI (and/or GPU) run
585  call clnmpi_img(mpi_enregs(0))
586  do ii=1,ndtset_alloc
587    if(mpi_enregs(ii)%me<0) cycle
588    call clnmpi_img(mpi_enregs(ii))
589    call clnmpi_grid(mpi_enregs(ii))
590    call clnmpi_atom(mpi_enregs(ii))
591    call clnmpi_pert(mpi_enregs(ii))
592  end do
593  do ii=0,max(1,ndtset)
594    call destroy_mpi_enreg(mpi_enregs(ii))
595  end do
596  ABI_FREE(mpi_enregs)
597 
598  ! If memory profiling is activated, check if bigdft plugin is used or not
599  print_mem_report = 1
600  do ii=1,ndtset_alloc
601    if ((dtsets(ii)%usewvl == 1) .or. (dtsets(ii)%icoulomb > 0)) then
602      print_mem_report = 0
603      exit
604    end if
605  end do
606 
607 #if defined HAVE_BIGDFT
608  if (timopt==10) then
609    call wvl_timing(xmpi_world,'== POSTPRC','PR')
610  end if
611  call f_lib_finalize()
612 #endif
613 
614  ! Here we deallocate dtsets. Do not access dtsets after this line!
615  do ii=0,size(dtsets)-1,1
616    call dtsets(ii)%free()
617  end do
618  ABI_FREE(dtsets)
619  ABI_FREE(pspheads)
620 
621 #if defined HAVE_GPU_CUDA
622  call unsetdevice_cuda(gpu_option)
623 #endif
624 
625  call xpapi_shutdown()
626 
627  ! Writes information on file about the memory before ending mpi module, if memory profiling is enabled
628  call abinit_doctor(filnam(4), print_mem_report=print_mem_report)
629 
630  call flush_unit(std_out)
631  call flush_unit(ab_out)
632 
633  if (me == 0) close(unit=ab_out)
634 
635  100 call xmpi_end()
636 
637  end program abinit