Statistiques
| Révision :

root / src / WriteInput_siesta.f90

Historique | Voir | Annoter | Télécharger (2,93 ko)

1 7 pfleura2
 SUBROUTINE WriteInput_siesta(GeomCart,FileUnit)
2 12 pfleura2
!----------------------------------------------------------------------
3 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
4 12 pfleura2
!  Centre National de la Recherche Scientifique,
5 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
6 12 pfleura2
!
7 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
8 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
9 12 pfleura2
!
10 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
11 12 pfleura2
!  Contact: optnpath@gmail.com
12 12 pfleura2
!
13 12 pfleura2
! This file is part of "Opt'n Path".
14 12 pfleura2
!
15 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
16 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
17 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
18 12 pfleura2
!  or (at your option) any later version.
19 12 pfleura2
!
20 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
21 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
22 12 pfleura2
!
23 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
24 12 pfleura2
!  GNU Affero General Public License for more details.
25 12 pfleura2
!
26 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
27 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
28 12 pfleura2
!
29 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
30 12 pfleura2
! for commercial licensing opportunities.
31 12 pfleura2
!----------------------------------------------------------------------
32 5 pfleura2
33 7 pfleura2
! This routine writes an input for Siesta
34 5 pfleura2
35 5 pfleura2
  use VarTypes
36 5 pfleura2
  use Path_module
37 5 pfleura2
  use Io_module
38 5 pfleura2
39 5 pfleura2
  IMPLICIT NONE
40 5 pfleura2
41 5 pfleura2
  INTERFACE
42 5 pfleura2
     function valid(string) result (isValid)
43 5 pfleura2
       CHARACTER(*), intent(in) :: string
44 5 pfleura2
       logical                  :: isValid
45 5 pfleura2
     END function VALID
46 5 pfleura2
47 5 pfleura2
48 7 pfleura2
     SUBROUTINE WriteList(Input,Unit)
49 7 pfleura2
        ! This routine reads an input template for Siesta
50 5 pfleura2
51 7 pfleura2
       use VarTypes
52 7 pfleura2
       use Io_module
53 5 pfleura2
54 7 pfleura2
       IMPLICIT NONE
55 5 pfleura2
56 7 pfleura2
     ! Input
57 7 pfleura2
       TYPE (Input_line), POINTER, INTENT(IN) :: Input
58 7 pfleura2
       INTEGER(KINT), OPTIONAL, INTENT(IN) :: Unit
59 7 pfleura2
60 7 pfleura2
     END SUBROUTINE WriteList
61 5 pfleura2
62 5 pfleura2
  END INTERFACE
63 5 pfleura2
64 7 pfleura2
!Input
65 7 pfleura2
 ! Geometry in cartesian coordinates
66 7 pfleura2
  REAL(KREAL), INTENT (IN) :: geomcart(Nat,3)
67 7 pfleura2
! Unit to write to
68 7 pfleura2
  INTEGER(KINT), INTENT(IN) :: FileUnit
69 5 pfleura2
70 5 pfleura2
  LOGICAL :: Debug
71 7 pfleura2
  INTEGER(KINT) :: I,Iat
72 5 pfleura2
73 7 pfleura2
  Debug=Valid("WriteInput").OR.Valid("WriteInput_siesta")
74 5 pfleura2
75 7 pfleura2
  if (debug) Call Header("Entering WriteInput_Siesta")
76 5 pfleura2
77 5 pfleura2
78 7 pfleura2
  Call WriteList(Siesta_input,Unit=FileUnit)
79 5 pfleura2
80 7 pfleura2
  WRITE(FileUnit,*)
81 5 pfleura2
82 7 pfleura2
  WRITE(FileUnit,'(1X,A)')  '%block AtomicCoordinatesAndAtomicSpecies'
83 5 pfleura2
84 7 pfleura2
  DO I=1,Nat
85 7 pfleura2
     If (renum) THEN
86 7 pfleura2
        Iat=Order(I)
87 7 pfleura2
        WRITE(FileUnit,'(1X,3(1X,F15.8),1X,I5,1X,A)') GeomCart(Iat,:)/Siesta_Unit_Read, IdxSpecies(Iat),TRIM(Siesta_Paste(I))
88 7 pfleura2
     ELSE
89 7 pfleura2
        Iat=OrderInv(I)
90 7 pfleura2
        WRITE(FileUnit,'(1X,3(1X,F15.8),1X,I5,1X,A)') GeomCart(I,:)/Siesta_Unit_Read, IdxSpecies(Iat), TRIM(Siesta_Paste(Iat))
91 7 pfleura2
     END IF
92 7 pfleura2
  END DO
93 5 pfleura2
94 7 pfleura2
  WRITE(FileUnit,'(1X,A)')  '%endblock AtomicCoordinatesAndAtomicSpecies'
95 7 pfleura2
  WRITE(FileUnit,*)
96 5 pfleura2
97 5 pfleura2
98 5 pfleura2
99 7 pfleura2
  if (debug) Call Header("Exiting WriteInput_Siesta")
100 7 pfleura2
101 7 pfleura2
END SUBROUTINE WRITEINPUT_SIESTA