Statistiques
| Révision :

root / src / Space_all.f90 @ 2

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

1
!C
2
!C  SPACE SIMPLY LOADS THE CURRENT VALUES OF Geom AND GRAD INTO
3
!C  THE ARRAYS GeomSet AND GradSet
4
!C
5
      SUBROUTINE Space_all(NGeomF,IGeom,MRESET,MSET,Geom,GRAD,HEAT,NCoord,GeomSet,GradSet,ESET,FRST)
6

    
7
!      IMPLICIT DOUBLE PRECISION (A-H,O-Z)
8
!      INCLUDE 'SIZES'
9
	  
10
      IMPLICIT NONE
11
      integer, parameter :: KINT = kind(1)
12
      integer, parameter :: KREAL = kind(1.0d0)
13

    
14
!      INCLUDE 'SIZES'
15

    
16
 !MSET=mth iteration, MRESET=Maximum no. of iterations. 
17
      INTEGER(KINT) :: NCoord,MRESET,MSET(NGeomF),NGeomF,IGeom
18
 !Geom=geometry with NCoord coordinates. GRAD=gradients.
19
      REAL(KREAL) :: Geom(NCoord),GRAD(NCoord)
20
      REAL(KREAL) :: Heat
21
      LOGICAL :: FRST(NGeomF), Print=.FALSE.
22
 ! GeomSet, GradSet : a long array to store
23
      REAL(KREAL) :: GeomSet(NGeomF,MRESET*NCoord),GradSet(NGeomF,MRESET*NCoord), ESET(MRESET)
24
        ! Geom and GRAD for all iterations.
25

    
26
      INTEGER(KINT) :: I,J,K,NMK,MI,NI
27
      INTEGER(KINT), SAVE :: NRESET
28
!C
29
!C     UPDATE PARAMETER AND GRADIENT SUBSPACE
30
!C
31
      IF (PRINT)  WRITE(*,'(/,''       BEGIN SPACE  '')')
32
      IF(FRST(IGeom))THEN
33
         NRESET=MIN(NCoord/2,MRESET)
34
         IF(NCoord .LT. 5 ) THEN ! This condition is imposed for small NCoord,
35
           ! particularly if NCoord is equal to 2 or 3.
36
           NRESET = NCoord-1
37
         ENDIF
38
         FRST(IGeom)=.FALSE.
39
         MSET(IGeom)=0
40
      ENDIF
41
!C
42
      !IF (PRINT)  WRITE(*,'(/,''       SPACE 1  '')')
43
        ! purging the very first Geom and GRAD.
44
       if (print) WRITE(*,*) "DBG Space MSET(",IGeom,"), NRESET",MSET(IGeom),NRESET
45
       IF (MSET(IGeom) .EQ. NRESET) THEN
46
         DO 10 I=1,MSET(IGeom)-1
47
            MI = NCoord*(I-1)
48
            NI = NCoord*I
49
            ESET(I)=ESET(I+1)
50
            DO 10 K=1,NCoord
51
               GeomSet(IGeom,MI+K) = GeomSet(IGeom,NI+K)
52
   10    GradSet(IGeom,MI+K) = GradSet(IGeom,NI+K)
53
            MSET(IGeom)=NRESET-1
54
       ENDIF
55
!C
56
!C     STORE THE CURRENT POINT
57
!C
58
      !IF (PRINT)  WRITE(*,'(/,''       SPACE 2  '')')
59
      DO  K=1,NCoord
60
         NMK = NCoord*MSET(IGeom)+K ! MSET(IGeom) corresponds the mth iteration.
61
         IF (PRINT)  WRITE(*,*) 'K,NMK,MSET(',IGeom,'),NCoord',K,NMK,MSET(IGeom),NCoord, &
62
                     SIZE(GeomSet(IGeom,:)), SIZE(GradSet(IGeom,:)),SIZE(Geom),SIZE(GRAD)
63
         GeomSet(IGeom,NMK) = Geom(K)
64
         GradSet(IGeom,NMK) = Grad(K)
65
      END DO
66
      MSET(IGeom)=MSET(IGeom)+1
67
      ESET(MSET(IGeom))=HEAT
68

    
69
      IF (PRINT) WRITE (*,*) "MSET(",IGeom,")=", MSET(IGeom)
70
      IF (PRINT)  WRITE(*,'(/,''       END SPACE   '')')
71
	  
72
      END SUBROUTINE Space_all