Statistiques
| Révision :

root / src / Hupdate_all.f90 @ 5

Historique | Voir | Annoter | Télécharger (3,47 ko)

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

    
3
  use Path_module, only :  HUpdate,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 driver 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 inverse Hessian:
33
!      - BFGS (Broyden, Fletcher, Goldfarb, and Shanno)
34
!      - DFP (Davidson - Fletcher - Powell )
35
!      - MS (Murtagh-Sargent)
36
!
37
! - For update of hessian:
38
!      - Bofill (combination of Murtagh-Sargent and Powell-symmetric-Broyden
39
!      - MS (Murtagh-Sargent)
40
!      - BFGS
41
!      - DFP
42
!----------------------------------------------------
43
! We use the fact that some formula are the dual of other
44
! that is, one can convert the formula for update of the Hessian 
45
! into the update of the inverse Hessian by replacing the Hessian
46
! (denoted by B in the Fletcher book and in the Nocedal&Wrigth book)
47
! by the inverse hessian (denoted by H), and replacing ds by dgrad in the
48
! formula.
49
! See for example:
50
! 1) Numerical Optimization, Springer 2nd Ed., 2006
51
! by Jorge Nocedal & Stephen J. Wright
52
! 2) ractical Methods of Optimization, John Wiley & Sons, second ed., 1987.
53
! by R. Fletcher
54
!
55
!
56
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
57

    
58

    
59

    
60
  interface
61
     function valid(string) result (isValid)
62
       logical                  :: isValid
63
       character(*), intent(in) :: string
64
     end function valid
65

    
66
  end interface
67

    
68
  ! ======================================================================
69
  LOGICAL :: Debug
70

    
71
  ! ======================================================================
72

    
73
  debug = valid ('HESS') .OR. Valid('HUPDATE')
74

    
75
  if (debug) WRITE(*,*) "================================= Entering Hupdate_all ==============="
76

    
77
  SELECT CASE (Hinv)
78
     CASE (.TRUE.)
79
        SELECT CASE (HUpdate)
80
           CASE ("BFGS")
81
              Call Hinvup_BFGS(n,ds,dgrad,hess)
82
           CASE ("MS")
83
! we use the fact that MS is self-dual 
84
              Call Hupdate_MS(n,dgrad,ds,hess)
85
           CASE ("DFP")
86
              Call Hinvup_DFP(n,ds,dgrad,hess)
87
           CASE DEFAULT
88
              WRITE(*,*) Trim(HUpdate) // " not known: using BFGS"
89
              Call Hinvup_BFGS(n,ds,dgrad,hess)
90
         END SELECT
91
     CASE (.FALSE.)
92
        SELECT CASE (HUpdate)
93
           CASE ("BOFILL")
94
              Call Hupdate_Bofill(n,ds,dgrad,hess)
95
           CASE ("MS")
96
              Call Hupdate_MS(n,ds,dgrad,hess)
97
           CASE ("DFP")
98
! we use the fact that DFP is the dual of BFGS
99
              Call Hinvup_BFGS(n,dgrad,ds,hess)
100
           CASE ("BFGS")
101
! we use the fact that DFP is the dual of BFGS
102
              Call Hinvup_DFP(n,dgrad,ds,hess)
103
           CASE DEFAULT
104
              WRITE(*,*) Trim(HUpdate) // " not known: using Bofill"
105
              Call Hupdate_Bofill(n,ds,dgrad,hess)
106
           END SELECT
107
    END SELECT
108

    
109
  if (debug) WRITE(*,*) "================================= Exiting Hupdate_all ==============="
110
end subroutine hupdate_all