Statistiques
| Révision :

root / src / Space_all.f90

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

1
      SUBROUTINE Space_all(NGeomF,IGeom,MRESET,MSET,Geom,GRAD,HEAT,NCoord,GeomSet,GradSet,ESET,FRST)
2

    
3
!C
4
!C  SPACE SIMPLY LOADS THE CURRENT VALUES OF Geom AND GRAD INTO
5
!C  THE ARRAYS GeomSet AND GradSet
6
!C
7

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

    
48
!      INCLUDE 'SIZES'
49

    
50
 !MSET=mth iteration, MRESET=Maximum no. of iterations. 
51
      INTEGER(KINT) :: NCoord,MRESET,NGeomF,IGeom
52
      INTEGER(KINT) :: MSET(NGeomF)
53
 !Geom=geometry with NCoord coordinates. GRAD=gradients.
54
      REAL(KREAL) :: Geom(NCoord),GRAD(NCoord)
55
      REAL(KREAL) :: Heat
56
      LOGICAL :: FRST(NGeomF), Print=.FALSE.
57
 ! GeomSet, GradSet : a long array to store
58
      REAL(KREAL) :: GeomSet(NGeomF,MRESET*NCoord),GradSet(NGeomF,MRESET*NCoord), ESET(MRESET)
59
        ! Geom and GRAD for all iterations.
60

    
61
      INTEGER(KINT) :: I, K, NMK, MI, NI
62
      INTEGER(KINT), SAVE :: NRESET
63
!C
64
!C     UPDATE PARAMETER AND GRADIENT SUBSPACE
65
!C
66
      IF (PRINT)  WRITE(*,'(/,''       BEGIN SPACE  '')')
67
      IF(FRST(IGeom))THEN
68
         NRESET=MIN(NCoord/2,MRESET)
69
         IF(NCoord .LT. 5 ) THEN ! This condition is imposed for small NCoord,
70
           ! particularly if NCoord is equal to 2 or 3.
71
           NRESET = NCoord-1
72
         ENDIF
73
         FRST(IGeom)=.FALSE.
74
         MSET(IGeom)=0
75
      ENDIF
76
!C
77
      !IF (PRINT)  WRITE(*,'(/,''       SPACE 1  '')')
78
        ! purging the very first Geom and GRAD.
79
       if (print) WRITE(*,*) "DBG Space MSET(",IGeom,"), NRESET",MSET(IGeom),NRESET
80
       IF (MSET(IGeom) .EQ. NRESET) THEN
81
         DO 10 I=1,MSET(IGeom)-1
82
            MI = NCoord*(I-1)
83
            NI = NCoord*I
84
            ESET(I)=ESET(I+1)
85
            DO 10 K=1,NCoord
86
               GeomSet(IGeom,MI+K) = GeomSet(IGeom,NI+K)
87
   10    GradSet(IGeom,MI+K) = GradSet(IGeom,NI+K)
88
            MSET(IGeom)=NRESET-1
89
       ENDIF
90
!C
91
!C     STORE THE CURRENT POINT
92
!C
93
      !IF (PRINT)  WRITE(*,'(/,''       SPACE 2  '')')
94
      DO  K=1,NCoord
95
         NMK = NCoord*MSET(IGeom)+K ! MSET(IGeom) corresponds the mth iteration.
96
         IF (PRINT)  WRITE(*,*) 'K,NMK,MSET(',IGeom,'),NCoord',K,NMK,MSET(IGeom),NCoord, &
97
                     SIZE(GeomSet(IGeom,:)), SIZE(GradSet(IGeom,:)),SIZE(Geom),SIZE(GRAD)
98
         GeomSet(IGeom,NMK) = Geom(K)
99
         GradSet(IGeom,NMK) = Grad(K)
100
      END DO
101
      MSET(IGeom)=MSET(IGeom)+1
102
      ESET(MSET(IGeom))=HEAT
103

    
104
      IF (PRINT) WRITE (*,*) "MSET(",IGeom,")=", MSET(IGeom)
105
      IF (PRINT)  WRITE(*,'(/,''       END SPACE   '')')
106
    
107
      END SUBROUTINE Space_all