Statistiques
| Révision :

root / src / Hupdate_all.f90 @ 2

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

1
 subroutine hupdate_all(n, ds, dgrad, Hess)
2

    
3
  use Path_module, only :  hesupd,Hinv
4
  use Io_module, only : IoOut
5

    
6
  IMPLICIT NONE
7

    
8
  INTEGER, PARAMETER :: KINT=KIND(1)
9
  INTEGER, PARAMETER :: KREAL=KIND(1.0D0)
10

    
11
  INTEGER(KINT), INTENT(IN) :: n
12
  real(KREAL), INTENT(IN) :: ds(n), dgrad(n)
13
  REAL(KREAL),INTENT(INOUT) :: Hess(n:n)
14

    
15
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
16
!
17
! This subroutine is a drive for the update of the Hessian 
18
! in the Quasi-Newton optimization step.
19
! We propose mostly update of the inverse Hessian.
20
!
21
! input:
22
!  - n: number of coordinates
23
!  - ds: GeomOld-Geom (expressed in the optimization coord.)
24
!  - dgrad: GradOld-Grad  (expressed in the optimization coord.)
25
!
26
!  input/output:
27
!  - Hess: old Hessian in input, replaced by updated Hessian on output
28
!
29
!!!!!!!!!!!!!!!!
30
!
31
! For now, we propose :
32
! - For update of inverser Hessian:
33
!      - BFGS
34
!
35
! - For update of hessian:
36
!      - Bofill (combination of Murtagh-Sargent and Powell-symmetric-Broyden
37
!      - Murtagh-Sargent
38
!
39
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
40

    
41

    
42

    
43
  interface
44
     function valid(string) result (isValid)
45
       logical                  :: isValid
46
       character(*), intent(in) :: string
47
     end function valid
48

    
49
  end interface
50

    
51
  ! ======================================================================
52
  LOGICAL :: Debug
53

    
54
  ! ======================================================================
55

    
56
  debug = valid ('DEBUG HESS') .OR. Valid('DEBUG HUPDATE')
57

    
58
  if (debug) WRITE(*,*) "================================= Entering Hupdate_all ==============="
59

    
60
  SELECT CASE (Hinv)
61
     CASE (.TRUE.)
62
        SELECT CASE (HesUpd)
63
           CASE ("BFGS")
64
              Call Hinvup_BFGS(n,ds,dgrad,hess)
65
           CASE DEFAULT
66
              WRITE(*,*) Trim(HesUpd) // " not known: using BFGS"
67
              Call Hinvup_BFGS(n,ds,dgrad,hess)
68
         END SELECT
69
     CASE (.FALSE.)
70
        SELECT CASE (HesUpd)
71
           CASE ("BOFILL")
72
              Call Hupdate_Bofill(n,ds,dgrad,hess)
73
           CASE ("MS")
74
              Call Hupdate_MS(n,ds,dgrad,hess)
75
           CASE DEFAULT
76
              WRITE(*,*) Trim(HesUpd) // " not known: using Bofill"
77
              Call Hupdate_Bofill(n,ds,dgrad,hess)
78
           END SELECT
79
    END SELECT
80

    
81
end subroutine hupdate_all