Statistiques
| Révision :

root / src / Space_GEDIIS_all.f90 @ 2

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

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

    
3
      SUBROUTINE SPACE_GEDIIS_All(NGeomF,IGeom,MRESET,MSET,Geom,Grad,HEAT,NCoord,GeomSet,GradSet,ESET,FRST)
4

    
5
      IMPLICIT NONE
6
      integer, parameter :: KINT = kind(1)
7
      integer, parameter :: KREAL = kind(1.0d0)
8

    
9
      ! MSET=mth iteration, MRESET=Maximum no. of iterations. 
10
      INTEGER(KINT) :: NCoord, MRESET, MSET(NGeomF), NGeomF, IGeom 
11
      ! Geom=geometry with NCoord coordinates. GRAD=gradients.
12
      REAL(KREAL) :: Geom(NCoord), Grad(NCoord)
13
	  REAL(KREAL) :: Heat
14
      LOGICAL :: FRST(NGeomF), Print=.FALSE.
15
      ! GeomSet, GradSet : a long array to store.
16
      REAL(KREAL) :: GeomSet(NGeomF,MRESET*NCoord), GradSet(NGeomF,MRESET*NCoord), ESET(NGeomF,MRESET)
17
      ! Geom and GRAD for all iterations.
18

    
19
      INTEGER(KINT) :: I,J,K,NMK,MI,NI
20
      INTEGER(KINT), SAVE :: NRESET
21

    
22
      ! UPDATE PARAMETER AND GRADIENT SUBSPACE:
23
      IF (PRINT)  WRITE(*,'(/,''       BEGIN SPACE_GEDIIS_ALL   '')')
24
	  IF(FRST(IGeom))THEN
25
	    ! Print *, 'Inside FRST(',IGeom,')=', FRST(IGeom)
26
         NRESET=MIN(NCoord/2,MRESET)
27
             IF (NCoord .LT. 5 ) THEN ! This condition is imposed for small NCoord,
28
               ! particularly if NCoord is equal to 2 or 3.
29
                NRESET = NCoord-1
30
             END IF
31
         FRST(IGeom)=.FALSE.
32
         MSET(IGeom)=0
33
      ENDIF
34

    
35
      IF (PRINT)  WRITE(*,'(/,''       SPACE_GEDIIS_ALL 1  '')')
36
      ! purging the very first Geom and GRAD.
37
      if (print) WRITE(*,*) "DBG SPACE_GEDIIS MSET, NRESET", MSET,NRESET
38
      IF (MSET(IGeom) .EQ. NRESET) THEN
39
         DO I=1,MSET(IGeom)-1
40
            MI = NCoord*(I-1)
41
            NI = NCoord*I
42
            ESET(IGeom,I)=ESET(IGeom,I+1)
43
            DO K=1,NCoord
44
               GeomSet(IGeom,MI+K) = GeomSet(IGeom,NI+K)
45
               GradSet(IGeom,MI+K) = GradSet(IGeom,NI+K)
46
            END DO
47
		 END DO	
48
            MSET(IGeom)=NRESET-1
49
      ENDIF
50

    
51
      ! STORE THE CURRENT POINT:
52
	  IF (PRINT)  WRITE(*,'(/,''       SPACE_GEDIIS_ALL  2  '')')
53
      DO  K=1,NCoord
54
         NMK = NCoord*MSET(IGeom)+K ! MSET(IGeom) corresponds the mth iteration.
55
         IF (PRINT)  WRITE(*,*) 'K,NMK,MSET(',IGeom,'),NCoord',K,NMK,MSET(IGeom),NCoord !, &
56
          !   SIZE(GeomSet(IGeom,:)), SIZE(GradSet(IGeom,:)),SIZE(Geom),SIZE(GRAD)
57
         GeomSet(IGeom,NMK) = Geom(K)
58
         GradSet(IGeom,NMK) = Grad(K)
59
      END DO
60
	  
61
      MSET(IGeom)=MSET(IGeom)+1
62
      ESET(IGeom,MSET(IGeom))=HEAT
63
	   
64
      IF (PRINT) WRITE (*,*) "MSET(",IGeom,")=", MSET(IGeom)
65
      IF (PRINT)  WRITE(*,'(/,''       END SPACE_GEDIIS_ALL    '')')
66

    
67
      END SUBROUTINE SPACE_GEDIIS_All