TABLE OF CONTENTS


ABINIT/outvars [ Functions ]

[ Top ] [ Functions ]

NAME

 outvars

FUNCTION

 Echo variables for the ABINIT code.

COPYRIGHT

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

INPUTS

  choice= 1 if echo of preprocessed variables, 2 if echo after call driver
  dmatpuflag=flag controlling the use of an initial density matrix in PAW+U (max. value over datasets)
  dtsets(0:ndtset_alloc)=<type datafiles_type>contains all input variables
  iout=unit number for echoed output
  mxvals=maximum size of some arrays along all datasets, including:
         ga_n_rules =maximal value of input ga_n_rules for all the datasets
         gw_nqlwl   =maximal value of input gw_nqlwl for all the datasets
         lpawu      =maximal value of input lpawu for all the datasets
         mband      =maximum number of bands
         natom      =maximal value of input natom for all the datasets
         natpawu    =maximal value of number of atoms on which +U is applied for all the datasets
         natsph     =maximal value of input natsph for all the datasets
         natvshift  =maximal value of input natvshift for all the datasets
         nconeq     =maximal value of input nconeq for all the datasets
         nimage     =maximal value of input nimage for all the datasets
         nimfrqs    =maximal value of input cd_customnimfrqs for all the datasets
         nkpt       =maximal value of input nkpt for all the datasets
         nkptgw     =maximal value of input nkptgw for all the datasets
         nkpthf     =maximal value of input nkpthf for all the datasets
         nnos       =maximal value of input nnos for all the datasets
         nqptdm     =maximal value of input nqptdm for all the datasets
         nspinor    =maximal value of input nspinor for all the datasets
         nsppol     =maximal value of input nsppol for all the datasets
         nsym       =maximum number of symmetries
         ntypat     =maximum number of type of atoms
         nzchempot  =maximal value of input nzchempot for all the datasets
  ndtset=number of datasets
  ndtset_alloc=number of datasets, corrected for allocation of at least
   one data set. Use for most dimensioned arrays.
  npsp=number of pseudopotentials
  results_out(0:ndtset_alloc)=<type results_out_type>contains the results
   needed for outvars, including evolving variables
  timopt=input variable to modulate the timing

OUTPUT

  Only writing

NOTES

 Note that this routine is called only by the processor me==0 .
 In consequence, no use of message and wrtout routine.
 The lines of code needed to output the defaults are preserved
 (see last section of the routine, but are presently disabled)

PARENTS

      abinit

CHILDREN

      create_nc_file,outvar_a_h,outvar_i_n,outvar_o_z,wrtout

SOURCE

 67 #if defined HAVE_CONFIG_H
 68 #include "config.h"
 69 #endif
 70 
 71 #include "abi_common.h"
 72 
 73 subroutine outvars(choice,dmatpuflag,dtsets,filnam4,iout,&
 74 &  mxvals,ndtset,ndtset_alloc,npsp,results_out,timopt)
 75 
 76  use defs_basis
 77  use defs_abitypes
 78  use m_results_out
 79  use m_profiling_abi
 80  use m_errors
 81  use m_xomp
 82  use m_xmpi
 83 #if defined HAVE_NETCDF
 84  use netcdf
 85 #endif
 86 
 87  use m_nctk,      only : create_nc_file
 88 
 89 !This section has been created automatically by the script Abilint (TD).
 90 !Do not modify the following lines by hand.
 91 #undef ABI_FUNC
 92 #define ABI_FUNC 'outvars'
 93  use interfaces_14_hidewrite
 94  use interfaces_57_iovars, except_this_one => outvars
 95 !End of the abilint section
 96 
 97  implicit none
 98 
 99 !Arguments ------------------------------------
