Statistiques
| Révision :

root / src / Space_GEDIIS.f90

Historique | Voir | Annoter | Télécharger (3,89 ko)

1
      ! SPACE_GEDIIS SIMPLY LOADS THE CURRENT VALUES OF Geom AND Grad INTO
2
      ! THE ARRAYS GeomSet AND GradSet
3

    
4
      SUBROUTINE SPACE_GEDIIS(MRESET,MSET,Geom,Grad,HEAT,NCoord,GeomSet,GradSet,ESET,FRST)
5

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

    
42
      IMPLICIT NONE
43
      integer, parameter :: KINT = kind(1)
44
      integer, parameter :: KREAL = kind(1.0d0)
45

    
46
      ! MSET=mth iteration, MRESET=Maximum no. of iterations. 
47
      INTEGER(KINT) :: NCoord, MRESET, MSET 
48
      ! Geom=geometry with NCoord coordinates. GRAD=gradients.
49
    REAL(KREAL), INTENT(IN) :: Geom(NCoord)
50
      REAL(KREAL) :: Grad(NCoord)
51
    REAL(KREAL) :: Heat
52
      LOGICAL :: FRST, Print=.TRUE.
53
      ! GeomSet, GradSet : a long array to store
54
      REAL(KREAL) :: GeomSet(MRESET*NCoord), GradSet(MRESET*NCoord), ESET(MRESET)
55
      ! Geom and GRAD for all iterations.
56

    
57
      INTEGER(KINT) :: I, K, NMK, MI, NI
58
      INTEGER(KINT), SAVE :: NRESET
59

    
60
      ! UPDATE PARAMETER AND GRADIENT SUBSPACE:
61
      IF (PRINT)  WRITE(*,'(/,''       BEGIN SPACE_GEDIIS  '')')
62
      IF(FRST)THEN
63
         NRESET=MIN(NCoord/2,MRESET)
64
             IF (NCoord .LT. 5 ) THEN ! This condition is imposed for small NCoord,
65
               ! particularly if NCoord is equal to 2 or 3.
66
                NRESET = NCoord-1
67
             END IF
68
         FRST=.FALSE.
69
         MSET=0
70
      ENDIF
71

    
72
      ! IF (PRINT)  WRITE(*,'(/,''       SPACE_GEDIIS 1  '')')
73
      ! purging the very first Geom and GRAD.
74
      if (print) WRITE(*,*) "DBG SPACE_GEDIIS MSET, NRESET", MSET,NRESET
75
      IF (MSET .EQ. NRESET) THEN
76
         DO I=1,MSET-1
77
            MI = NCoord*(I-1)
78
            NI = NCoord*I
79
            ESET(I)=ESET(I+1)
80
            DO K=1,NCoord
81
               GeomSet(MI+K) = GeomSet(NI+K)
82
               GradSet(MI+K) = GradSet(NI+K)
83
            END DO
84
     END DO  
85
            MSET=NRESET-1
86
      ENDIF
87

    
88
      ! STORE THE CURRENT POINT:
89
      !IF (PRINT)  WRITE(*,'(/,''       SPACE_GEDIIS 2  '')')
90
      DO  K=1,NCoord
91
         NMK = NCoord*MSET+K ! MSET corresponds mth iteration.
92
         !IF (PRINT)  WRITE(*,*) 'K,NMK,MSET,NCoord',K,NMK,MSET,NCoord !, &
93
             !SIZE(GeomSet), SIZE(GradSet),SIZE(Geom),SIZE(GRAD)
94
         GeomSet(NMK) = Geom(K)
95
         GradSet(NMK) = Grad(K)
96
      END DO
97
    
98
      MSET=MSET+1
99
      ESET(MSET)=HEAT
100
     
101
      IF (PRINT) WRITE (*,*) "MSET=", MSET
102
      IF (PRINT)  WRITE(*,'(/,''       END SPACE_GEDIIS   '')')
103

    
104
      END SUBROUTINE SPACE_GEDIIS