Statistiques
| Révision :

root / src / ReadGeom_cart.f90

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

1
SUBROUTINE ReadGeom_cart
2
!----------------------------------------------------------------------
3
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
4
!  Centre National de la Recherche Scientifique,
5
!  Université Claude Bernard Lyon 1. All rights reserved.
6
!
7
!  This work is registered with the Agency for the Protection of Programs 
8
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
9
!
10
!  Authors: P. Fleurat-Lessard, P. Dayal
11
!  Contact: optnpath@gmail.com
12
!
13
! This file is part of "Opt'n Path".
14
!
15
!  "Opt'n Path" is free software: you can redistribute it and/or modify
16
!  it under the terms of the GNU Affero General Public License as
17
!  published by the Free Software Foundation, either version 3 of the License,
18
!  or (at your option) any later version.
19
!
20
!  "Opt'n Path" is distributed in the hope that it will be useful,
21
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
22
!
23
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
24
!  GNU Affero General Public License for more details.
25
!
26
!  You should have received a copy of the GNU Affero General Public License
27
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
28
!
29
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
30
! for commercial licensing opportunities.
31
!----------------------------------------------------------------------
32

    
33
  Use Path_module
34
  Use Io_module
35

    
36
  IMPLICIT NONE
37

    
38
  CHARACTER(132) :: Line
39

    
40
  INTEGER(KINT) :: I, J, NAtP
41
  LOGICAL :: Debug
42

    
43
  INTERFACE
44
     function valid(string) result (isValid)
45
       CHARACTER(*), intent(in) :: string
46
       logical                  :: isValid
47
     END function VALID
48
  END INTERFACE
49

    
50
  debug=valid('Read_geom').or.valid('ReadGeom_cart')
51

    
52
 if (debug) Call Header("Entering ReadGeom_cart")
53

    
54
     DO I=1,NGeomI
55
        IF (DEBUG) WRITE(*,*) "Reading Geom :",I
56
        READ(IOIN,*) NAtp
57
        if (NAtp.NE.Nat) THEN
58
           IF (I==1) THEN
59
              WRITE(IOOUT,*) 'WARNING Number of atoms not consistent between NAMELIST &path and First geom'
60
              WRITE(IOOUT,*) "Using:",Natp 
61
              DEALLOCATE(XyzGeomI, AtName)
62
              Nat=Natp 
63
              ALLOCATE(XyzGeomI(NGeomI,3,Nat), AtName(NAt))
64
           ELSE
65
              WRITE(IOOUT,*) 'Number of atoms not consistent between geometries. STOP'
66
              STOP
67
           END IF
68
        END IF
69
        READ(IOIN,'(A)') Line
70
        DO J=1,NAt
71
           READ(IOIN,*) AtName(J),XyzGeomI(I,1:3,J)
72
        END DO
73
        If (Debug) THEN
74
           WRITE(*,*) "Geom ",I
75
           DO J=1,NAt
76
              WRITE(*,'(1X,A2,3(1X,F15.6))') AtName(J),XyzGeomI(I,1:3,J)
77
           END DO
78
        END IF
79
     END DO
80

    
81

    
82
  if (debug) Call Header("Exiting ReadGeom_cart")
83

    
84
END SUBROUTINE ReadGeom_cart