Statistiques
| Révision :

root / src / ReadGeom_siesta.f90

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

1 5 pfleura2
SUBROUTINE ReadGeom_siesta
2 5 pfleura2
! We read geometries given in siesta format
3 5 pfleura2
! Here we just read the equivalent of %block AtomicCoordinatesAndAtomicsLabel
4 5 pfleura2
! i.e. x,y,z,species
5 5 pfleura2
! we know nothing about:
6 5 pfleura2
! - the format and units
7 5 pfleura2
! - the significations of species
8 5 pfleura2
9 12 pfleura2
!----------------------------------------------------------------------
10 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
11 12 pfleura2
!  Centre National de la Recherche Scientifique,
12 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
13 12 pfleura2
!
14 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
15 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
16 12 pfleura2
!
17 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
18 12 pfleura2
!  Contact: optnpath@gmail.com
19 12 pfleura2
!
20 12 pfleura2
! This file is part of "Opt'n Path".
21 12 pfleura2
!
22 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
23 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
24 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
25 12 pfleura2
!  or (at your option) any later version.
26 12 pfleura2
!
27 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
28 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
29 12 pfleura2
!
30 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
31 12 pfleura2
!  GNU Affero General Public License for more details.
32 12 pfleura2
!
33 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
34 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
35 12 pfleura2
!
36 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
37 12 pfleura2
! for commercial licensing opportunities.
38 12 pfleura2
!----------------------------------------------------------------------
39 12 pfleura2
40 5 pfleura2
  Use Path_module
41 5 pfleura2
  Use Io_module
42 5 pfleura2
43 5 pfleura2
  IMPLICIT NONE
44 5 pfleura2
45 5 pfleura2
  INTEGER(KINT) :: I, J
46 5 pfleura2
  LOGICAL :: Debug
47 5 pfleura2
48 5 pfleura2
49 5 pfleura2
  INTERFACE
50 5 pfleura2
     function valid(string) result (isValid)
51 5 pfleura2
       CHARACTER(*), intent(in) :: string
52 5 pfleura2
       logical                  :: isValid
53 5 pfleura2
     END function VALID
54 5 pfleura2
  END INTERFACE
55 5 pfleura2
56 5 pfleura2
  debug=valid('Read_geom').or.valid('ReadGeom_siesta')
57 5 pfleura2
58 5 pfleura2
 if (debug) Call Header("Entering ReadGeom_siesta")
59 5 pfleura2
60 5 pfleura2
 IF (.NOT.ALLOCATED(IdxSpecies)) ALLOCATE(IdxSpecies(NAt))
61 5 pfleura2
62 5 pfleura2
     DO I=1,NGeomI
63 5 pfleura2
        IF (DEBUG) WRITE(*,*) "Reading Geom :",I
64 5 pfleura2
65 5 pfleura2
        DO J=1,NAt
66 5 pfleura2
           READ(IOIN,*) XyzGeomI(I,1:3,J),IdxSpecies(J)
67 5 pfleura2
        END DO
68 5 pfleura2
69 5 pfleura2
        If (Debug) THEN
70 5 pfleura2
           WRITE(*,*) "Geom ",I
71 5 pfleura2
           DO J=1,NAt
72 5 pfleura2
              WRITE(*,'(1X,3(1X,F15.6),1X,I5)') XyzGeomI(I,1:3,J),IdxSpecies(J)
73 5 pfleura2
           END DO
74 5 pfleura2
        END IF
75 5 pfleura2
     END DO
76 5 pfleura2
77 5 pfleura2
  if (debug) Call Header("Exiting ReadGeom_siesta")
78 5 pfleura2
79 5 pfleura2
END SUBROUTINE ReadGeom_siesta