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

Contents of /MITgcm_contrib/ecco_utils/lbfgs_jpl_version/optim.2/simul.F

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


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

1
2
3 subroutine simul(
4 I indic,
5 I isforward,
6 I mylen,
7 O xx,
8 O objf,
9 O adxx
10 & )
11
12 c ==================================================================
13 c SUBROUTINE simul
14 c ==================================================================
15 c
16 c o This routine is called by the large-scale optimization lsopt.
17 c
18 c Input : indic - Parameter for optimcycle
19 c nmax - Number of control variables.
20 c
21 c Output : xx - Array of control variables.
22 c objf - Value of objective function.
23 c adxx - Gradients of objective function with respect
24 c to the control variables.
25 c
26 c
27 c started: Christian Eckert eckert@mit.edu 15-Feb-2000
28 c
29 c changed: Christian Eckert eckert@mit.edu 10-Mar-2000
30 c
31 c - Added ECCO layout.
32 c
33 c changed: Patrick Heimbach heimbach@mit.edu 19-Jun-2000
34 c - finished, revised and debugged
35 c
36 c ==================================================================
37 c SUBROUTINE simul
38 c ==================================================================
39
40 implicit none
41
42 c == global variables ==
43
44 #include "EEPARAMS.h"
45 #include "SIZE.h"
46 #include "ctrl.h"
47 include 'mpif.h'
48
49 c == routine arguments ==
50
51 logical isforward
52 integer indic
53 integer mylen
54 _RL xx(mylen)
55 _RL objf
56 _RL adxx(mylen)
57 integer nmax
58 parameter( nmax = MAX_INDEPEND )
59
60 c == local variables ==
61
62 integer i
63 _RL adobjf
64 _RS,allocatable:: vv(:)
65 _RS,allocatable:: tempvv(:)
66
67 logical lheaderonly
68 integer pidlen,myindx(2)
69 integer status(MPI_STATUS_SIZE),ierr
70 common /mpi_parm/myid, nprocs,mystart,myend
71 integer myid,nprocs,mystart,myend
72
73 c == end of interface ==
74
75 if(myid .eq. 0)
76 & print *, 'pathei-lsopt in simul'
77
78 c-- Call the combined modified forward model and the adjoint model.
79 do i = 1,mylen
80 xx(i) = 0.D0
81 adxx(i) = 0.D0
82 enddo
83
84 adobjf = 1.
85 c
86 lheaderonly = .false.
87
88 if (myid .eq. 0) then
89
90 print *, 'pathei-lsopt vor optim_readdata'
91
92 allocate(vv(nmax))
93 call optim_readdata(indic, nmax, ctrlname, lheaderonly, objf, vv)
94 endif
95
96 allocate(tempvv(mylen))
97 tempvv = 0.
98
99 ! As a master, sent out vectors of length pidlen to myid
100 if(myid.eq.0) then
101 do i=1,nprocs-1
102 call MPI_RECV(myindx,2,MPI_INTEGER,i,10,MPI_COMM_WORLD,
103 & status,ierr)
104 pidlen = myindx(2)-myindx(1)+1
105 call MPI_SEND(vv(myindx(1):myindx(2)),pidlen,
106 & MPI_FLOAT,i,11,MPI_COMM_WORLD,ierr)
107 enddo
108 !
109 xx(1:mylen) = vv(mystart:myend)
110 !
111 else
112 !
113 call MPI_SEND((/mystart,myend/),2,MPI_INTEGER,0,10,
114 & MPI_COMM_WORLD,ierr)
115 call MPI_RECV(tempvv,myend-mystart+1,MPI_FLOAT,0,11,
116 & MPI_COMM_WORLD,status,ierr)
117 !
118 xx(1:mylen) = tempvv
119 endif
120
121
122 if (.not. isforward) then
123
124 if (myid .eq. 0 ) then
125 vv = 0.
126 call optim_readdata(indic, nmax, costname, lheaderonly, objf, vv )
127 endif
128 tempvv = 0.
129
130 if(myid.eq.0) then
131 do i=1,nprocs-1
132 call MPI_RECV(myindx,2,MPI_INTEGER,i,10,MPI_COMM_WORLD,
133 & status,ierr)
134 pidlen = myindx(2)-myindx(1)+1
135 call MPI_SEND(vv(myindx(1):myindx(2)),pidlen,
136 & MPI_FLOAT,i,11,MPI_COMM_WORLD,ierr)
137 enddo
138 !
139 adxx(1:mylen) = vv(mystart:myend)
140 !
141 else
142 !
143 call MPI_SEND((/mystart,myend/),2,MPI_INTEGER,0,10,
144 & MPI_COMM_WORLD,ierr)
145 call MPI_RECV(tempvv,myend-mystart+1,MPI_FLOAT,0,11,
146 & MPI_COMM_WORLD,status,ierr)
147 !
148 adxx(1:mylen) = tempvv
149 endif
150
151 endif !end isforward
152
153 call MPI_BCAST(objf,1,MPI_DOUBLE_PRECISION,0,MPI_COMM_WORLD,ierr)
154
155 if(myid .eq. 0) then
156 cph(
157 print *, ' leaving simul with nn, objf = ', nmax, objf
158 print *, ' leaving simul with xx = ', xx(1), xx(2)
159 print *, ' leaving simul with adxx = ', adxx(1), adxx(2)
160
161 deallocate(vv)
162 endif
163 deallocate(tempvv)
164
165 do i=1,mylen
166 c if (xx(i).EQ.'NaN') then
167 c print *, 'pathei - out: i = ', i
168 c end if
169 end do
170 cph)
171
172 return
173 end

  ViewVC Help
Powered by ViewVC 1.1.22