1!
2! Copyright (C) 1996-2016	The SIESTA group
3!  This file is distributed under the terms of the
4!  GNU General Public License: see COPYING in the top directory
5!  or http://www.gnu.org/copyleft/gpl.txt.
6! See Docs/Contributors.txt for a list of contributors.
7!-----------------------------------------------------------------------------
8!
9! module fsiesta
10!
11! Support routines for siesta-as-a-subroutine.
12! This version requires SIESTA to be compiled together with its calling program.
13! It allows multiple siesta processes to run and communicate through MPI.
14!
15! Public procedures provided by this module:
16!   siesta_launch   : Starts a siesta process
17!   siesta_units    : Sets the physical units for calls to siesta_forces
18!   siesta_forces   : Calculates atomic forces, energy, and stress
19!   siesta_get      : Calculates other properties
20!   siesta_quit     : Finishes a siesta process
21!
22! Public parameters, variables and arrays provided by this module:
23!   none
24!
25! Interfaces of public procedures:
26!
27!   subroutine siesta_launch( label, nnodes, mpi_comm, launcher, localhost )
28!     character(len=*),intent(in) :: label    : Name of siesta process
29!                                               (prefix of its .fdf file)
30!     integer,optional,intent(in) :: nnodes   : Number of MPI processes
31!                                               reserved for each siesta process
32!     integer,optional,intent(in) :: mpi_comm : MPI communicator defined by the
33!                                               calling program for siesta use
34!     character(len=*),optional,intent(in):: launcher (not used in this version)
35!     logical,optional,intent(in) :: localhost : will siesta run at localhost?
36!                                                (not used in this version)
37!   end subroutine siesta_launch
38!
39!   subroutine siesta_units( length, energy )
40!     character(len=*),intent(in) :: length : Physical unit of length
41!     character(len=*),intent(in) :: energy : Physical unit of energy
42!   end subroutine siesta_units
43!
44!   subroutine siesta_forces( label, na, xa, cell, energy, fa, stress )
45!     character(len=*), intent(in) :: label      : Name of siesta process
46!     integer,          intent(in) :: na         : Number of atoms
47!     real(dp),         intent(in) :: xa(3,na)   : Cartesian coords
48!     real(dp),optional,intent(in) :: cell(3,3)  : Unit cell vectors
49!     real(dp),optional,intent(out):: energy     : Total energy
50!     real(dp),optional,intent(out):: fa(3,na)   : Atomic forces
51!     real(dp),optional,intent(out):: stress(3,3): Stress tensor
52!   end subroutine siesta_forces
53!
54!   subroutine siesta_get( label, property, value, units )
55!     character(len=*), intent(in) :: label      : Name of siesta process
56!     character(len=*), intent(in) :: property   : Name of required magnitude
57!     real(dp),         intent(out):: value      : Value of the magnitude
58!                                                (various dimensions overloaded)
59!     character(len=*), intent(out):: units      : Name of physical units
60!   end subroutine siesta_get
61!
62!   subroutine siesta_quit( label )
63!     character(len=*),intent(in) :: label       : Name of siesta process
64!   end subroutine siesta_quit
65!
66! Properties available through siesta_get:
67!
68!   property name:  'atomic_numbers'
69!            size:  na (number of atoms per unit cell)
70!            units: ' '
71!
72! Usage:
73! - The typical expected profiles for calling siesta_launch are
74!   - call siesta_launch(myLabel) => a siesta process is launched for each
75!     label, with as many MPI processes as they use the same label. Each
76!     siesta process will read a different myLabel.fdf data file.
77!   - call siesta_launch(singleLabel,siestaNodes) => a number nSiestaProc =
78!     (totalNodes/siestaNodes) of siesta processes are launched, each with
79!     siestaNodes MPI processes. All will read the same file singleLabel.fdf
80!     The MPI processes of any given siesta process have conscutive ranks
81!     so that siestaNode = int(MPInode/siestaNodes)
82!   - call siesta_launch(singleLabel,mpi_comm=siestaComm) => the same as
83!     previous one, but with more control and flexibility in distributing
84!     MPI processes among siesta processes (notice: 'mpi_comm=' is mandatory)
85! - Using nnodes/mpi_comm AND different labels is possible but care must be
86!   paid to their consistency, i.e. different labels cannot occur within the
87!   same siesta process.
88! - A data file named label.fdf (e.g. H2O.fdf) must be present in the working
89!   directory for each label used in siesta_launch. Parameter NumberOfAtoms
90!   in label.fdf must coincide with input argument na in siesta_forces.
91!   See siesta manual for format and required parameters in label.fdf
92! - A statement 'MD.TypeOfRun forces' must be present in label.fdf, to istruct
93!   siesta not to perform any dynamics or relaxation of its own, and to accept
94!   instead the geometries from the master program
95! - A pseudopotential data file for each atomic species must also be present
96! - The call to siesta_launch can be omited in serial execution, and when
97!   neither nnodes nor mpi_comm are present. If the call is present, it must
98!   be before the first call to siesta_forces.
99! - siesta_units may be called either before or after siesta_launch
100! - The stress is defined as dE/d(strain)/Volume, with a positive sign
101!   when the system tends to contract (negative pressure)
102! - Output unit 6 should be open explicitly, assigning it to a file, before
103!   calling siesta_launch. Otherwise, the output of print (or write(unit=6)),
104!   after calling siesta_launch, may be written on a file named MAIN_OUTPUT.
105!
106! Sample usage for serial MD simulation:
107!   use fsiesta, only: siesta_forces, siesta_get
108!   character(len=32):: label='H2O', units
109!   integer:: na
110!   real*8 :: energy, dipole(3), cell(3,3), stress(3,3)
111!   real*8 :: fa(3,maxAtoms), xa(3,maxAtoms)
112!   do mdStep = 1,nSteps
113!     ... find the new geometry. Angstroms & eV are assumed.
114!     call siesta_forces( label, na, xa, cell, energy, fa, stress )
115!   end do
116!   call siesta_get( label, 'dipole', dipole, units )
117!
118! Sample usage for a nudged elastic band calculation:
119!   use mpi,     only: MPI_Comm_World
120!   use fsiesta, only: siesta_launch, siesta_units, siesta_forces
121!   character(len=20):: label='Si_vacancy'
122!   integer:: error, MPI_Comm_Siesta, myNode, myNudge
123!   integer:: na, nNodes, nNudges, siestaNodes
124!   real*8 :: energy, cell(3,3), stress(3,3), fa(3,maxAtoms), xa(3,maxAtoms)
125!   close(6)
126!   open(6,file='neb.out')
127!   call MPI_Comm_Rank( MPI_Comm_World, myNode, error )
128!   call MPI_Comm_Size( MPI_Comm_World, nNodes, error )
129!   ! Set distribution of MPI processes by
130!     siestaNodes = nNodes / nNudges
131!     call siesta_launch( label, siestaNodes )
132!   ! Or equivalently (but not simultaneously)
133!     myNudge = myNode / nNudges
134!     call MPI_Comm_Split( MPI_Comm_World, myNudge, 0, MPI_Comm_Siesta, error )
135!     call siesta_launch( label, mpi_comm=MPI_Comm_Siesta )
136!   call siesta_units( 'bohr', 'Ryd' )
137!   do iStep = relaxSteps
138!     ... find my nudge's new geometry
139!     call siesta_forces( label, na, xa, cell, energy, fa, stress )
140!   end do
141!
142! Behaviour:
143! - Different siesta processes are distiguished because they either:
144!   - have different labels in siesta_launch
145!   - belong to different MPI groups, as set by nnodes or mpi_comm
146! - If mpi_comm is present, nnodes is ignored
147! - If neither nnodes nor mpi_comm are present, the MPI processes are
148!   assigned to the siesta processes according to the input labels
149! - If siesta_units is not called, length='Ang', energy='eV' are
150!   used by default. If it is called more than once, the units in the
151!   last call become in effect.
152! - The physical units set by siesta_units are used for all the siesta
153!   processes launched
154! - If siesta_forces is called without a previous call to siesta_launch
155!   for that label, an internal call siesta_launch(label) is generated
156! - If argument cell is not present in the call to siesta_forces, or if
157!   the cell has zero volume, it is assumed that the system is a molecule,
158!   and a supercell is generated automatically by siesta so that the
159!   different images do not overlap. In this case the stress returned
160!   has no physical meaning.
161! - The following events result in a stopping error message:
162!   - mpi_comm is not a valid MPI communicator
163!   - two MPI processes in the same siesta process have a different label
164!   - two different labels are used in any calls within the same MPI process
165!   - siesta_launch is called twice
166!   - siesta_quit is called before a call to siesta_launch or siesta_forces
167!   - file label.fdf is not found
168!   - NumberOfAtoms in label.fdf is different from na input in siesta_forces
169!   - An input argument of siesta_forces differs in two MPI processes within
170!     the same siesta process
171!
172! Written by J.M.Soler. Oct.2010
173!-----------------------------------------------------------------------------
174
175MODULE fsiesta
176
177! Used module parameters and procedures
178  use precision,        only: dp              ! Double precision real kind
179  use sys,              only: die             ! Termination routine
180  use m_siesta_init,    only: siesta_init     ! Siesta initialization
181  use m_siesta_analysis,only: siesta_analysis ! Post processing calculations
182  use m_siesta_move,    only: siesta_move     ! Move atoms
183  use m_siesta_forces,  only: &
184    external_siesta_forces => siesta_forces   ! Atomic force calculation
185  use m_siesta_end,     only: siesta_end      ! Finish siesta
186  use siesta_master,    only: siesta_server        ! Is siesta a server?
187  use siesta_master,    only: siesta_subroutine    ! Is siesta a subroutine?
188  use siesta_master,    only: setMasterUnits       ! Set physical units
189  use siesta_master,    only: setCoordsFromMaster  ! Set atomic positions
190  use siesta_master,    only: getForcesForMaster   ! Get atomic forces
191  use siesta_master,    only: getPropertyForMaster ! Get other properties
192  use siesta_master,    only: siesta_server        ! Is siesta a server?
193  use siesta_master,    only: siesta_subroutine    ! Is siesta a subroutine?
194  use siesta_master,    only: input_file           ! fdf data file
195#ifdef MPI
196  use mpi_siesta, only: MPI_Comm_World => true_MPI_Comm_World ! The true
197                                                              ! MPI_COMM_WORLD
198  use mpi_siesta, only: MPI_Comm_Siesta => MPI_Comm_World ! What siesta uses
199                                                          ! as MPI_Comm_World
200  use mpi_siesta, only: MPI_Integer           ! Integer data type
201  use mpi_siesta, only: MPI_Character         ! Character data type
202  use mpi_siesta, only: MPI_Double_Precision  ! Real double precision type
203  use mpi_siesta, only: MPI_Max               ! Maximum-option switch
204#endif
205
206  implicit none
207
208PUBLIC :: &
209  siesta_launch, &! Start a siesta process
210  siesta_units,  &! Set physical units
211  siesta_forces, &! Calculate atomic forces, energy, and stress
212  siesta_get,    &! Calculate other magnitudes
213  siesta_quit     ! Finish siesta process
214
215PRIVATE ! Nothing is declared public beyond this point
216
217! Global module variables
218  integer,      parameter :: maxLenLabel = 32
219  integer,      parameter :: maxLenFile = 300
220  logical,           save :: siesta_launched = .false.
221  logical,           save :: siesta_quitted  = .false.
222  logical,           save :: analysed = .false.
223  logical,           save :: relaxed = .false.
224  integer,           save :: step  = 0
225  character(len=32), save :: xunit = 'Ang'
226  character(len=32), save :: eunit = 'eV'
227  character(len=32), save :: funit = 'eV/Ang'
228  character(len=32), save :: sunit = 'eV/Ang**3'
229  character(len=maxLenLabel):: myLabel = ' '
230  character(len=*),parameter:: mainOutFileDef = 'MAIN_OUTPUT'
231  character(len=maxLenFile) :: mainOutFile = mainOutFileDef
232
233interface siesta_get
234  module procedure siesta_get_rank0, siesta_get_rank1, siesta_get_rank2
235end interface
236
237CONTAINS
238
239!---------------------------------------------------
240
241subroutine siesta_launch( label, nNodes, mpi_comm, launcher, localhost )
242  implicit none
243  character(len=*),  intent(in) :: label    ! Name of the siesta process
244  integer, optional, intent(in) :: nNodes   ! Number of MPI processes to be used
245  integer, optional, intent(in) :: mpi_comm ! MPI communicator to be used
246  character(len=*),optional,intent(in):: launcher  ! Not used in this version
247  logical,         optional,intent(in):: localhost ! Not used in this version
248
249#ifdef MPI
250  logical:: initialized, labelFound, mainOutFileOpened
251  integer:: error, iColor, iNode, lenLabel, &
252            myColor, myLenLabel, myNode, mySiestaNode, &
253            nColors, siestaNodes, totNodes
254  integer,  allocatable:: color(:)
255  character(len=maxLenLabel):: rootLabel
256  character(len=maxLenLabel),allocatable:: colorLabel(:), nodeLabel(:)
257#endif
258
259! DEBUG
260!  character(len=32):: output_file
261!  inquire( unit=6, name=output_file )
262!  print*,'siesta_launch: output file = ', trim(output_file)
263! END DEBUG
264
265! Check that siesta has not been launched yet
266  if (siesta_launched .or. siesta_quitted) &
267    print*, 'siesta_launch: ERROR: siesta process already launched'
268
269! Declare siesta as a server subroutine and set input file
270  siesta_server     = .true.
271  siesta_subroutine = .true.
272  input_file = trim(label)//'.fdf'
273
274! Store label
275  myLabel = label
276
277#ifdef MPI
278
279! Initialise MPI unless siesta is running as a subroutine
280! of a driver program that may have initialized MPI already
281  call MPI_Initialized( initialized, error )
282  if (.not.initialized) call MPI_Init( error )
283
284! Get total number of MPI processes (nodes) and my index among them
285  call MPI_Comm_Size( MPI_Comm_World, totNodes, error )
286  call MPI_Comm_Rank( MPI_Comm_World, myNode, error )
287
288! Find maximum label length
289  myLenLabel = len(trim(label))
290  call MPI_AllReduce( myLenLabel, lenLabel, 1, MPI_Integer, &
291                      MPI_Max, MPI_Comm_World, error )
292  if (lenLabel>maxLenLabel) &
293    call die('siesta_launch: ERROR: parameter maxLenLabel too small')
294
295! Start parallel siesta process
296  if (present(mpi_comm)) then                   ! Use input MPI communicator
297
298    ! Check that mpi_comm is a valid MPI communicator
299    call MPI_Comm_Size( mpi_comm, siestaNodes, error )
300    if (error/=0) &
301      call die('siesta_launch: ERROR: mpi_comm not a valid MPI communicator')
302
303    ! Assign communicator to siesta
304    MPI_Comm_Siesta = mpi_comm
305
306  elseif (present(nNodes) .and. nNodes>0) then  ! Create new MPI communicator
307
308    call MPI_Comm_Rank( MPI_Comm_World, myNode, error )
309    myColor = myNode/nNodes
310    call MPI_Comm_Split( MPI_Comm_World, myColor, 0, MPI_Comm_Siesta, error )
311
312  else   ! Create new MPI communicator according to label(s)
313
314    ! Collect all labels
315    allocate( nodeLabel(totNodes) )
316    call MPI_AllGather( myLabel,   maxLenLabel, MPI_Character, &
317                        nodeLabel, maxLenLabel, MPI_Character, &
318                        MPI_Comm_World, error )
319
320    ! Assing processor colors according to labels
321    allocate( color(totNodes), colorLabel(totNodes) )
322    nColors = 0
323    do iNode = 1,totNodes
324      labelFound = .false.
325      do iColor = 1,nColors
326        if (nodeLabel(iNode)==colorLabel(iColor)) then
327          labelFound = .true.
328          color(iNode) = iColor
329          exit ! iColor loop
330        end if
331      end do ! iColor
332      if (.not.labelFound) then
333        nColors = nColors + 1
334        colorLabel(nColors) = nodeLabel(iNode)
335        color(iNode) = nColors
336      end if
337    end do ! iNode
338
339    ! Create new communicator
340    myColor = color(myNode+1)
341    call MPI_Comm_Split( MPI_Comm_World, myColor, 0, MPI_Comm_Siesta, error )
342    deallocate( color, colorLabel, nodeLabel )
343
344  end if ! (present(mpi_comm))
345
346! Check that my siesta process has a unique label
347  rootLabel = myLabel
348  call MPI_Bcast( rootLabel, maxLenLabel, MPI_Character, &
349                  0, MPI_Comm_Siesta, error )
350  if (myLabel/=rootLabel) &
351    call die('siesta_launch: ERROR: label mismatch in siesta process')
352
353! Store name of output file of the calling program
354  inquire( unit=6, name=mainOutFile )
355  inquire( file=mainOutFile, opened=mainOutFileOpened )
356  if (.not.mainOutFileOpened) mainOutFile = mainOutFileDef
357! DEBUG
358!  if (myNode==0) print*,'siesta_launch: mainOutFile= ',trim(mainOutFile)
359! END DEBUG
360
361! Create a directory for each siesta process, e.g.
362!   mkdir -p H2O_proc07
363!   cp -n H2O_proc07.* *.fdf *.psf *.vps *.ion H2O_proc07 2> /dev/null
364  call MPI_Comm_Rank( MPI_Comm_Siesta, mySiestaNode, error )
365  if (mySiestaNode==0) then
366    call system('mkdir -p '//trim(label))
367    call system('cp -n ' // trim(label) // '.* ' // trim(label))
368    call system('cp -n *.fdf *.vps *.psf *.ion ' &
369                // trim(label) // ' 2> /dev/null')
370  endif
371
372#endif
373
374! Initialize flags and counters
375  siesta_launched = .true.
376  siesta_quitted  = .false.
377  analysed        = .false.
378  relaxed         = .false.
379  step = 0
380
381end subroutine siesta_launch
382
383!---------------------------------------------------
384
385subroutine siesta_units( length, energy )
386  implicit none
387  character(len=*), intent(in) :: length, energy
388  xunit = length
389  eunit = energy
390  funit = trim(eunit)//'/'//trim(xunit)
391  sunit = trim(eunit)//'/'//trim(xunit)//'**3'
392  call setMasterUnits( xunit, eunit )
393end subroutine siesta_units
394
395!---------------------------------------------------
396
397subroutine siesta_forces( label, na, xa, cell, energy, fa, stress )
398  implicit none
399  character(len=*),   intent(in) :: label
400  integer,            intent(in) :: na
401  real(dp),           intent(in) :: xa(3,na)
402  real(dp), optional, intent(in) :: cell(3,3)
403  real(dp), optional, intent(out):: energy
404  real(dp), optional, intent(out):: fa(3,na)
405  real(dp), optional, intent(out):: stress(3,3)
406
407  real(dp):: e, f(3,na), myCell(3,3), s(3,3)
408  integer :: myNode=0
409
410#ifdef MPI
411  integer :: error, n
412  real(dp):: c(3,3), x(3,na)
413#endif
414
415! Launch siesta, if not yet done
416  if (.not.siesta_launched) call siesta_launch( label )
417
418! Check label
419  if (label/=myLabel) call die('siesta_forces: ERROR: label mismatch')
420
421! Set unit cell vectors
422  if (present(cell)) then
423    myCell = cell
424  else
425    myCell = 0
426  end if
427
428#ifdef MPI
429! Check that input arguments are equal in all MPI processes
430  call MPI_Comm_Rank( MPI_Comm_Siesta, myNode, error )
431  n = na
432  x = xa
433  c = myCell
434  call MPI_Bcast( n, 1, MPI_Integer, 0, MPI_Comm_Siesta, error )
435  call MPI_Bcast( x, 3*na, MPI_Double_Precision, 0, MPI_Comm_Siesta, error )
436  call MPI_Bcast( c, 3*3, MPI_Double_Precision, 0, MPI_Comm_Siesta, error )
437  if (n/=na .or. any(x/=xa) .or. any(c/=myCell)) &
438    call die('siesta_forces: ERROR: input mismatch among MPI processes')
439#endif
440
441#ifdef MPI
442! Change directory and set output file
443  call chdir(trim(label))
444  close(unit=6)
445  open(unit=6, file=trim(label)//'.out', position='append')
446#endif
447
448! Copy master's coordinates to master repository
449  call setCoordsFromMaster( na, xa, myCell )
450
451! BEGIN DEBUG: Print coords
452  if (myNode==0) then
453    write(6,'(/,2a)')          'siesta_forces: label = ', trim(label)
454    write(6,'(3a,/,(3f12.6))') 'siesta_forces: cell (',trim(xunit),') =',myCell
455    write(6,'(3a,/,(3f12.6))') 'siesta_forces: xa (',trim(xunit),') =', xa
456    write(6,*) ' '
457  end if
458! END DEBUG
459
460! Move atoms (positions will be read from master repository)
461  if (step==0) then
462    call siesta_init()
463  else
464    call siesta_move( step, relaxed )
465  end if
466  step = step + 1
467
468! Calculate forces
469  call external_siesta_forces( step )
470
471! Get from master repository the forces for master
472  call getForcesForMaster( na, e, f, s )
473
474! BEGIN DEBUG: Print forces
475  if (myNode==0) then
476    write(6,'(/,3a,f12.6)')    'siesta_forces: energy (',trim(eunit),') =', e
477    write(6,'(3a,/,(3f12.6))') 'siesta_forces: stress (',trim(sunit),') =', s
478    write(6,'(3a,/,(3f12.6))') 'siesta_forces: forces (',trim(funit),') =', f
479    write(6,*) ' '
480  end if
481! END DEBUG
482
483! Copy results to output arguments
484  if (present(energy)) energy = e
485  if (present(fa))     fa     = f
486  if (present(stress)) stress = s
487
488! Flag that post processing analysis has not been done for this geometry
489  analysed = .false.
490
491#ifdef MPI
492! Go back to parent directory and reset output file
493  call chdir('..')
494  close(unit=6)
495  open(unit=6, file=trim(mainOutFile), position='append')
496#endif
497
498end subroutine siesta_forces
499
500!---------------------------------------------------
501
502subroutine siesta_get_rank0( label, property, value, units )
503  character(len=*), intent(in) :: label      ! Name of siesta process
504  character(len=*), intent(in) :: property   ! Name of required magnitude
505  real(dp),         intent(out):: value      ! Value of the magnitude
506  character(len=*), intent(out):: units      ! Name of physical units
507  real(dp):: v(1)
508  call siesta_get_value( label, property, 1, v, units )
509  value = v(1)
510end subroutine siesta_get_rank0
511
512!---------------------------------------------------
513
514subroutine siesta_get_rank1( label, property, value, units )
515  character(len=*), intent(in) :: label      ! Name of siesta process
516  character(len=*), intent(in) :: property   ! Name of required magnitude
517  real(dp),         intent(out):: value(:)   ! Value(s) of the magnitude
518  character(len=*), intent(out):: units      ! Name of physical units
519  integer:: vsize
520  vsize = size(value)
521  call siesta_get_value( label, property, vsize, value, units )
522end subroutine siesta_get_rank1
523
524!---------------------------------------------------
525
526subroutine siesta_get_rank2( label, property, value, units )
527  character(len=*), intent(in) :: label      ! Name of siesta process
528  character(len=*), intent(in) :: property   ! Name of required magnitude
529  real(dp),         intent(out):: value(:,:) ! Value(s) of the magnitude
530  character(len=*), intent(out):: units      ! Name of physical units
531  integer:: vsize
532  vsize = size(value)
533  call siesta_get_value( label, property, vsize, value, units )
534end subroutine siesta_get_rank2
535
536!---------------------------------------------------
537
538recursive subroutine siesta_get_value( label, property, vsize, value, units )
539  character(len=*), intent(in) :: label         ! Name of siesta process
540  character(len=*), intent(in) :: property      ! Name of required magnitude
541  integer,          intent(in) :: vsize         ! Size of value array
542  real(dp),         intent(out):: value(vsize)  ! Value(s) of the magnitude
543  character(len=*), intent(out):: units         ! Name of physical units
544
545  character(len=132):: error, message
546
547#ifdef MPI
548! Change directory and set output file
549  call chdir(trim(label))
550  close(unit=6)
551  open(unit=6, file=trim(label)//'.out', position='append')
552#endif
553
554! Check that siesta has been launched
555  if (.not.siesta_launched) call die('siesta_get: ERROR: siesta not launched')
556
557! Check label
558  if (label/=myLabel) call die('siesta_get: ERROR: label mismatch')
559
560! Get property from master repository
561  call getPropertyForMaster( property, vsize, value, units, error )
562
563! Check that this property is returned with the right size
564  if (error=='unknown_property') then
565    if (analysed) then
566      write(message,*) 'siesta_get: ERROR: not prepared for property = ', &
567                        trim(property)
568      call die( trim(message) )
569    else ! (.not.analysed) => try again after performing post-processing
570      call siesta_analysis( relaxed )
571      analysed = .true.
572      call siesta_get_value( label, property, vsize, value, units )
573    end if ! (analysed)
574  elseif (error=='wrong_size') then
575    write(message,*) 'siesta_get: ERROR: wrong array size for property = ', &
576                      trim(property)
577    call die( trim(message) )
578  end if ! (error=='unknown_property')
579
580#ifdef MPI
581! Go back to parent directory and reset output file
582  call chdir('..')
583  close(unit=6)
584  open(unit=6, file=trim(mainOutFile), position='append')
585#endif
586
587end subroutine siesta_get_value
588
589!---------------------------------------------------
590
591subroutine siesta_quit( label )
592  implicit none
593  character(len=*), intent(in) :: label
594
595#ifdef MPI
596! Change directory and set output file
597  call chdir(trim(label))
598  close(unit=6)
599  open(unit=6, file=trim(label)//'.out', position='append')
600#endif
601
602  if (.not.siesta_launched) then
603    call die('siesta_quit: ERROR: no siesta process launched')
604  elseif (label /= myLabel) then
605    call die('siesta_quit: ERROR: label mismatch')
606  endif
607
608! Finish siesta process
609  call siesta_end()
610
611  siesta_launched = .false.
612  siesta_quitted  = .true.
613
614#ifdef MPI
615! Go back to parent directory and reset output file
616  call chdir('..')
617  close(unit=6)
618  open(unit=6, file=trim(mainOutFile), position='append')
619#endif
620
621end subroutine siesta_quit
622
623END MODULE fsiesta
624
625