Statistiques
| Révision :

root / src / Space_all.f90 @ 9

Historique | Voir | Annoter | Télécharger (2,56 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,NGeomF,IGeom
18
      INTEGER(KINT) :: MSET(NGeomF)
19
 !Geom=geometry with NCoord coordinates. GRAD=gradients.
20
      REAL(KREAL) :: Geom(NCoord),GRAD(NCoord)
21
      REAL(KREAL) :: Heat
22
      LOGICAL :: FRST(NGeomF), Print=.FALSE.
23
 ! GeomSet, GradSet : a long array to store
24
      REAL(KREAL) :: GeomSet(NGeomF,MRESET*NCoord),GradSet(NGeomF,MRESET*NCoord), ESET(MRESET)
25
        ! Geom and GRAD for all iterations.
26

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

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