Statistiques
| Révision :

root / src / Space.f90 @ 12

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

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