Statistiques
| Révision :

root / src / Space_all.f90 @ 12

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

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