Statistiques
| Révision :

root / src / ReadInput_mopac.f90

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

1
 SUBROUTINE ReadInput_Mopac
2

    
3
! This routine reads an input template for MOPAC
4

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

    
36
  use VarTypes
37
  use Path_module
38
  use Io_module
39

    
40
  IMPLICIT NONE
41

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

    
48
    SUBROUTINE die(routine, msg, file, line, unit)
49

    
50
      Use VarTypes
51
      Use io_module
52

    
53
      implicit none
54
      character(len=*), intent(in)           :: routine, msg
55
      character(len=*), intent(in), optional :: file
56
      integer(KINT), intent(in), optional      :: line, unit
57

    
58
    END SUBROUTINE die
59

    
60

    
61
  END INTERFACE
62

    
63

    
64
  CHARACTER(LCHARS) ::  Line,LineUp
65
  INTEGER(KINT) :: LineL, Idx, NTmp
66
  INTEGER(KINT) :: NatMopac
67
  REAL(KREAL) :: Lat(3,3)
68
  
69
  LOGICAL :: Debug
70

    
71

    
72
  Debug=Valid("readinput").OR.Valid("readinput_mopac")
73

    
74
  if (debug) Call Header("Entering ReadInput_mopac")
75

    
76
! The structure is:
77
! A MOPAC data set normally consists of one line of keywords, two lines of user-defined text, then the coordinates
78
! Then  a blank line or a line of 0.
79
! then the symmetry description.
80
! comment lines start with * and can be anywhere !!!
81

    
82
  ! First, the root
83
  IF (DEBUG) WRITE(*,*) "Reading Mopac input"
84
  ALLOCATE(Mopac_Root)
85
  NULLIFY(Mopac_Root%next)
86
  ALLOCATE(Mopac_Comment)
87
  NULLIFY(Mopac_Comment%next)
88
  ALLOCATE(Mopac_End)
89
  NuLLIFY(Mopac_End%Next)
90
  Current => Mopac_root
91
  CurCom => Mopac_Comment
92
  LineL=1
93
  NTmp=0
94
  DO WHILE (NTmp.LT.3)
95
     READ(IOIN,'(A)') Line
96
     Line=AdjustL(Line)
97
     LineL=len(Trim(Line))
98
     IF (Line(1:1)/="*") THEN
99
        IF (NTmp==0) THEN
100
           LineUp=Line
101
           Call UpCase(LineUp)
102
           Idx=Index(LineUp,'GRADIENTS')
103
           If (Idx==0) Line=TRIM(Line) // " GRADIENTS"
104
           Idx=Index(LineUp,'1SCF')
105
           If (Idx==0) Line=TRIM(Line) // " 1SCF"
106
        END IF
107
        current%Line=TRIM(Line)
108
        ALLOCATE(current%next)
109
        Current => Current%next
110
        Nullify(Current%next)
111
        NTmp=NTmp+1
112
     ELSE
113
        CurCom%Line=TRIM(LINE)
114
        ALLOCATE(CurCom%Next)
115
        CurCom => CurCom%Next
116
        NULLIFY(CurCom%Next)
117
     END IF
118
  END DO
119

    
120
!     Current => Mopac_root
121
!     DO WHILE (ASSOCIATED(Current%next))
122
!        WRITE(*,'(1X,A)') Trim(current%line)
123
!        Current => current%next
124
!     END DO
125

    
126
! Now the geometry... that we just skip :)
127
! PFL 2013 Apr 
128
! We take care that there is no Translation vectors...
129
! We also check that the number of atoms is ok
130
  IF (DEBUG) WRITE(*,*) "Reading Mopac Geometry"
131
  Mopac_EndGeom=""
132
  LineL=1
133
  NatMopac=0
134
  Lat=0.d0
135
  IPer=0
136
  FPBC=.FALSE.
137
  DO WHILE (LineL.NE.0)
138
     READ(IOIN,'(A)',END=989) Line
139
     Line=AdjustL(Line)
140
     LineL=len(Trim(Line))
141
     ! The last line might be either blank or filled with 0
142
     If (LineL>0) THEN
143
        SELECT CASE (Line(1:1))
144
          CASE ("0") 
145
             LineL=0
146
             Mopac_EndGeom=Trim(Line)
147
          CASE("*") 
148
             CurCom%Line=TRIM(LINE)
149
             ALLOCATE(CurCom%Next)
150
             CurCom => CurCom%Next
151
             NULLIFY(CurCom%Next)
152
          CASE DEFAULT
153
             LineUp=Line
154
             Call UpCase(LineUp)
155
             If (LineUp(1:2)=="TV") THEN
156
                FPBC=.TRUE.
157
                IPer=IPer+1
158
                If (Iper>3) THEN
159
                   Call Die("ReadInput Mopac","Iper>3",Unit=IOOUT)
160
                END IF
161
                NTmp=Index(LineUp," ")
162
                LineUp=LineUp(NTmp:)
163
                Read(LineUp,*) Lat(IPer,1:3)
164
             ELSE
165
                NatMopac=NatMopac+1
166
             END IF
167
         END SELECT
168
      END IF
169
     
170
   END DO
171

    
172
!  WRITE(*,*) "NatMopac,Nat:",NAtMopac,Nat
173
  IF (NatMopac/=Nat) Call Die("ReadInput_mopac","Nat read does not mat nat",Unit=IOOUT)
174
  IF (FPBC) THEN
175
     Lat_a(1:3)=Lat(1,1:3)
176
     Lat_b(1:3)=Lat(2,1:3)
177
     Lat_c(1:3)=Lat(3,1:3)
178
     If (IPer>=1) THEN
179
        kaBeg=-1
180
        kaEnd=1
181
     END IF
182
     If (IPer>=2) THEN
183
        kbBeg=-1
184
        kbEnd=1
185
     END IF
186
     If (IPer==3) THEN
187
        kcBeg=-1
188
        kcEnd=1
189
     END IF
190
     If (IPer>3) THEN
191
        Call Die("Readinput_mopac","Found too many Tv lines !",Unit=IOOUT)
192
     END IF
193
  END IF
194

    
195
! If we are here, there might be something else to read: Mopac_end
196

    
197
  ! We now read the last part
198
  IF (DEBUG) WRITE(*,*) "Reading Mopac End"
199
  !     READ(IOIN,'(A)') Line
200
  Current => Mopac_End
201
  LineL=1
202
  DO WHILE (1.EQ.1)
203
     READ(IOIN,'(A)',END=989) Line
204
     Line=AdjustL(Line)
205
     LineL=len(Trim(Line))
206
     IF (Line(1:1)/="*") THEN
207
        current%Line=TRIM(Line)
208
        ALLOCATE(current%next)
209
        Current => Current%next
210
        Nullify(Current%next)
211
        NTmp=NTmp+1
212
     ELSE
213
        CurCom%Line=TRIM(LINE)
214
        ALLOCATE(CurCom%Next)
215
        CurCom => CurCom%Next
216
        NULLIFY(CurCom%Next)
217
        END IF
218
     END DO
219
989  CONTINUE
220

    
221
  if (debug) Call Header("Exiting ReadInput_mopac")
222

    
223
END SUBROUTINE READINPUT_Mopac