/[MITgcm]/MITgcm_contrib/heimbach/OpenAD/OAD_support/active_module.f90
ViewVC logotype

Contents of /MITgcm_contrib/heimbach/OpenAD/OAD_support/active_module.f90

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


Revision 1.4 - (show annotations) (download)
Wed Jun 25 21:51:50 2008 UTC (15 years, 9 months ago) by utke
Branch: MAIN
CVS Tags: HEAD
Changes since 1.3: +0 -0 lines
FILE REMOVED
file renames and signature changes after
the introduction of the AUTODIFF_TAMC_COMPATIBILITY option

1 module active_module
2 use w2f__types
3 implicit none
4 private
5 public :: active, saxpy, sax, setderiv, zero_deriv, &
6 &convert_p2a_scalar, convert_a2p_scalar, &
7 &convert_p2a_vector, convert_a2p_vector, &
8 &convert_p2a_matrix, convert_a2p_matrix, &
9 &convert_p2a_three_tensor, convert_a2p_three_tensor, &
10 &convert_p2a_four_tensor, convert_a2p_four_tensor, &
11 &convert_p2a_five_tensor, convert_a2p_five_tensor
12
13
14 !
15 ! active needs to be a sequence type
16 ! with no initialization
17 !
18 type active
19 sequence
20 real(w2f__8) :: v
21 ! initialization does not work for active variables
22 ! inside of common block, such as in boxmodel
23 ! initialization is required for correct adjoint
24 real(w2f__8) :: d=0.0
25 ! real(w2f__8) :: d
26 end type active
27
28 interface saxpy
29 module procedure saxpy_a_a
30 end interface
31
32 interface setderiv
33 module procedure setderiv_a_a
34 end interface
35
36 interface zero_deriv
37 module procedure zero_deriv_a
38 end interface
39
40 interface sax
41 module procedure sax_d_a_a, sax_i_a_a
42 end interface
43
44 interface convert_p2a_scalar
45 module procedure convert_sp2a_scalar_impl
46 module procedure convert_p2a_scalar_impl
47 end interface
48 interface convert_a2p_scalar
49 module procedure convert_a2sp_scalar_impl
50 module procedure convert_a2p_scalar_impl
51 end interface
52
53 interface convert_p2a_vector
54 module procedure convert_sp2a_vector_impl
55 module procedure convert_p2a_vector_impl
56 end interface
57 interface convert_a2p_vector
58 module procedure convert_a2sp_vector_impl
59 module procedure convert_a2p_vector_impl
60 end interface
61
62 interface convert_p2a_matrix
63 module procedure convert_sp2a_matrix_impl
64 module procedure convert_p2a_matrix_impl
65 end interface
66 interface convert_a2p_matrix
67 module procedure convert_a2sp_matrix_impl
68 module procedure convert_a2p_matrix_impl
69 end interface
70
71 interface convert_p2a_three_tensor
72 module procedure convert_sp2a_three_tensor_impl
73 module procedure convert_p2a_three_tensor_impl
74 end interface
75 interface convert_a2p_three_tensor
76 module procedure convert_a2sp_three_tensor_impl
77 module procedure convert_a2p_three_tensor_impl
78 end interface
79
80 interface convert_p2a_four_tensor
81 module procedure convert_sp2a_four_tensor_impl
82 module procedure convert_p2a_four_tensor_impl
83 end interface
84 interface convert_a2p_four_tensor
85 module procedure convert_a2sp_four_tensor_impl
86 module procedure convert_a2p_four_tensor_impl
87 end interface
88
89 interface convert_p2a_five_tensor
90 module procedure convert_sp2a_five_tensor_impl
91 module procedure convert_p2a_five_tensor_impl
92 end interface
93 interface convert_a2p_five_tensor
94 module procedure convert_a2sp_five_tensor_impl
95 module procedure convert_a2p_five_tensor_impl
96 end interface
97
98 contains
99
100 !
101 ! chain rule saxpy to be used in forward and reverse modes
102 !
103
104 subroutine saxpy_a_a(a,x,y)
105 real(w2f__8), intent(in) :: a
106 type(active), intent(in) :: x
107 type(active), intent(inout) :: y
108 y%d=y%d+x%d*a
109 end subroutine saxpy_a_a
110
111 !
112 ! chain rule saxpy to be used in forward and reverse modes
113 ! derivative component of y is equal to zero initially
114 ! note: y needs to be inout as otherwise value component gets
115 ! zeroed out
116 !
117
118 subroutine sax_d_a_a(a,x,y)
119 real(w2f__8), intent(in) :: a
120 type(active), intent(in) :: x
121 type(active), intent(inout) :: y
122 y%d=x%d*a
123 end subroutine sax_d_a_a
124
125 subroutine sax_i_a_a(a,x,y)
126 integer(kind=w2f__i8), intent(in) :: a
127 type(active), intent(in) :: x
128 type(active), intent(inout) :: y
129 y%d=x%d*a
130 end subroutine sax_i_a_a
131
132 !
133 ! set derivative of y to be equal to derivative of x
134 ! note: making y inout allows for already existing active
135 ! variables to become the target of a derivative assignment
136 !
137
138 subroutine setderiv_a_a(y,x)
139 type(active), intent(inout) :: y
140 type(active), intent(in) :: x
141 y%d=x%d
142 end subroutine setderiv_a_a
143
144 !
145 ! set derivative components to 0.0
146 !
147 subroutine zero_deriv_a(x)
148 type(active), intent(inout) :: x
149 x%d=0.0d0
150 end subroutine zero_deriv_a
151
152 !
153 ! active/passive conversions
154 !
155 subroutine convert_a2sp_scalar_impl(convertTo, convertFrom)
156 real(w2f__4), intent(out) :: convertTo
157 type(active), intent(in) :: convertFrom
158 convertTo=convertFrom%v
159 end subroutine
160
161 subroutine convert_a2p_scalar_impl(convertTo, convertFrom)
162 real(w2f__8), intent(out) :: convertTo
163 type(active), intent(in) :: convertFrom
164 convertTo=convertFrom%v
165 end subroutine
166
167 subroutine convert_sp2a_scalar_impl(convertTo, convertFrom)
168 real(w2f__4), intent(in) :: convertFrom
169 type(active), intent(inout) :: convertTo
170 convertTo%v=convertFrom
171 end subroutine
172
173 subroutine convert_p2a_scalar_impl(convertTo, convertFrom)
174 real(w2f__8), intent(in) :: convertFrom
175 type(active), intent(inout) :: convertTo
176 convertTo%v=convertFrom
177 end subroutine
178
179 subroutine convert_a2sp_vector_impl(convertTo, convertFrom)
180 type(active), dimension(:), intent(in) :: convertFrom
181 real(w2f__4), dimension(:), intent(out) :: convertTo
182 convertTo=convertFrom%v
183 end subroutine
184
185 subroutine convert_a2p_vector_impl(convertTo, convertFrom)
186 type(active), dimension(:), intent(in) :: convertFrom
187 real(w2f__8), dimension(:), intent(out) :: convertTo
188 convertTo=convertFrom%v
189 end subroutine
190
191 subroutine convert_sp2a_vector_impl(convertTo, convertFrom)
192 real(w2f__4), dimension(:), intent(in) :: convertFrom
193 type(active), dimension(:), intent(inout) :: convertTo
194 convertTo%v=convertFrom
195 end subroutine
196
197 subroutine convert_p2a_vector_impl(convertTo, convertFrom)
198 real(w2f__8), dimension(:), intent(in) :: convertFrom
199 type(active), dimension(:), intent(inout) :: convertTo
200 convertTo%v=convertFrom
201 end subroutine
202
203 subroutine convert_a2sp_matrix_impl(convertTo, convertFrom)
204 type(active), dimension(:,:), intent(in) :: convertFrom
205 real(w2f__4), dimension(:,:), intent(out) :: convertTo
206 convertTo=convertFrom%v
207 end subroutine
208
209 subroutine convert_sp2a_matrix_impl(convertTo, convertFrom)
210 real(w2f__4), dimension(:,:), intent(in) :: convertFrom
211 type(active), dimension(:,:), intent(inout) :: convertTo
212 convertTo%v=convertFrom
213 end subroutine
214
215 subroutine convert_a2p_matrix_impl(convertTo, convertFrom)
216 type(active), dimension(:,:), intent(in) :: convertFrom
217 real(w2f__8), dimension(:,:), intent(out) :: convertTo
218 convertTo=convertFrom%v
219 end subroutine
220
221 subroutine convert_p2a_matrix_impl(convertTo, convertFrom)
222 real(w2f__8), dimension(:,:), intent(in) :: convertFrom
223 type(active), dimension(:,:), intent(inout) :: convertTo
224 convertTo%v=convertFrom
225 end subroutine
226
227 subroutine convert_a2sp_three_tensor_impl(convertTo, convertFrom)
228 type(active), dimension(:,:,:), intent(in) :: convertFrom
229 real(w2f__4), dimension(:,:,:), intent(out) :: convertTo
230 convertTo=convertFrom%v
231 end subroutine
232
233 subroutine convert_a2p_three_tensor_impl(convertTo, convertFrom)
234 type(active), dimension(:,:,:), intent(in) :: convertFrom
235 real(w2f__8), dimension(:,:,:), intent(out) :: convertTo
236 convertTo=convertFrom%v
237 end subroutine
238
239 subroutine convert_sp2a_three_tensor_impl(convertTo, convertFrom)
240 real(w2f__4), dimension(:,:,:), intent(in) :: convertFrom
241 type(active), dimension(:,:,:), intent(inout) :: convertTo
242 convertTo%v=convertFrom
243 end subroutine
244
245 subroutine convert_p2a_three_tensor_impl(convertTo, convertFrom)
246 real(w2f__8), dimension(:,:,:), intent(in) :: convertFrom
247 type(active), dimension(:,:,:), intent(inout) :: convertTo
248 convertTo%v=convertFrom
249 end subroutine
250
251 subroutine convert_a2sp_four_tensor_impl(convertTo, convertFrom)
252 type(active), dimension(:,:,:,:), intent(in) :: convertFrom
253 real(w2f__4), dimension(:,:,:,:), intent(out) :: convertTo
254 convertTo=convertFrom%v
255 end subroutine
256
257 subroutine convert_a2p_four_tensor_impl(convertTo, convertFrom)
258 type(active), dimension(:,:,:,:), intent(in) :: convertFrom
259 real(w2f__8), dimension(:,:,:,:), intent(out) :: convertTo
260 convertTo=convertFrom%v
261 end subroutine
262
263 subroutine convert_sp2a_four_tensor_impl(convertTo, convertFrom)
264 real(w2f__4), dimension(:,:,:,:), intent(in) :: convertFrom
265 type(active), dimension(:,:,:,:), intent(inout) :: convertTo
266 convertTo%v=convertFrom
267 end subroutine
268
269 subroutine convert_p2a_four_tensor_impl(convertTo, convertFrom)
270 real(w2f__8), dimension(:,:,:,:), intent(in) :: convertFrom
271 type(active), dimension(:,:,:,:), intent(inout) :: convertTo
272 convertTo%v=convertFrom
273 end subroutine
274
275 subroutine convert_a2sp_five_tensor_impl(convertTo, convertFrom)
276 type(active), dimension(:,:,:,:,:), intent(in) :: convertFrom
277 real(w2f__4), dimension(:,:,:,:,:), intent(out) :: convertTo
278 convertTo=convertFrom%v
279 end subroutine
280
281 subroutine convert_a2p_five_tensor_impl(convertTo, convertFrom)
282 type(active), dimension(:,:,:,:,:), intent(in) :: convertFrom
283 real(w2f__8), dimension(:,:,:,:,:), intent(out) :: convertTo
284 convertTo=convertFrom%v
285 end subroutine
286
287 subroutine convert_sp2a_five_tensor_impl(convertTo, convertFrom)
288 real(w2f__4), dimension(:,:,:,:,:), intent(in) :: convertFrom
289 type(active), dimension(:,:,:,:,:), intent(inout) :: convertTo
290 convertTo%v=convertFrom
291 end subroutine
292
293 subroutine convert_p2a_five_tensor_impl(convertTo, convertFrom)
294 real(w2f__8), dimension(:,:,:,:,:), intent(in) :: convertFrom
295 type(active), dimension(:,:,:,:,:), intent(inout) :: convertTo
296 convertTo%v=convertFrom
297 end subroutine
298
299 end module
300
301

  ViewVC Help
Powered by ViewVC 1.1.22