Statistiques
| Révision :

root / src / ReadGeom_turbomole.f90 @ 12

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

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