100 !scalars
101  integer,intent(in) :: choice,dmatpuflag,iout
102  integer,intent(in) :: ndtset,ndtset_alloc,npsp,timopt
103  type(ab_dimensions),intent(in) :: mxvals
104  character(len=*),intent(in) :: filnam4
105 !arrays
106  type(dataset_type),intent(in) :: dtsets(0:ndtset_alloc)
107  type(results_out_type),intent(in) :: results_out(0:ndtset_alloc)
108 
109 !Local variables-------------------------------
110 !scalars
111  integer,parameter :: nkpt_max=50
112  integer :: first,idtset,iimage,kptopt
113  integer :: marr,mu,ncerr
114  integer :: nshiftk
115  integer :: prtvol_glob,max_nthreads
116  integer :: rfddk,rfelfd,rfphon,rfstrs,rfuser,rfmagn,rf2_dkdk,rf2_dkde
117  integer :: ncid=0 ! Variables for NetCDF output
118  character(len=500) :: message
119  character(len=4) :: stringimage
120  type(ab_dimensions) :: multivals
121 !arrays
122  integer,allocatable :: jdtset_(:),response_(:)
123  character(len=8),allocatable :: strimg(:)
124 
125 ! *************************************************************************
126 
127 !Set up a 'global' prtvol value
128  prtvol_glob=1
129  if(sum((dtsets(:)%prtvol)**2)==0)prtvol_glob=0
130 
131 !###########################################################
132 !### 00. Echo of selected default values
133 
134  if(choice==1)then
135 
136    max_nthreads = xomp_get_max_threads()
137 #ifndef HAVE_OPENMP
138    max_nthreads = 0 ! this value signals that OMP is not enabled in ABINIT.
139 #endif
140 
141    write(iout, '(10a)' )&
142 &   '--------------------------------------------------------------------------------',ch10,&
143 &   '------------- Echo of variables that govern the present computation ------------',ch10,&
144 &   '--------------------------------------------------------------------------------',ch10,&
145 &   '-',ch10,&
146 &   '- outvars: echo of selected default values                                      '
147    write(iout, '(3(a,i3),2a)' )&
148 &   '-   iomode0 =',dtsets(0)%iomode,' , fftalg0 =',dtsets(0)%ngfft(7),' , wfoptalg0 =',dtsets(0)%wfoptalg,ch10,&
149 &   '-'
150    write(iout, '(3a,(a,i5),2a)' )&
151 &   '- outvars: echo of global parameters not present in the input file              ',ch10,&
152 &   '- ',' max_nthreads =',max_nthreads,ch10,&
153 &   '-'
154  end if
155 
156 !write(std_out,*) 'outvar 01'
157 !###########################################################
158 !### 01. First line indicating outvars
159 
160  if(choice==1)then
161    write(iout, '(a)' )&
162 &   ' -outvars: echo values of preprocessed input variables --------'
163  else
164    write(iout, '(a)' )&
165 &   ' -outvars: echo values of variables after computation  --------'
166  end if
167 
168 !###########################################################
169 !### 02. Open NetCDF file for export variables
170 
171 #ifdef HAVE_NETCDF
172  ! Enable netcdf output only if the number of datasets is small.
173  ! otherwise v6[34] crashes with errmess:
174  !    nf90_def_dim - NetCDF library returned:   NetCDF: NC_MAX_DIMS exceeded
175  ! because we keep on creating dimensions in write_var_netcdf.
176  ! one should use groups for this kind of operations!!
177 
178  ncid = 0
179  if (ndtset_alloc  < 10) then
180    if (iout==std_out)then
181      write(iout,*) ch10,' These variables are accessible in NetCDF format (',trim(filnam4)//'_OUT.nc',')',ch10
182    end if
183    call create_nc_file(trim(filnam4)//"_OUT.nc",ncid)
184 
185    if (dtsets(1)%prtvol==-2) then
186      if (ncid>0)then
187        ncid=-ncid
188      else
189        ncid=-1
190      end if
191    end if
192  else
193    MSG_WARNING("output of OUT.nc has been disabled. Too many datasets")
194  end if
195 #endif
196  !ncid = 0
197 
198 !###########################################################
199 !##1 03. Set up dimensions : determine whether these are different for different datasets.
200 
201  multivals%ga_n_rules=0
202  multivals%gw_nqlwl=0
203  multivals%mband=0
204  multivals%natom=0
205  multivals%natpawu=0
206  multivals%natsph=0
207  multivals%natvshift=0
208  multivals%nberry=0
209  multivals%nbandhf=0
210  multivals%nconeq=0
211  multivals%nfreqsp=0
212  multivals%nimage=0
213  multivals%nimfrqs=0
214  multivals%nkpt=0
215  multivals%nkptgw=0
216  multivals%nkpthf=0
217  multivals%nnos=0
218  multivals%nqptdm=0
219  multivals%nshiftk=0
220  multivals%nsp=0
221  multivals%nspinor=0
222  multivals%nsppol=0
223  multivals%nsym=0
224  multivals%ntypat=0
225  multivals%ntypalch=0
226  multivals%nzchempot=0
227 
228  if(ndtset_alloc>1)then
229    do idtset=1,ndtset_alloc
230      if(dtsets(1)%ga_n_rules/=dtsets(idtset)%ga_n_rules) multivals%ga_n_rules =1
231      if(dtsets(1)%gw_nqlwl /=dtsets(idtset)%gw_nqlwl ) multivals%gw_nqlwl =1
232      if(dtsets(1)%mband    /=dtsets(idtset)%mband    ) multivals%mband    =1
233      if(dtsets(1)%natom    /=dtsets(idtset)%natom    ) multivals%natom    =1
234      if(dtsets(1)%natpawu  /=dtsets(idtset)%natpawu  ) multivals%natpawu  =1
235      if(dtsets(1)%natsph   /=dtsets(idtset)%natsph   ) multivals%natsph   =1
236      if(dtsets(1)%natvshift/=dtsets(idtset)%natvshift) multivals%natvshift=1
237      if(dtsets(1)%nberry   /=dtsets(idtset)%nberry   ) multivals%nberry   =1
238      if(dtsets(1)%nbandhf  /=dtsets(idtset)%nbandhf  ) multivals%nbandhf  =1
239      if(dtsets(1)%nconeq   /=dtsets(idtset)%nconeq   ) multivals%nconeq   =1
240      if(dtsets(1)%nfreqsp  /=dtsets(idtset)%nfreqsp  ) multivals%nfreqsp  =1
241      if(dtsets(1)%nimage   /=dtsets(idtset)%nimage   ) multivals%nimage   =1
242      if(dtsets(1)%cd_customnimfrqs  /=dtsets(idtset)%cd_customnimfrqs  ) multivals%nimfrqs  =1
243      if(dtsets(1)%nkpt     /=dtsets(idtset)%nkpt     ) multivals%nkpt     =1
244      if(dtsets(1)%nkptgw   /=dtsets(idtset)%nkptgw   ) multivals%nkptgw   =1
245      if(dtsets(1)%nkpthf*dtsets(1)%usefock /=dtsets(idtset)%nkpthf*dtsets(idtset)%usefock) multivals%nkpthf=1
246      if(dtsets(1)%nnos     /=dtsets(idtset)%nnos     ) multivals%nnos     =1
247      if(dtsets(1)%nqptdm   /=dtsets(idtset)%nqptdm   ) multivals%nqptdm   =1
248      if(dtsets(1)%nsppol*dtsets(1)%nspinor/=dtsets(idtset)%nsppol*dtsets(idtset)%nspinor) multivals%nsp=1
249      if(dtsets(1)%nsppol   /=dtsets(idtset)%nsppol   ) multivals%nsppol   =1
250      if(dtsets(1)%nspinor  /=dtsets(idtset)%nspinor  ) multivals%nspinor  =1
251      if(dtsets(1)%nsym     /=dtsets(idtset)%nsym     ) multivals%nsym     =1
252      if(dtsets(1)%ntypat   /=dtsets(idtset)%ntypat   ) multivals%ntypat   =1
253      if(dtsets(1)%ntypalch /=dtsets(idtset)%ntypalch ) multivals%ntypalch =1
254      if(dtsets(1)%nzchempot/=dtsets(idtset)%nzchempot) multivals%nzchempot=1
255    end do
256  end if
257 
258 !DEBUG
259  write(std_out,*)' outvars : multivals%nkpthf =',multivals%nkpthf
260  write(std_out,*)' outvars : dtsets(1:ndtset_alloc)%nkpthf =',dtsets(1:ndtset_alloc)%nkpthf
261 !ENDDEBUG
262 
263  nshiftk=1
264  if(sum((dtsets(1:ndtset_alloc)%kptopt)**2)/=0)then
265    first=0
266    do idtset=1,ndtset_alloc
267      kptopt=dtsets(idtset)%kptopt
268      if(kptopt>=1)then
269        if(first==0)then
270          first=1
271          nshiftk=dtsets(idtset)%nshiftk
272        else
273          if(nshiftk/=dtsets(idtset)%nshiftk)multivals%nshiftk=1
274        end if
275      end if
276    end do
277  end if
278 
279 !###########################################################
280 !### 04. Determine whether each dataset is (or not) a response calculation
281 !## (should use optdriver, isn't it ?)
282 
283  ABI_ALLOCATE(response_,(ndtset_alloc))
284  response_(:)=0
285  do idtset=1,ndtset_alloc
286    rfddk=dtsets(idtset)%rfddk
287    rfelfd=dtsets(idtset)%rfelfd
288    rfphon=dtsets(idtset)%rfphon
289    rfstrs=dtsets(idtset)%rfstrs
290    rfuser=dtsets(idtset)%rfuser
291    rfmagn=dtsets(idtset)%rfmagn
292    rf2_dkdk=dtsets(idtset)%rf2_dkdk
293    rf2_dkde=dtsets(idtset)%rf2_dkde
294    if(rfddk/=0 .or. rfelfd/=0 .or. rfphon/=0 .or. rfstrs/=0 .or. &
295 &   rfuser/=0 .or. rf2_dkdk/=0 .or. rf2_dkde/=0 .or. rfmagn/=0)then
296      response_(idtset)=1
297    end if
298  end do
299 
300 !###########################################################
301 !### 05. Determine size of work arrays
302 
303  marr=max(3*mxvals%natom,&
304 & mxvals%natsph,&
305 & mxvals%natvshift*mxvals%nsppol*mxvals%natom,&
306 & 3*mxvals%nberry,&
307 & mxvals%nimage,&
308 & 3*mxvals%nkptgw,&
309 & 3*mxvals%nkpthf,&
310 & mxvals%nkpt*mxvals%nsppol*mxvals%mband,&
311 & 3*mxvals%nkpt,npsp,&
312 & 3*mxvals%nqptdm,&
313 & mxvals%ntypat,&
314 & 9*mxvals%nsym,3*8,&
315 & 3*mxvals%natom*mxvals%nconeq,&
316 & mxvals%nnos,&
317 & 3*mxvals%nqptdm,&
318 & 3*mxvals%nzchempot*mxvals%ntypat,&
319 & 3*mxvals%gw_nqlwl,&
320 & (2*mxvals%lpawu+1)**2*max(mxvals%nsppol,mxvals%nspinor)*mxvals%natpawu*dmatpuflag,&
321 & 30 ) ! used by ga_rules TODO : replace with mxvals% ga_n_rules
322 
323 !###########################################################
324 !### 06. Initialize strimg
325 
326  ABI_ALLOCATE(strimg,(mxvals%nimage))
327  do iimage=1,mxvals%nimage
328    if(iimage<10)then
329      write(stringimage,'(i1)')iimage
330    else if(iimage<100)then
331      write(stringimage,'(i2)')iimage
332    else if(iimage<1000)then
333      write(stringimage,'(i3)')iimage
334    else if(iimage<10000)then
335      write(stringimage,'(i4)')iimage
336    end if
337    strimg(iimage)='_'//trim(stringimage)//'img'
338  end do
339  strimg(1)=''
340 
341 !###########################################################
342 !### 07. Initialize jdtset_
343 
344  ABI_ALLOCATE(jdtset_,(0:ndtset_alloc))
345  jdtset_(0:ndtset_alloc)=dtsets(0:ndtset_alloc)%jdtset
346 
347 
348 !###########################################################
349 !### 08. Print variables, for different ranges of names
350 
351  call outvar_a_h(choice,dmatpuflag,dtsets,iout,jdtset_,marr,multivals,mxvals,&
352 & ncid,ndtset,ndtset_alloc,results_out,strimg)
353 
354  call outvar_i_n(dtsets,iout,jdtset_,marr,multivals,mxvals,&
355 & ncid,ndtset,ndtset_alloc,npsp,prtvol_glob,response_,results_out,strimg)
356 
357  call outvar_o_z(choice,dtsets,iout,&
358 & jdtset_,marr,multivals,mxvals,ncid,ndtset,ndtset_alloc,npsp,prtvol_glob,&
359 & results_out,strimg,timopt)
360 
361 
362 !###########################################################
363 !## Deallocations and cleaning
364 
365  ABI_DEALLOCATE(jdtset_)
366  ABI_DEALLOCATE(response_)
367  ABI_DEALLOCATE(strimg)
368 
369  write(message,'(a,80a)')ch10,('=',mu=1,80)
370  call wrtout(iout,message,'COLL')
371 
372 #ifdef HAVE_NETCDF
373  if (ncid /= 0) then
374    ncerr=nf90_close(abs(ncid))
375    if (ncerr/=nf90_NoErr) then
376      message='Netcdf Error while closing the OUT.nc file: '//trim(nf90_strerror(ncerr))
377      MSG_ERROR(message)
378    end if
379  end if
380 #endif
381  if (.false.) write(std_out,*) ncerr
382 
383 !**************************************************************************
384 
385 end subroutine outvars