Statistiques
| Révision :

root / src / Space_GEDIIS_all.f90

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

1 1 pfleura2
      ! SPACE_GEDIIS SIMPLY LOADS THE CURRENT VALUES OF Geom AND Grad INTO THE ARRAYS GeomSet AND GradSet
2 1 pfleura2
3 1 pfleura2
      SUBROUTINE SPACE_GEDIIS_All(NGeomF,IGeom,MRESET,MSET,Geom,Grad,HEAT,NCoord,GeomSet,GradSet,ESET,FRST)
4 1 pfleura2
5 12 pfleura2
!----------------------------------------------------------------------
6 12 pfleura2
! This routine was adapted from the public domain mopac6 diis.f
7 12 pfleura2
!  source file (c) 2009, Stewart Computational Chemistry.
8 12 pfleura2
!  <http://www.openmopac.net/Downloads/Downloads.html>
9 12 pfleura2
!
10 12 pfleura2
!----------------------------------------------------------------------
11 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
12 12 pfleura2
!  Centre National de la Recherche Scientifique,
13 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
14 12 pfleura2
!
15 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
16 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
17 12 pfleura2
!
18 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
19 12 pfleura2
!  Contact: optnpath@gmail.com
20 12 pfleura2
!
21 12 pfleura2
! This file is part of "Opt'n Path".
22 12 pfleura2
!
23 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
24 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
25 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
26 12 pfleura2
!  or (at your option) any later version.
27 12 pfleura2
!
28 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
29 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
30 12 pfleura2
!
31 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
32 12 pfleura2
!  GNU Affero General Public License for more details.
33 12 pfleura2
!
34 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
35 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
36 12 pfleura2
!
37 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
38 12 pfleura2
! for commercial licensing opportunities.
39 12 pfleura2
!----------------------------------------------------------------------
40 12 pfleura2
41 1 pfleura2
      IMPLICIT NONE
42 1 pfleura2
      integer, parameter :: KINT = kind(1)
43 1 pfleura2
      integer, parameter :: KREAL = kind(1.0d0)
44 1 pfleura2
45 1 pfleura2
      ! MSET=mth iteration, MRESET=Maximum no. of iterations.
46 1 pfleura2
      INTEGER(KINT) :: NGeomF,  IGeom
47 1 pfleura2
      INTEGER(KINT) :: NCoord, MRESET, MSET(NGeomF)
48 1 pfleura2
      ! Geom=geometry with NCoord coordinates. GRAD=gradients.
49 1 pfleura2
      REAL(KREAL) :: Geom(NCoord), Grad(NCoord)
50 1 pfleura2
    REAL(KREAL) :: Heat
51 1 pfleura2
      LOGICAL :: FRST(NGeomF), Print=.FALSE.
52 1 pfleura2
      ! GeomSet, GradSet : a long array to store.
53 1 pfleura2
      REAL(KREAL) :: GeomSet(NGeomF,MRESET*NCoord), GradSet(NGeomF,MRESET*NCoord), ESET(NGeomF,MRESET)
54 1 pfleura2
      ! Geom and GRAD for all iterations.
55 1 pfleura2
56 2 pfleura2
      INTEGER(KINT) :: I, K, NMK, MI, NI
57 1 pfleura2
      INTEGER(KINT), SAVE :: NRESET
58 1 pfleura2
59 1 pfleura2
      ! UPDATE PARAMETER AND GRADIENT SUBSPACE:
60 1 pfleura2
      IF (PRINT)  WRITE(*,'(/,''       BEGIN SPACE_GEDIIS_ALL   '')')
61 1 pfleura2
    IF(FRST(IGeom))THEN
62 1 pfleura2
      ! Print *, 'Inside FRST(',IGeom,')=', FRST(IGeom)
63 1 pfleura2
         NRESET=MIN(NCoord/2,MRESET)
64 1 pfleura2
             IF (NCoord .LT. 5 ) THEN ! This condition is imposed for small NCoord,
65 1 pfleura2
               ! particularly if NCoord is equal to 2 or 3.
66 1 pfleura2
                NRESET = NCoord-1
67 1 pfleura2
             END IF
68 1 pfleura2
         FRST(IGeom)=.FALSE.
69 1 pfleura2
         MSET(IGeom)=0
70 1 pfleura2
      ENDIF
71 1 pfleura2
72 1 pfleura2
      IF (PRINT)  WRITE(*,'(/,''       SPACE_GEDIIS_ALL 1  '')')
73 1 pfleura2
      ! purging the very first Geom and GRAD.
74 1 pfleura2
      if (print) WRITE(*,*) "DBG SPACE_GEDIIS MSET, NRESET", MSET,NRESET
75 1 pfleura2
      IF (MSET(IGeom) .EQ. NRESET) THEN
76 1 pfleura2
         DO I=1,MSET(IGeom)-1
77 1 pfleura2
            MI = NCoord*(I-1)
78 1 pfleura2
            NI = NCoord*I
79 1 pfleura2
            ESET(IGeom,I)=ESET(IGeom,I+1)
80 1 pfleura2
            DO K=1,NCoord
81 1 pfleura2
               GeomSet(IGeom,MI+K) = GeomSet(IGeom,NI+K)
82 1 pfleura2
               GradSet(IGeom,MI+K) = GradSet(IGeom,NI+K)
83 1 pfleura2
            END DO
84 1 pfleura2
     END DO
85 1 pfleura2
            MSET(IGeom)=NRESET-1
86 1 pfleura2
      ENDIF
87 1 pfleura2
88 1 pfleura2
      ! STORE THE CURRENT POINT:
89 1 pfleura2
    IF (PRINT)  WRITE(*,'(/,''       SPACE_GEDIIS_ALL  2  '')')
90 1 pfleura2
      DO  K=1,NCoord
91 1 pfleura2
         NMK = NCoord*MSET(IGeom)+K ! MSET(IGeom) corresponds the mth iteration.
92 1 pfleura2
         IF (PRINT)  WRITE(*,*) 'K,NMK,MSET(',IGeom,'),NCoord',K,NMK,MSET(IGeom),NCoord !, &
93 1 pfleura2
          !   SIZE(GeomSet(IGeom,:)), SIZE(GradSet(IGeom,:)),SIZE(Geom),SIZE(GRAD)
94 1 pfleura2
         GeomSet(IGeom,NMK) = Geom(K)
95 1 pfleura2
         GradSet(IGeom,NMK) = Grad(K)
96 1 pfleura2
      END DO
97 1 pfleura2
98 1 pfleura2
      MSET(IGeom)=MSET(IGeom)+1
99 1 pfleura2
      ESET(IGeom,MSET(IGeom))=HEAT
100 1 pfleura2
101 1 pfleura2
      IF (PRINT) WRITE (*,*) "MSET(",IGeom,")=", MSET(IGeom)
102 1 pfleura2
      IF (PRINT)  WRITE(*,'(/,''       END SPACE_GEDIIS_ALL    '')')
103 1 pfleura2
104 1 pfleura2
      END SUBROUTINE SPACE_GEDIIS_All