Statistiques
| Révision :

root / src / Write_path.f90

Historique | Voir | Annoter | Télécharger (6,19 ko)

1
SUBROUTINE Write_path(Iopt)
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
  INTEGER(KINT), INTENT(IN) :: Iopt
39

    
40
  INTEGER(KINT) :: IGeom, Iat, I
41
  REAL(KREAL), ALLOCATABLE :: GeomTmpC(:), GeomTmp(:),GeomTmpC2(:,:)
42
  CHARACTER(SCHARS) :: Line
43
  CHARACTER(LCHARS) ::Title
44
  LOGICAL :: Debug
45

    
46
  INTERFACE
47
     function valid(string) result (isValid)
48
       CHARACTER(*), intent(in) :: string
49
       logical                  :: isValid
50
     END function VALID
51
  END INTERFACE
52

    
53
  debug=valid('write_path').OR.valid('writepath')
54
  if (debug) Call Header("Entering Write_PATH")
55

    
56

    
57
  ALLOCATE(GeomTmpC(3*Nat), GeomTmp(NCoord),GeomTmpC2(Nat,3))
58

    
59
  IF (IOpt.GE.0) THEN
60
     WRITE(Line,'(I5)') Iopt
61
  ELSE
62
     Line="Ini"
63
     Energies=0.
64
  END IF
65
  OPEN(IOTMP,File=Trim(PathName) // '.' // AdjustL(TRIM(Line)))
66
  IF ((COORD.EQ.'ZMAT').OR.(COORD.EQ.'MIXED').OR.(COORD.EQ.'BAKER')) &
67
       OPEN(IOCART,File=TRIM(PathName) // '_cart.' //  AdjustL(TRIM(Line)))
68

    
69
  DO IGeom=1,NGeomF
70
     WRITE(Title,"('Geometry ',I3,'/',I3,' for iteration ',I3,' E=',F13.6)") Igeom,NgeomF,Iopt,Energies(IGeom)
71
     SELECT CASE(Coord)
72
     CASE ('CART','HYBRID')
73
        ! XyzGeomF is 3,Nat... but Printgeom expects Nat,3... 
74
        ! this should really be rewritten !!!!
75
        GeomTmp=Reshape(reshape(XyzGeomF(IGeom,:,:),(/Nat,3/),ORDER=(/2,1/)),(/3*Nat/)) 
76
     CASE ('ZMAT','MIXED','BAKER')
77
        GeomTmp=IntCoordF(IGeom,:)
78
     CASE DEFAULT
79
        WRITE(*,*) "Coord=",TRIM(Coord)," not recognized in Write_path. L34.STOP"
80
        STOP
81
     END SELECT
82

    
83
     ! Nothing for the baker case.
84
     Call PrintGeom(Title,Nat,NCoord,GeomTmp,Coord,IoTmp,Atome,Order,OrderInv,IndZmat)
85

    
86
     IF (COORD.EQ.'ZMAT') THEN
87
        ! Writing the Cartesian coordinates
88
        WRITE(IOCART,'(1X,I5)') Nat
89
        WRITE(IOCART,'(1X,A)') Title
90
        ! we have to generate the cartesian coordinates from the internal coordinates
91
        Call Int2Cart(nat,indzmat,GeomTmp,GeomTmpC)
92
        GeomTmpC2=reshape(GeomTmpC,(/Nat,3/))
93
        DO I=1,Nat
94
           IF (renum) THEN
95
              Iat=Order(I)
96
              !             WRITE(IOCART,'(1X,A10,3(1X,F15.8))') Trim(AtName(I)),GeomTmpC(3*Iat-2:3*Iat)
97
              WRITE(IOCART,'(1X,A10,3(1X,F15.8))') Trim(AtName(I)),GeomTmpC2(Iat,1:3)
98
           ELSE
99
              Iat=OrderInv(I)
100
              !            WRITE(IOCART,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomTmpC(3*I-2:3*I)
101
              WRITE(IOCART,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomTmpC2(I,1:3)
102
           END IF
103
        END DO
104
     END IF ! matches IF (COORD.EQ.'ZMAT') THEN
105

    
106
     IF (COORD.EQ.'BAKER') THEN
107
        ! Writing the Cartesian coordinates
108
        WRITE(IOCART,'(1X,I5)') Nat
109
        WRITE(IOCART,'(1X,A)') Title
110
        ! we have to generate the cartesian coordinates from the internal coordinates
111
        ! we can also print the cartesiann coordinates directly from XyzGeomF??
112
        !Call ConvertBakerInternal_cart(InCoordF(IGeom-1,:),InCoordF(IGeom,:))
113
        ! XyzGeomF(NGeomF,3,Nat), GeomTmpC(3*Nat),GeomTmpC2(Nat,3)
114
        !GeomTmpC2=reshape(GeomTmpC,(/Nat,3/)). XyzGeomF is already updated in 
115
        ! EgradPath.f90
116
        DO I =1, 3
117
           GeomTmpC2(:,I)=XyzGeomF(IGeom,I,:)
118
        END DO
119
        DO I=1,Nat
120
           IF (renum) THEN
121
              Iat=Order(I)
122
              !             WRITE(IOCART,'(1X,A10,3(1X,F15.8))') Trim(AtName(I)),GeomTmpC(3*Iat-2:3*Iat)
123
              !Print *, GeomTmpC2(Iat,1:3)
124
              WRITE(IOCART,'(1X,A10,3(1X,F15.8))') Trim(AtName(I)),GeomTmpC2(Iat,1:3)
125
           ELSE
126
              Iat=OrderInv(I)
127
              !            WRITE(IOCART,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomTmpC(3*I-2:3*I)
128
              WRITE(IOCART,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomTmpC2(I,1:3)
129
           END IF
130
        END DO
131
     END IF ! matches IF (COORD.EQ.'BAKER') THEN
132

    
133
     IF (COORD.EQ.'MIXED') THEN
134
        ! Writing the Cartesian coordinates
135
        WRITE(IOCART,'(1X,I5)') Nat
136
        WRITE(IOCART,'(1X,A)') Title
137
        ! we have to generate the cartesian coordinates from the internal coordinates
138
        Call Mixed2Cart(nat,indzmat,geomtmp,GeomTmpC)
139
        GeomTmpC2=reshape(GeomTmpC,(/Nat,3/))
140
        DO I=1,Nat
141
           IF (renum) THEN
142
              Iat=Order(I)
143
              !             WRITE(IOCART,'(1X,A10,3(1X,F15.8))') Trim(AtName(I)),GeomTmpC(3*Iat-2:3*Iat)
144
              WRITE(IOCART,'(1X,A10,3(1X,F15.8))') Trim(AtName(I)),GeomTmpC2(Iat,1:3)
145
           ELSE
146
              Iat=OrderInv(I)
147
              !             WRITE(IOCART,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomTmpC(3*I-2:3*I)
148
              WRITE(IOCART,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomTmpC2(I,1:3)
149
           END IF
150
        END DO
151
     END IF ! matches IF (COORD.EQ.'MIXED') THEN
152
  END DO ! matches DO IGeom=1,NGeomF
153
  CLOSE(IOTMP)
154
  IF ((COORD.EQ.'ZMAT').OR.(COORD.EQ.'MIXED').OR.(COORD.EQ.'BAKER')) CLOSE(IOCART)
155
  DEALLOCATE(GeomTmpC,GeomTmp)
156

    
157
  if (debug) Call Header('Exiting Write_PATH')
158
END SUBROUTINE Write_path