/[MITgcm]/MITgcm_contrib/ecco_utils/lbfgs_jpl_version/optim.2/optim_sub.F
ViewVC logotype

Annotation of /MITgcm_contrib/ecco_utils/lbfgs_jpl_version/optim.2/optim_sub.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.1 - (hide annotations) (download)
Wed Apr 3 23:36:08 2013 UTC (12 years, 4 months ago) by heimbach
Branch: MAIN
CVS Tags: HEAD
Add L-BFGS code adapted to ECCO Production by JPL

1 heimbach 1.1
2    
3     subroutine optim_sub(
4     I nn
5     & )
6    
7     c ==================================================================
8     c SUBROUTINE optim_sub
9     c ==================================================================
10     c
11     c o Initialization of optimization run.
12     c
13     c started: Christian Eckert eckert@mit.edu 15-Feb-2000
14     c
15     c changed: Christian Eckert eckert@mit.edu 10-Mar-2000
16     c
17     c - Added ECCO layout.
18     c
19     c changed: Patrick Heimbach heimbach@mit.edu 19-Jun-2000
20     c - finished, revised and debugged
21     c
22     c ==================================================================
23     c SUBROUTINE optim_sub
24     c ==================================================================
25    
26     implicit none
27    
28     c == global variables ==
29    
30     #include "EEPARAMS.h"
31     #include "SIZE.h"
32    
33     #include "ctrl.h"
34     #include "optim.h"
35    
36     c == routine arguments ==
37    
38     integer nn
39    
40     c == local variables ==
41    
42     _RL objf
43    
44     #if defined (DYNAMIC)
45     _RL xx(nn)
46     _RL adxx(nn)
47     _RL dd(nn)
48     _RL gold(nn)
49     _RL xdiff(nn)
50     #elif defined (USE_POINTER) || (MAX_INDEPEND == 0)
51     _RL xx
52     _RL adxx
53     _RL dd(1)
54     _RL gold(1)
55     _RL xdiff(1)
56     pointer (pxx,xx(1))
57     pointer (padxx,adxx(1))
58     pointer (pdd,dd)
59     pointer (pgold,gold)
60     pointer (pxdiff,xdiff)
61     #else
62     integer nmax
63     parameter( nmax = MAX_INDEPEND )
64     ! _RL xx(nmax)
65     ! _RL adxx(nmax)
66     ! _RL dd(nmax)
67     ! _RL gold(nmax)
68     ! _RL xdiff(nmax)
69     _RL,allocatable:: xx(:)
70     _RL,allocatable:: adxx(:)
71     _RL,allocatable:: dd(:)
72     _RL,allocatable:: gold(:)
73     _RL,allocatable:: xdiff(:)
74     #endif
75    
76     integer myid,nprocs
77     common /mpi_parm/ myid,nprocs,mystart,myend
78     integer mylen, mystart,myend
79    
80     external distwork
81    
82     c-- Allocate memory for the control variables and the gradient vector.
83     #if defined(DYNAMIC)
84     #elif defined(USE_POINTER) || (MAX_INDEPEND == 0)
85     call myalloc( pxx , nn*REAL_BYTE )
86     call myalloc( padxx, nn*REAL_BYTE )
87     call myalloc( pdd, nn*REAL_BYTE )
88     call myalloc( pgold, nn*REAL_BYTE )
89     call myalloc( pxdiff, nn*REAL_BYTE )
90     #endif
91    
92     integer ifail
93     integer itmax
94     logical loffline
95    
96     c == external ==
97    
98     external simul
99     external lsline
100    
101     c == end of interface ==
102    
103     c-- Initialisize the model and set a first guess of the control
104     c-- variables.
105     ! call optim_initmod( nn, xx )
106     call optim_initmod(nn)
107    
108     #if defined (DYNAMIC)
109     #elif defined(USE_POINTER) || (MAX_INDEPEND == 0)
110     #else
111     if (nn .gt. nmax) then
112     print*,' OPTIMUM: Not enough space.'
113     print*,' nmax = ',nmax
114     print*,' nn = ',nn
115     print*
116     print*,' Set MAX_INDEPEND in Makefile .ge. ',nn
117     print*
118     stop ' ... stopped in OPTIMUM.'
119     endif
120     #endif
121    
122     if (myid .eq. 0) then
123     print*, ' OPTIMUM: Calling lsopt for iteration: ',optimcycle
124     print*, ' OPTIMUM: with nn, REAL_BYTE = ', nn, REAL_BYTE
125     endif
126    
127     loffline = .true.
128     itmax = numiter
129    
130     call distwork(myid,nprocs,nn,mystart,myend,mylen)
131     ! print '(a,i4,x,i10,x,i10,x,i10)','myid mystart myend mylen',myid,mystart,myend,mylen
132    
133     allocate(xx(mylen))
134     allocate(xdiff(mylen))
135     allocate(dd(mylen))
136     allocate(adxx(mylen))
137     allocate(gold(mylen))
138    
139     c-- Large scale optimization --> Gilbert & Lemarechal.
140     call lsopt_top( mylen, xx, objf, adxx
141     & , simul, lsline
142     & , epsx, fmin, epsg
143     & , iprint
144     & , itmax, nfunc, nupdate
145     & , dd, gold, xdiff
146     & , loffline
147     & , ifail )
148    
149     deallocate(xx)
150     deallocate(xdiff)
151     deallocate(adxx)
152     deallocate(dd)
153     deallocate(gold)
154    
155     return
156     end

  ViewVC Help
Powered by ViewVC 1.1.22