Statistiques
| Révision :

root / src / Space_GEDIIS.f90 @ 2

Historique | Voir | Annoter | Télécharger (2,33 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
      IMPLICIT NONE
7
      integer, parameter :: KINT = kind(1)
8
      integer, parameter :: KREAL = kind(1.0d0)
9

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

    
21
      INTEGER(KINT) :: I,J,K,NMK,MI,NI
22
      INTEGER(KINT), SAVE :: NRESET
23

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

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

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

    
68
      END SUBROUTINE SPACE_GEDIIS