source: CPL/oasis3-mct/branches/OASIS3-MCT_5.0_branch/lib/psmile/src/mod_oasis_getput_interface.F90 @ 6331

Last change on this file since 6331 was 6331, checked in by aclsce, 17 months ago

Moved oasis-mct_5.0 in oasis3-mct/branches directory.

File size: 48.3 KB
Line 
1
2!> OASIS send/receive (put/get) user interfaces
3
4MODULE mod_oasis_getput_interface
5!---------------------------------------------------------------------
6
7    use mod_oasis_kinds
8    use mod_oasis_data
9    use mod_oasis_parameters
10    use mod_oasis_advance
11    use mod_oasis_var
12    use mod_oasis_sys
13
14    implicit none
15    private
16
17    public oasis_put
18    public oasis_get
19
20#include "oasis_os.h"
21
22    integer(kind=ip_i4_p)     istatus(MPI_STATUS_SIZE)
23
24!> Generic overloaded interface for data put (send)
25  interface oasis_put
26#ifndef __NO_4BYTE_REALS
27     module procedure oasis_put_r14
28     module procedure oasis_put_r24
29     module procedure oasis_put_r34
30#endif
31     module procedure oasis_put_r18
32     module procedure oasis_put_r28
33     module procedure oasis_put_r38
34  end interface
35
36!> Generic overloaded interface for data get (receive)
37  interface oasis_get
38#ifndef __NO_4BYTE_REALS
39     module procedure oasis_get_r14
40     module procedure oasis_get_r24
41     module procedure oasis_get_r34
42#endif
43     module procedure oasis_get_r18
44     module procedure oasis_get_r28
45     module procedure oasis_get_r38
46  end interface
47
48!---------------------------------------------------------------------
49contains
50!---------------------------------------------------------------------
51#ifndef __NO_4BYTE_REALS
52
53!> Send 4 byte real 1D data
54
55  SUBROUTINE oasis_put_r14(var_id,kstep,fld1,kinfo, &
56    fld2, fld3, fld4, fld5, write_restart)
57
58    IMPLICIT none
59    !-------------------------------------
60    integer(kind=ip_i4_p) , intent(in) :: var_id      !< variable id
61    integer(kind=ip_i4_p) , intent(in) :: kstep       !< model time in seconds
62    real(kind=ip_single_p)             :: fld1(:)     !< field data
63    integer(kind=ip_i4_p) , intent(out):: kinfo       !< return code
64    real(kind=ip_single_p), optional :: fld2(:)       !< higher order field data
65    real(kind=ip_single_p), optional :: fld3(:)       !< higher order field data
66    real(kind=ip_single_p), optional :: fld4(:)       !< higher order field data
67    real(kind=ip_single_p), optional :: fld5(:)       !< higher order field data
68    logical               , optional :: write_restart !< write restart now
69    !-------------------------------------
70    logical :: lwrst
71    character(len=*),parameter :: subname = '(oasis_put_r14)'
72    !-------------------------------------
73
74    call oasis_debug_enter(subname)
75    kinfo = OASIS_OK
76    if (.not. oasis_coupled) then
77       call oasis_debug_exit(subname)
78       return
79    endif
80
81    if (prism_var(var_id)%num > 1) then
82       write(nulprt,*) subname,estr,'called for variable ',trim(prism_var(var_id)%name)
83       write(nulprt,*) subname,estr,'expecting bundled field with num = ',prism_var(var_id)%num
84       call oasis_abort(file=__FILE__,line=__LINE__)
85    endif
86
87    if (present(write_restart)) then
88       lwrst = write_restart
89    else
90       lwrst = .false.
91    endif
92
93    if (present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
94       CALL oasis_put_worker(var_id,kstep,DBLE(fld1),kinfo,DBLE(fld2), &
95            DBLE(fld3),DBLE(fld4),DBLE(fld5),write_restart=lwrst)
96    elseif (.not.present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
97       CALL oasis_put_worker(var_id,kstep,DBLE(fld1),kinfo,DBLE(fld2), &
98            DBLE(fld3),DBLE(fld4),write_restart=lwrst)
99    elseif (.not.present(fld5) .and. .not.present(fld4) .and. present(fld3) .and. present(fld2)) then
100       CALL oasis_put_worker(var_id,kstep,DBLE(fld1),kinfo,DBLE(fld2), &
101            DBLE(fld3),write_restart=lwrst)
102    elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. present(fld2)) then
103       CALL oasis_put_worker(var_id,kstep,DBLE(fld1),kinfo,DBLE(fld2), &
104            write_restart=lwrst)
105    elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. .not.present(fld2)) then
106       CALL oasis_put_worker(var_id,kstep,DBLE(fld1),kinfo,write_restart=lwrst)
107    else
108       WRITE(nulprt,*) subname,estr,' Wrong field array argument list in oasis_put'
109       call oasis_abort(file=__FILE__,line=__LINE__)
110    endif
111
112    call oasis_debug_exit(subname)
113
114  END SUBROUTINE oasis_put_r14
115#endif
116
117!-------------------------------------------------------------------
118
119!> Send 4 byte real 1D data
120
121  SUBROUTINE oasis_put_r18(var_id,kstep,fld1,kinfo, &
122    fld2, fld3, fld4, fld5, write_restart)
123
124    IMPLICIT none
125    !-------------------------------------
126    integer(kind=ip_i4_p) , intent(in) :: var_id      !< variable id
127    integer(kind=ip_i4_p) , intent(in) :: kstep       !< model time in seconds
128    real(kind=ip_double_p)             :: fld1(:)     !< field data
129    integer(kind=ip_i4_p) , intent(out):: kinfo       !< return code
130    real(kind=ip_double_p), optional :: fld2(:)       !< higher order field data
131    real(kind=ip_double_p), optional :: fld3(:)       !< higher order field data
132    real(kind=ip_double_p), optional :: fld4(:)       !< higher order field data
133    real(kind=ip_double_p), optional :: fld5(:)       !< higher order field data
134    logical               , optional :: write_restart !< write restart now
135    !-------------------------------------
136    logical :: lwrst
137    character(len=*),parameter :: subname = '(oasis_put_r18)'
138    !-------------------------------------
139
140    call oasis_debug_enter(subname)
141    kinfo = OASIS_OK
142    if (.not. oasis_coupled) then
143       call oasis_debug_exit(subname)
144       return
145    endif
146
147    if (prism_var(var_id)%num > 1) then
148       write(nulprt,*) subname,estr,'called for variable ',trim(prism_var(var_id)%name)
149       write(nulprt,*) subname,estr,'expecting bundled field with num = ',prism_var(var_id)%num
150       call oasis_abort(file=__FILE__,line=__LINE__)
151    endif
152
153    if (present(write_restart)) then
154       lwrst = write_restart
155    else
156       lwrst = .false.
157    endif
158
159    if (present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
160       CALL oasis_put_worker(var_id,kstep,fld1,kinfo,fld2, &
161            fld3,fld4,fld5,write_restart=lwrst)
162    elseif (.not.present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
163       CALL oasis_put_worker(var_id,kstep,fld1,kinfo,fld2, &
164            fld3,fld4,write_restart=lwrst)
165    elseif (.not.present(fld5) .and. .not.present(fld4) .and. present(fld3) .and. present(fld2)) then
166       CALL oasis_put_worker(var_id,kstep,fld1,kinfo,fld2, &
167            fld3,write_restart=lwrst)
168    elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. present(fld2)) then
169       CALL oasis_put_worker(var_id,kstep,fld1,kinfo,fld2, &
170            write_restart=lwrst)
171    elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. .not.present(fld2)) then
172       CALL oasis_put_worker(var_id,kstep,fld1,kinfo,write_restart=lwrst)
173    else
174       WRITE(nulprt,*) subname,estr,' Wrong field array argument list in oasis_put'
175       call oasis_abort(file=__FILE__,line=__LINE__)
176    endif
177
178    call oasis_debug_exit(subname)
179
180  END SUBROUTINE oasis_put_r18
181
182!---------------------------------------------------------------------
183#ifndef __NO_4BYTE_REALS
184
185!> Send 4 byte real 2D data
186
187  SUBROUTINE oasis_put_r24(var_id,kstep,fld1,kinfo, &
188    fld2, fld3, fld4, fld5, write_restart)
189
190    IMPLICIT none
191    !-------------------------------------
192    integer(kind=ip_i4_p) , intent(in) :: var_id      !< variable id
193    integer(kind=ip_i4_p) , intent(in) :: kstep       !< model time in seconds
194    real(kind=ip_single_p) :: fld1(:,:)               !< field data
195    integer(kind=ip_i4_p) , intent(out):: kinfo       !< return code
196    real(kind=ip_single_p), optional :: fld2(:,:)     !< higher order field data
197    real(kind=ip_single_p), optional :: fld3(:,:)     !< higher order field data
198    real(kind=ip_single_p), optional :: fld4(:,:)     !< higher order field data
199    real(kind=ip_single_p), optional :: fld5(:,:)     !< higher order field data
200    logical               , optional :: write_restart !< write restart now
201    !-------------------------------------
202    logical :: lwrst
203    integer(kind=ip_i4_p) :: n, size_fld1
204    character(len=*),parameter :: subname = '(oasis_put_r24)'
205    !-------------------------------------
206
207    call oasis_debug_enter(subname)
208    kinfo = OASIS_OK
209    if (.not. oasis_coupled) then
210       call oasis_debug_exit(subname)
211       return
212    endif
213
214    if (present(write_restart)) then
215       lwrst = write_restart
216    else
217       lwrst = .false.
218    endif
219
220    if (prism_var(var_id)%num > 1) then
221    ! treat data as 1d bundled data
222
223       if (size(fld1,dim=2) /= prism_var(var_id)%num) then
224          write(nulprt,*) subname,estr,'called for variable ',trim(prism_var(var_id)%name)
225          write(nulprt,*) subname,estr,'expecting bundled field with num = ',prism_var(var_id)%num
226          write(nulprt,*) subname,estr,'passing in field with incorrect 2nd dim size = ',size(fld1,dim=2)
227          call oasis_abort(file=__FILE__,line=__LINE__)
228       endif
229
230       size_fld1 = size(fld1,dim=2)
231       if (present(fld2)) then
232          if (size(fld2,dim=2) /= size_fld1) then
233             write(nulprt,*) subname,estr,'fld2 size different than fld1 size ',size_fld1,size(fld2,dim=2)
234             call oasis_abort(file=__FILE__,line=__LINE__)
235          endif
236       endif
237       if (present(fld3)) then
238          if (size(fld3,dim=2) /= size_fld1) then
239             write(nulprt,*) subname,estr,'fld3 size different than fld1 size ',size_fld1,size(fld3,dim=2)
240             call oasis_abort(file=__FILE__,line=__LINE__)
241          endif
242       endif
243       if (present(fld4)) then
244          if (size(fld4,dim=2) /= size_fld1) then
245             write(nulprt,*) subname,estr,'fld4 size different than fld1 size ',size_fld1,size(fld4,dim=2)
246             call oasis_abort(file=__FILE__,line=__LINE__)
247          endif
248       endif
249       if (present(fld5)) then
250          if (size(fld5,dim=2) /= size_fld1) then
251             write(nulprt,*) subname,estr,'fld5 size different than fld1 size ',size_fld1,size(fld5,dim=2)
252             call oasis_abort(file=__FILE__,line=__LINE__)
253          endif
254       endif
255
256       do n = 1,prism_var(var_id)%num
257          if (present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
258             CALL oasis_put_worker(var_id,kstep,DBLE(fld1(:,n)),kinfo,DBLE(fld2(:,n)), &
259                  DBLE(fld3(:,n)),DBLE(fld4(:,n)),DBLE(fld5(:,n)),write_restart=lwrst,varnum=n)
260          elseif (.not.present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
261             CALL oasis_put_worker(var_id,kstep,DBLE(fld1(:,n)),kinfo,DBLE(fld2(:,n)), &
262                  DBLE(fld3(:,n)),DBLE(fld4(:,n)),write_restart=lwrst,varnum=n)
263          elseif (.not.present(fld5) .and. .not.present(fld4) .and. present(fld3) .and. present(fld2)) then
264             CALL oasis_put_worker(var_id,kstep,DBLE(fld1(:,n)),kinfo,DBLE(fld2(:,n)), &
265                  DBLE(fld3(:,n)),write_restart=lwrst,varnum=n)
266          elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. present(fld2)) then
267             CALL oasis_put_worker(var_id,kstep,DBLE(fld1(:,n)),kinfo,DBLE(fld2(:,n)), &
268                  write_restart=lwrst,varnum=n)
269          elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. .not.present(fld2)) then
270             CALL oasis_put_worker(var_id,kstep,DBLE(fld1(:,n)),kinfo,write_restart=lwrst,varnum=n)
271          else
272             WRITE(nulprt,*) subname,estr,' Wrong field array argument list in oasis_put'
273             call oasis_abort(file=__FILE__,line=__LINE__)
274          endif
275       enddo
276
277    else
278    ! treat data as 2d unbundled data
279
280       if (present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
281          CALL oasis_put_worker(var_id,kstep,DBLE(PACK(fld1,mask=.true.)),kinfo,DBLE(PACK(fld2,mask=.true.)), &
282               DBLE(PACK(fld3,mask=.true.)),DBLE(PACK(fld4,mask=.true.)),DBLE(PACK(fld5,mask=.true.)),write_restart=lwrst)
283       elseif (.not.present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
284          CALL oasis_put_worker(var_id,kstep,DBLE(PACK(fld1,mask=.true.)),kinfo,DBLE(PACK(fld2,mask=.true.)), &
285               DBLE(PACK(fld3,mask=.true.)),DBLE(PACK(fld4,mask=.true.)),write_restart=lwrst)
286       elseif (.not.present(fld5) .and. .not.present(fld4) .and. present(fld3) .and. present(fld2)) then
287          CALL oasis_put_worker(var_id,kstep,DBLE(PACK(fld1,mask=.true.)),kinfo,DBLE(PACK(fld2,mask=.true.)), &
288               DBLE(PACK(fld3,mask=.true.)),write_restart=lwrst)
289       elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. present(fld2)) then
290          CALL oasis_put_worker(var_id,kstep,DBLE(PACK(fld1,mask=.true.)),kinfo,DBLE(PACK(fld2,mask=.true.)), &
291               write_restart=lwrst)
292       elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. .not.present(fld2)) then
293          CALL oasis_put_worker(var_id,kstep,DBLE(PACK(fld1,mask=.true.)),kinfo,write_restart=lwrst)
294       else
295          WRITE(nulprt,*) subname,estr,' Wrong field array argument list in oasis_put'
296          call oasis_abort(file=__FILE__,line=__LINE__)
297       endif
298
299    endif
300
301    call oasis_debug_exit(subname)
302
303  END SUBROUTINE oasis_put_r24
304#endif
305
306!---------------------------------------------------------------------
307#ifndef __NO_4BYTE_REALS
308
309!> Send 4 byte real 2D bundled data
310
311  SUBROUTINE oasis_put_r34(var_id,kstep,fld1,kinfo, &
312    fld2, fld3, fld4, fld5, write_restart)
313
314    IMPLICIT none
315    !-------------------------------------
316    integer(kind=ip_i4_p) , intent(in) :: var_id      !< variable id
317    integer(kind=ip_i4_p) , intent(in) :: kstep       !< model time in seconds
318    real(kind=ip_single_p) :: fld1(:,:,:)             !< field data
319    integer(kind=ip_i4_p) , intent(out):: kinfo       !< return code
320    real(kind=ip_single_p), optional :: fld2(:,:,:)   !< higher order field data
321    real(kind=ip_single_p), optional :: fld3(:,:,:)   !< higher order field data
322    real(kind=ip_single_p), optional :: fld4(:,:,:)   !< higher order field data
323    real(kind=ip_single_p), optional :: fld5(:,:,:)   !< higher order field data
324    logical               , optional :: write_restart !< write restart now
325    !-------------------------------------
326    logical :: lwrst
327    integer(kind=ip_i4_p) :: n, size_fld1
328    character(len=*),parameter :: subname = '(oasis_put_r34)'
329    !-------------------------------------
330
331    call oasis_debug_enter(subname)
332    kinfo = OASIS_OK
333    if (.not. oasis_coupled) then
334       call oasis_debug_exit(subname)
335       return
336    endif
337
338    if (present(write_restart)) then
339       lwrst = write_restart
340    else
341       lwrst = .false.
342    endif
343
344    if (prism_var(var_id)%num > 1) then
345    ! treat data as 2d bundled data
346
347       if (size(fld1,dim=3) /= prism_var(var_id)%num) then
348          write(nulprt,*) subname,estr,'called for variable ',trim(prism_var(var_id)%name)
349          write(nulprt,*) subname,estr,'expecting bundled field with num = ',prism_var(var_id)%num
350          write(nulprt,*) subname,estr,'passing in field with incorrect 3rd dim size = ',size(fld1,dim=3)
351          call oasis_abort(file=__FILE__,line=__LINE__)
352       endif
353
354       size_fld1 = size(fld1,dim=3)
355       if (present(fld2)) then
356          if (size(fld2,dim=3) /= size_fld1) then
357             write(nulprt,*) subname,estr,'fld2 size different than fld1 size ',size_fld1,size(fld2,dim=3)
358             call oasis_abort(file=__FILE__,line=__LINE__)
359          endif
360       endif
361       if (present(fld3)) then
362          if (size(fld3,dim=3) /= size_fld1) then
363             write(nulprt,*) subname,estr,'fld3 size different than fld1 size ',size_fld1,size(fld3,dim=3)
364             call oasis_abort(file=__FILE__,line=__LINE__)
365          endif
366       endif
367       if (present(fld4)) then
368          if (size(fld4,dim=3) /= size_fld1) then
369             write(nulprt,*) subname,estr,'fld4 size different than fld1 size ',size_fld1,size(fld4,dim=3)
370             call oasis_abort(file=__FILE__,line=__LINE__)
371          endif
372       endif
373       if (present(fld5)) then
374          if (size(fld5,dim=3) /= size_fld1) then
375             write(nulprt,*) subname,estr,'fld5 size different than fld1 size ',size_fld1,size(fld5,dim=3)
376             call oasis_abort(file=__FILE__,line=__LINE__)
377          endif
378       endif
379
380       do n = 1,prism_var(var_id)%num
381          if (present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
382             CALL oasis_put_worker(var_id,kstep,DBLE(PACK(fld1(:,:,n),mask=.true.)),kinfo,DBLE(PACK(fld2(:,:,n),mask=.true.)), &
383                  DBLE(PACK(fld3(:,:,n),mask=.true.)),DBLE(PACK(fld4(:,:,n),mask=.true.)),DBLE(PACK(fld5(:,:,n),mask=.true.)), &
384                  write_restart=lwrst,varnum=n)
385          elseif (.not.present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
386             CALL oasis_put_worker(var_id,kstep,DBLE(PACK(fld1(:,:,n),mask=.true.)),kinfo,DBLE(PACK(fld2(:,:,n),mask=.true.)), &
387                  DBLE(PACK(fld3(:,:,n),mask=.true.)),DBLE(PACK(fld4(:,:,n),mask=.true.)),write_restart=lwrst,varnum=n)
388          elseif (.not.present(fld5) .and. .not.present(fld4) .and. present(fld3) .and. present(fld2)) then
389             CALL oasis_put_worker(var_id,kstep,DBLE(PACK(fld1(:,:,n),mask=.true.)),kinfo,DBLE(PACK(fld2(:,:,n),mask=.true.)), &
390                  DBLE(PACK(fld3(:,:,n),mask=.true.)),write_restart=lwrst,varnum=n)
391          elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. present(fld2)) then
392             CALL oasis_put_worker(var_id,kstep,DBLE(PACK(fld1(:,:,n),mask=.true.)),kinfo,DBLE(PACK(fld2(:,:,n),mask=.true.)), &
393                  write_restart=lwrst,varnum=n)
394          elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. .not.present(fld2)) then
395             CALL oasis_put_worker(var_id,kstep,DBLE(PACK(fld1(:,:,n),mask=.true.)),kinfo,write_restart=lwrst,varnum=n)
396          else
397             WRITE(nulprt,*) subname,estr,' Wrong field array argument list in oasis_put'
398             call oasis_abort(file=__FILE__,line=__LINE__)
399          endif
400       enddo
401
402    else
403       WRITE(nulprt,*) subname,estr,' Dimension sizes incorrect'
404       call oasis_abort(file=__FILE__,line=__LINE__)
405
406    endif
407
408    call oasis_debug_exit(subname)
409
410  END SUBROUTINE oasis_put_r34
411#endif
412!-------------------------------------------------------------------
413!---------------------------------------------------------------------
414
415!> Send 8 byte real 2D data
416
417  SUBROUTINE oasis_put_r28(var_id,kstep,fld1,kinfo, &
418    fld2, fld3, fld4, fld5, write_restart)
419
420    IMPLICIT none
421    !-------------------------------------
422    integer(kind=ip_i4_p) , intent(in) :: var_id      !< variable id
423    integer(kind=ip_i4_p) , intent(in) :: kstep       !< model time in seconds
424    real(kind=ip_double_p) :: fld1(:,:)               !< field data
425    integer(kind=ip_i4_p) , intent(out):: kinfo       !< return code
426    real(kind=ip_double_p), optional :: fld2(:,:)     !< higher order field data
427    real(kind=ip_double_p), optional :: fld3(:,:)     !< higher order field data
428    real(kind=ip_double_p), optional :: fld4(:,:)     !< higher order field data
429    real(kind=ip_double_p), optional :: fld5(:,:)     !< higher order field data
430    logical               , optional :: write_restart !< write restart now
431    !-------------------------------------
432    logical :: lwrst
433    integer(kind=ip_i4_p) :: n, size_fld1
434    character(len=*),parameter :: subname = '(oasis_put_r28)'
435    !-------------------------------------
436
437    call oasis_debug_enter(subname)
438    kinfo = OASIS_OK
439    if (.not. oasis_coupled) then
440       call oasis_debug_exit(subname)
441       return
442    endif
443
444    if (present(write_restart)) then
445       lwrst = write_restart
446    else
447       lwrst = .false.
448    endif
449
450    if (prism_var(var_id)%num > 1) then
451    ! treat data as 1d bundled data
452
453       if (size(fld1,dim=2) /= prism_var(var_id)%num) then
454          write(nulprt,*) subname,estr,'called for variable ',trim(prism_var(var_id)%name)
455          write(nulprt,*) subname,estr,'expecting bundled field with num = ',prism_var(var_id)%num
456          write(nulprt,*) subname,estr,'passing in field with incorrect 2nd dim size = ',size(fld1,dim=2)
457          call oasis_abort(file=__FILE__,line=__LINE__)
458       endif
459
460       size_fld1 = size(fld1,dim=2)
461       if (present(fld2)) then
462          if (size(fld2,dim=2) /= size_fld1) then
463             write(nulprt,*) subname,estr,'fld2 size different than fld1 size ',size_fld1,size(fld2,dim=2)
464             call oasis_abort(file=__FILE__,line=__LINE__)
465          endif
466       endif
467       if (present(fld3)) then
468          if (size(fld3,dim=2) /= size_fld1) then
469             write(nulprt,*) subname,estr,'fld3 size different than fld1 size ',size_fld1,size(fld3,dim=2)
470             call oasis_abort(file=__FILE__,line=__LINE__)
471          endif
472       endif
473       if (present(fld4)) then
474          if (size(fld4,dim=2) /= size_fld1) then
475             write(nulprt,*) subname,estr,'fld4 size different than fld1 size ',size_fld1,size(fld4,dim=2)
476             call oasis_abort(file=__FILE__,line=__LINE__)
477          endif
478       endif
479       if (present(fld5)) then
480          if (size(fld5,dim=2) /= size_fld1) then
481             write(nulprt,*) subname,estr,'fld5 size different than fld1 size ',size_fld1,size(fld5,dim=2)
482             call oasis_abort(file=__FILE__,line=__LINE__)
483          endif
484       endif
485
486       do n = 1,prism_var(var_id)%num
487          if (present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
488             CALL oasis_put_worker(var_id,kstep,(fld1(:,n)),kinfo,(fld2(:,n)), &
489                  (fld3(:,n)),(fld4(:,n)),(fld5(:,n)),write_restart=lwrst,varnum=n)
490          elseif (.not.present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
491             CALL oasis_put_worker(var_id,kstep,(fld1(:,n)),kinfo,(fld2(:,n)), &
492                  (fld3(:,n)),(fld4(:,n)),write_restart=lwrst,varnum=n)
493          elseif (.not.present(fld5) .and. .not.present(fld4) .and. present(fld3) .and. present(fld2)) then
494             CALL oasis_put_worker(var_id,kstep,(fld1(:,n)),kinfo,(fld2(:,n)), &
495                  (fld3(:,n)),write_restart=lwrst,varnum=n)
496          elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. present(fld2)) then
497             CALL oasis_put_worker(var_id,kstep,(fld1(:,n)),kinfo,(fld2(:,n)), &
498                  write_restart=lwrst,varnum=n)
499          elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. .not.present(fld2)) then
500             CALL oasis_put_worker(var_id,kstep,(fld1(:,n)),kinfo,write_restart=lwrst,varnum=n)
501          else
502             WRITE(nulprt,*) subname,estr,' Wrong field array argument list in oasis_put'
503             call oasis_abort(file=__FILE__,line=__LINE__)
504          endif
505       enddo
506
507    else
508    ! treat data as 2d unbundled data
509
510       if (present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
511          CALL oasis_put_worker(var_id,kstep,PACK(fld1,mask=.true.),kinfo,PACK(fld2,mask=.true.), &
512               PACK(fld3,mask=.true.),PACK(fld4,mask=.true.),PACK(fld5,mask=.true.),write_restart=lwrst)
513       elseif (.not.present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
514          CALL oasis_put_worker(var_id,kstep,PACK(fld1,mask=.true.),kinfo,PACK(fld2,mask=.true.), &
515               PACK(fld3,mask=.true.),PACK(fld4,mask=.true.),write_restart=lwrst)
516       elseif (.not.present(fld5) .and. .not.present(fld4) .and. present(fld3) .and. present(fld2)) then
517          CALL oasis_put_worker(var_id,kstep,PACK(fld1,mask=.true.),kinfo,PACK(fld2,mask=.true.), &
518               PACK(fld3,mask=.true.),write_restart=lwrst)
519       elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. present(fld2)) then
520          CALL oasis_put_worker(var_id,kstep,PACK(fld1,mask=.true.),kinfo,PACK(fld2,mask=.true.), &
521               write_restart=lwrst)
522       elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. .not.present(fld2)) then
523          CALL oasis_put_worker(var_id,kstep,PACK(fld1,mask=.true.),kinfo,write_restart=lwrst)
524       else
525          WRITE(nulprt,*) subname,estr,' Wrong field array argument list in oasis_put'
526          call oasis_abort(file=__FILE__,line=__LINE__)
527       endif
528
529    endif
530
531    call oasis_debug_exit(subname)
532
533  END SUBROUTINE oasis_put_r28
534
535!-------------------------------------------------------------------
536!---------------------------------------------------------------------
537
538!> Send 8 byte real 2D bundled data
539
540  SUBROUTINE oasis_put_r38(var_id,kstep,fld1,kinfo, &
541    fld2, fld3, fld4, fld5, write_restart)
542
543    IMPLICIT none
544    !-------------------------------------
545    integer(kind=ip_i4_p) , intent(in) :: var_id      !< variable id
546    integer(kind=ip_i4_p) , intent(in) :: kstep       !< model time in seconds
547    real(kind=ip_double_p) :: fld1(:,:,:)             !< field data
548    integer(kind=ip_i4_p) , intent(out):: kinfo       !< return code
549    real(kind=ip_double_p), optional :: fld2(:,:,:)   !< higher order field data
550    real(kind=ip_double_p), optional :: fld3(:,:,:)   !< higher order field data
551    real(kind=ip_double_p), optional :: fld4(:,:,:)   !< higher order field data
552    real(kind=ip_double_p), optional :: fld5(:,:,:)   !< higher order field data
553    logical               , optional :: write_restart !< write restart now
554    !-------------------------------------
555    logical :: lwrst
556    integer(kind=ip_i4_p) :: n, size_fld1
557    character(len=*),parameter :: subname = '(oasis_put_r38)'
558    !-------------------------------------
559
560    call oasis_debug_enter(subname)
561    kinfo = OASIS_OK
562    if (.not. oasis_coupled) then
563       call oasis_debug_exit(subname)
564       return
565    endif
566
567    if (present(write_restart)) then
568       lwrst = write_restart
569    else
570       lwrst = .false.
571    endif
572
573    if (prism_var(var_id)%num > 1) then
574    ! treat data as 1d bundled data
575
576       if (size(fld1,dim=3) /= prism_var(var_id)%num) then
577          write(nulprt,*) subname,estr,'called for variable ',trim(prism_var(var_id)%name)
578          write(nulprt,*) subname,estr,'expecting bundled field with num = ',prism_var(var_id)%num
579          write(nulprt,*) subname,estr,'passing in field with incorrect 3rd dim size = ',size(fld1,dim=3)
580          call oasis_abort(file=__FILE__,line=__LINE__)
581       endif
582
583       size_fld1 = size(fld1,dim=3)
584       if (present(fld2)) then
585          if (size(fld2,dim=3) /= size_fld1) then
586             write(nulprt,*) subname,estr,'fld2 size different than fld1 size ',size_fld1,size(fld2,dim=3)
587             call oasis_abort(file=__FILE__,line=__LINE__)
588          endif
589       endif
590       if (present(fld3)) then
591          if (size(fld3,dim=3) /= size_fld1) then
592             write(nulprt,*) subname,estr,'fld3 size different than fld1 size ',size_fld1,size(fld3,dim=3)
593             call oasis_abort(file=__FILE__,line=__LINE__)
594          endif
595       endif
596       if (present(fld4)) then
597          if (size(fld4,dim=3) /= size_fld1) then
598             write(nulprt,*) subname,estr,'fld4 size different than fld1 size ',size_fld1,size(fld4,dim=3)
599             call oasis_abort(file=__FILE__,line=__LINE__)
600          endif
601       endif
602       if (present(fld5)) then
603          if (size(fld5,dim=3) /= size_fld1) then
604             write(nulprt,*) subname,estr,'fld5 size different than fld1 size ',size_fld1,size(fld5,dim=3)
605             call oasis_abort(file=__FILE__,line=__LINE__)
606          endif
607       endif
608
609       do n = 1,prism_var(var_id)%num
610          if (present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
611             CALL oasis_put_worker(var_id,kstep,PACK(fld1(:,:,n),mask=.true.),kinfo,PACK(fld2(:,:,n),mask=.true.), &
612                  PACK(fld3(:,:,n),mask=.true.),PACK(fld4(:,:,n),mask=.true.),PACK(fld5(:,:,n),mask=.true.), &
613                  write_restart=lwrst,varnum=n)
614          elseif (.not.present(fld5) .and. present(fld4) .and. present(fld3) .and. present(fld2)) then
615             CALL oasis_put_worker(var_id,kstep,PACK(fld1(:,:,n),mask=.true.),kinfo,PACK(fld2(:,:,n),mask=.true.), &
616                  PACK(fld3(:,:,n),mask=.true.),PACK(fld4(:,:,n),mask=.true.),write_restart=lwrst,varnum=n)
617          elseif (.not.present(fld5) .and. .not.present(fld4) .and. present(fld3) .and. present(fld2)) then
618             CALL oasis_put_worker(var_id,kstep,PACK(fld1(:,:,n),mask=.true.),kinfo,PACK(fld2(:,:,n),mask=.true.), &
619                  PACK(fld3(:,:,n),mask=.true.),write_restart=lwrst,varnum=n)
620          elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. present(fld2)) then
621             CALL oasis_put_worker(var_id,kstep,PACK(fld1(:,:,n),mask=.true.),kinfo,PACK(fld2(:,:,n),mask=.true.), &
622                  write_restart=lwrst,varnum=n)
623          elseif (.not.present(fld5) .and. .not.present(fld4) .and. .not.present(fld3) .and. .not.present(fld2)) then
624             CALL oasis_put_worker(var_id,kstep,PACK(fld1(:,:,n),mask=.true.),kinfo,write_restart=lwrst,varnum=n)
625          else
626             WRITE(nulprt,*) subname,estr,' Wrong field array argument list in oasis_put'
627             call oasis_abort(file=__FILE__,line=__LINE__)
628          endif
629       enddo
630
631    else
632       WRITE(nulprt,*) subname,estr,' Dimension sizes incorrect'
633       call oasis_abort(file=__FILE__,line=__LINE__)
634
635    endif
636
637    call oasis_debug_exit(subname)
638
639  END SUBROUTINE oasis_put_r38
640
641!-------------------------------------------------------------------
642!---------------------------------------------------------------------
643!> Send worker routine puts 8 byte real 1D data
644
645  SUBROUTINE oasis_put_worker(var_id,kstep,fld1,kinfo, &
646    fld2, fld3, fld4, fld5, write_restart, varnum)
647
648    IMPLICIT none
649    !-------------------------------------
650    integer(kind=ip_i4_p) , intent(in) :: var_id      !< variable id
651    integer(kind=ip_i4_p) , intent(in) :: kstep       !< model time in seconds
652    real(kind=ip_double_p)             :: fld1(:)     !< field data
653    integer(kind=ip_i4_p) , intent(out):: kinfo       !< return code
654    real(kind=ip_double_p), optional :: fld2(:)       !< higher order field data
655    real(kind=ip_double_p), optional :: fld3(:)       !< higher order field data
656    real(kind=ip_double_p), optional :: fld4(:)       !< higher order field data
657    real(kind=ip_double_p), optional :: fld5(:)       !< higher order field data
658    logical               , optional :: write_restart !< write restart now
659    integer(kind=ip_i4_p) , optional :: varnum        !< varnum in bundled field
660    !-------------------------------------
661    integer(kind=ip_i4_p) :: nfld,ncpl
662    integer(kind=ip_i4_p) :: ns,nsx
663    integer(kind=ip_i4_p) :: n
664    integer(kind=ip_i4_p) :: lvarnum
665    logical :: a2on, a3on, a4on, a5on
666    logical :: lwrst
667    character(len=*),parameter :: subname = '(oasis_put_worker)'
668    !-------------------------------------
669
670    call oasis_debug_enter(subname)
671    kinfo = OASIS_OK
672    if (.not. oasis_coupled) then
673       call oasis_debug_exit(subname)
674       return
675    endif
676
677    if (.not. enddef_called) then
678       write(nulprt,*) subname,estr,'called before oasis_enddef'
679       call oasis_abort(file=__FILE__,line=__LINE__)
680    endif
681
682    if (var_id == OASIS_Var_Uncpl) then
683       write(nulprt,*) subname,estr,'oasis_put is called for a variable not in namcouple'
684       call oasis_abort(file=__FILE__,line=__LINE__)
685       call oasis_debug_exit(subname)
686       return
687    endif
688
689    if (var_id < 1 .or. var_id > prism_nvar) then
690       write(nulprt,*) subname,estr,'oasis_put is called for a variable not defined'
691       call oasis_abort(file=__FILE__,line=__LINE__)
692       call oasis_debug_exit(subname)
693       return
694    endif
695
696    if (present(write_restart)) then
697       lwrst = write_restart
698    else
699       lwrst = .false.
700    endif
701
702    if (present(varnum)) then
703       lvarnum = varnum
704    else
705       lvarnum = 1
706    endif
707
708    nfld = var_id
709    ncpl  = prism_var(nfld)%ncpl
710
711    if (ncpl <= 0) then
712       if (OASIS_debug >= 15) write(nulprt,*) subname,' variable not coupled ',&
713                              trim(prism_var(nfld)%name)
714       call oasis_debug_exit(subname)
715       return
716    endif
717
718    ns = size(fld1,dim=1)
719
720    a2on = .false.
721    a3on = .false.
722    a4on = .false.
723    a5on = .false.
724
725    if (present(fld2)) then
726       a2on = .true.
727       nsx = size(fld2,dim=1)
728       if (nsx /= ns) then
729          write(nulprt,*) subname,estr,'fld2 size does not match fld ', &
730                          trim(prism_var(nfld)%name)
731          call oasis_abort(file=__FILE__,line=__LINE__)
732       endif
733    endif
734
735    if (present(fld3)) then
736       a3on = .true.
737       nsx = size(fld3,dim=1)
738       if (nsx /= ns) then
739          write(nulprt,*) subname,estr,'fld3 size does not match fld ', &
740                          trim(prism_var(nfld)%name)
741          call oasis_abort(file=__FILE__,line=__LINE__)
742       endif
743    endif
744
745    if (present(fld4)) then
746       a4on = .true.
747       nsx = size(fld4,dim=1)
748       if (nsx /= ns) then
749          write(nulprt,*) subname,estr,'fld4 size does not match fld ', &
750                          trim(prism_var(nfld)%name)
751          call oasis_abort(file=__FILE__,line=__LINE__)
752       endif
753    endif
754
755    if (present(fld5)) then
756       a5on = .true.
757       nsx = size(fld5,dim=1)
758       if (nsx /= ns) then
759          write(nulprt,*) subname,estr,'fld5 size does not match fld ', &
760                          trim(prism_var(nfld)%name)
761          call oasis_abort(file=__FILE__,line=__LINE__)
762       endif
763    endif
764
765    IF ((.NOT. a2on) .AND. (.NOT. a3on) .AND. (.NOT. a4on) .AND. (.NOT. a5on)) THEN
766        CALL oasis_advance_run(OASIS_Out,nfld,kstep,kinfo,&
767                               array1din=fld1,readrest=.FALSE.,writrest=lwrst,varnum=lvarnum)
768    ELSE IF (a2on .AND. (.NOT. a3on) .AND. (.NOT. a4on) .AND. (.NOT. a5on)) THEN
769        CALL oasis_advance_run(OASIS_Out,nfld,kstep,kinfo,&
770                               array1din=fld1,readrest=.FALSE.,&
771                               a2on=a2on,array2=fld2,writrest=lwrst,varnum=lvarnum)
772    ELSE IF (a2on .AND. a3on .AND. (.NOT. a4on) .AND. (.NOT. a5on)) THEN
773        CALL oasis_advance_run(OASIS_Out,nfld,kstep,kinfo,&
774                               array1din= fld1,readrest=.FALSE.,&
775                               a2on=a2on,array2=fld2,&
776                               a3on=a3on,array3=fld3,writrest=lwrst,varnum=lvarnum)
777    ELSE IF (a2on .AND. a3on .AND. a4on .AND. (.NOT. a5on)) THEN
778        CALL oasis_advance_run(OASIS_Out,nfld,kstep,kinfo,&
779                               array1din=fld1,readrest=.FALSE.,&
780                               a2on=a2on,array2=fld2,&
781                               a3on=a3on,array3=fld3,&
782                               a4on=a4on,array4=fld4,writrest=lwrst,varnum=lvarnum)
783    ELSE IF (a2on .AND. a3on .AND. a4on .AND. a5on) THEN
784        CALL oasis_advance_run(OASIS_Out,nfld,kstep,kinfo,&
785                               array1din=fld1,readrest=.FALSE.,&
786                               a2on=a2on,array2=fld2,&
787                               a3on=a3on,array3=fld3,&
788                               a4on=a4on,array4=fld4,&
789                               a5on=a5on,array5=fld5,writrest=lwrst,varnum=lvarnum)
790    ELSE
791        WRITE(nulprt,*) subname,estr,' Wrong field array argument list in oasis_put'
792        call oasis_abort(file=__FILE__,line=__LINE__)
793    ENDIF
794
795    call oasis_debug_exit(subname)
796
797  END SUBROUTINE oasis_put_worker
798
799!-------------------------------------------------------------------
800!---------------------------------------------------------------------
801#ifndef __NO_4BYTE_REALS 
802
803!> Receive 4 byte real 1D data
804
805  SUBROUTINE oasis_get_r14(var_id,kstep,fld,kinfo)
806
807    IMPLICIT none
808    !-------------------------------------
809    integer(kind=ip_i4_p) , intent(in) :: var_id     !< variable id
810    integer(kind=ip_i4_p) , intent(in) :: kstep      !< model time in seconds
811    real(kind=ip_single_p), intent(inout) :: fld(:)  !< field data
812    integer(kind=ip_i4_p) , intent(out):: kinfo      !< return code
813    !-------------------------------------
814    integer(kind=ip_i4_p) :: ns
815    real(kind=ip_r8_p), allocatable :: array(:)
816    character(len=*),parameter :: subname = '(oasis_get_r14)'
817    !-------------------------------------
818
819    call oasis_debug_enter(subname)
820    kinfo = OASIS_OK
821    if (.not. oasis_coupled) then
822       call oasis_debug_exit(subname)
823       return
824    endif
825
826    if (prism_var(var_id)%num > 1) then
827       write(nulprt,*) subname,estr,'called for variable ',trim(prism_var(var_id)%name)
828       write(nulprt,*) subname,estr,'expecting bundled field with num = ',prism_var(var_id)%num
829       call oasis_abort(file=__FILE__,line=__LINE__)
830    endif
831
832    ns = size(fld,dim=1)
833    allocate(array(ns))
834
835    call oasis_get_worker(var_id,kstep,array,kinfo)
836
837    IF (kinfo /= OASIS_OK) THEN
838        fld(:) = REAL(array(:))
839    ENDIF
840
841    deallocate(array)
842
843    call oasis_debug_exit(subname)
844
845  END SUBROUTINE oasis_get_r14
846#endif
847
848!---------------------------------------------------------------------
849
850!> Receive 8 byte real 1D data
851
852  SUBROUTINE oasis_get_r18(var_id,kstep,fld,kinfo)
853
854    IMPLICIT none
855    !-------------------------------------
856    integer(kind=ip_i4_p) , intent(in) :: var_id     !< variable id
857    integer(kind=ip_i4_p) , intent(in) :: kstep      !< model time in seconds
858    real(kind=ip_r8_p)    , intent(inout) :: fld(:)  !< field data
859    integer(kind=ip_i4_p) , intent(out):: kinfo      !< return code
860    !-------------------------------------
861    character(len=*),parameter :: subname = '(oasis_get_r18)'
862    !-------------------------------------
863
864    call oasis_debug_enter(subname)
865    kinfo = OASIS_OK
866    if (.not. oasis_coupled) then
867       call oasis_debug_exit(subname)
868       return
869    endif
870
871    if (prism_var(var_id)%num > 1) then
872       write(nulprt,*) subname,estr,'called for variable ',trim(prism_var(var_id)%name)
873       write(nulprt,*) subname,estr,'expecting bundled field with num = ',prism_var(var_id)%num
874       call oasis_abort(file=__FILE__,line=__LINE__)
875    endif
876
877    call oasis_get_worker(var_id,kstep,fld,kinfo)
878
879    call oasis_debug_exit(subname)
880
881  END SUBROUTINE oasis_get_r18
882
883!---------------------------------------------------------------------
884#ifndef __NO_4BYTE_REALS
885
886!> Receive 4 byte real 2D data
887
888  SUBROUTINE oasis_get_r24(var_id,kstep,fld,kinfo)
889
890    IMPLICIT none
891    !-------------------------------------
892    integer(kind=ip_i4_p) , intent(in) :: var_id      !< variable id
893    integer(kind=ip_i4_p) , intent(in) :: kstep       !< model time in seconds
894    real(kind=ip_single_p), intent(inout) :: fld(:,:) !< field data
895    integer(kind=ip_i4_p) , intent(out):: kinfo       !< return code
896    !-------------------------------------
897    integer(kind=ip_i4_p) :: ns,nis,njs,n
898    REAL(kind=ip_r8_p), ALLOCATABLE :: array(:)
899    character(len=*),parameter :: subname = '(oasis_get_r24)'
900    !-------------------------------------
901
902    call oasis_debug_enter(subname)
903    kinfo = OASIS_OK
904    if (.not. oasis_coupled) then
905       call oasis_debug_exit(subname)
906       return
907    endif
908
909    if (prism_var(var_id)%num > 1) then
910    ! treat as 1d bundled data
911       if (size(fld,dim=2) /= prism_var(var_id)%num) then
912          write(nulprt,*) subname,estr,'called for variable ',trim(prism_var(var_id)%name)
913          write(nulprt,*) subname,estr,'expecting bundled field with num = ',prism_var(var_id)%num
914          write(nulprt,*) subname,estr,'passing in field with incorrect 2nd dim size = ',size(fld,dim=2)
915          call oasis_abort(file=__FILE__,line=__LINE__)
916       endif
917
918       nis = size(fld,dim=1)
919       ALLOCATE(array(nis))
920
921       do n = 1,prism_var(var_id)%num
922          kinfo = OASIS_OK
923          CALL oasis_get_worker(var_id,kstep,array,kinfo,varnum=n)
924          IF (kinfo /= OASIS_OK) THEN
925             fld(:,n) = REAL(array(:))
926          ENDIF
927       enddo
928
929       deallocate(array)
930
931    else
932    ! treat as 2d unbundled data
933
934       nis = size(fld,dim=1)
935       njs = size(fld,dim=2)
936       ns = nis*njs
937
938       ALLOCATE(array(ns))
939
940       CALL oasis_get_worker(var_id,kstep,array,kinfo)
941
942       IF (kinfo /= OASIS_OK) THEN
943          fld(:,:) = REAL(RESHAPE(array(:),SHAPE(fld)))
944       ENDIF
945
946       deallocate(array)
947
948    endif
949
950    call oasis_debug_exit(subname)
951
952  END SUBROUTINE oasis_get_r24
953#endif
954
955!---------------------------------------------------------------------
956!---------------------------------------------------------------------
957#ifndef __NO_4BYTE_REALS
958
959!> Receive 4 byte real 2D bundled data
960
961  SUBROUTINE oasis_get_r34(var_id,kstep,fld,kinfo)
962
963    IMPLICIT none
964    !-------------------------------------
965    integer(kind=ip_i4_p) , intent(in) :: var_id      !< variable id
966    integer(kind=ip_i4_p) , intent(in) :: kstep       !< model time in seconds
967    real(kind=ip_single_p), intent(inout) :: fld(:,:,:) !< field data
968    integer(kind=ip_i4_p) , intent(out):: kinfo       !< return code
969    !-------------------------------------
970    integer(kind=ip_i4_p) :: ns,nis,njs,n
971    REAL(kind=ip_r8_p), ALLOCATABLE :: array(:)
972    character(len=*),parameter :: subname = '(oasis_get_r34)'
973    !-------------------------------------
974
975    call oasis_debug_enter(subname)
976    kinfo = OASIS_OK
977    if (.not. oasis_coupled) then
978       call oasis_debug_exit(subname)
979       return
980    endif
981
982    if (prism_var(var_id)%num > 1) then
983    ! treat as 2d bundled data
984       if (size(fld,dim=3) /= prism_var(var_id)%num) then
985          write(nulprt,*) subname,estr,'called for variable ',trim(prism_var(var_id)%name)
986          write(nulprt,*) subname,estr,'expecting bundled field with num = ',prism_var(var_id)%num
987          write(nulprt,*) subname,estr,'passing in field with incorrect 3rd dim size = ',size(fld,dim=3)
988          call oasis_abort(file=__FILE__,line=__LINE__)
989       endif
990
991       nis = size(fld,dim=1)
992       njs = size(fld,dim=2)
993       ns = nis*njs
994
995       ALLOCATE(array(ns))
996
997       do n = 1,prism_var(var_id)%num
998          kinfo = OASIS_OK
999          CALL oasis_get_worker(var_id,kstep,array,kinfo,varnum=n)
1000          IF (kinfo /= OASIS_OK) THEN
1001             fld(:,:,n) = REAL(RESHAPE(array(:),SHAPE(fld(:,:,n))))
1002          ENDIF
1003       enddo
1004
1005       deallocate(array)
1006
1007    else
1008
1009       WRITE(nulprt,*) subname,estr,' Dimension sizes incorrect'
1010       call oasis_abort(file=__FILE__,line=__LINE__)
1011
1012    endif
1013
1014    call oasis_debug_exit(subname)
1015
1016  END SUBROUTINE oasis_get_r34
1017#endif
1018
1019!---------------------------------------------------------------------
1020
1021!> Receive 8 byte real 2D data
1022
1023  SUBROUTINE oasis_get_r28(var_id,kstep,fld,kinfo)
1024
1025    IMPLICIT none
1026    !-------------------------------------
1027    integer(kind=ip_i4_p) , intent(in) :: var_id      !< variable id
1028    integer(kind=ip_i4_p) , intent(in) :: kstep       !< model time in seconds
1029    real(kind=ip_double_p), intent(inout) :: fld(:,:) !< field data
1030    integer(kind=ip_i4_p) , intent(out):: kinfo       !< return code
1031    !-------------------------------------
1032    integer(kind=ip_i4_p) :: ns,nis,njs,n
1033    REAL(kind=ip_r8_p), ALLOCATABLE :: array(:)
1034    character(len=*),parameter :: subname = '(oasis_get_r28)'
1035    !-------------------------------------
1036
1037    call oasis_debug_enter(subname)
1038    kinfo = OASIS_OK
1039    if (.not. oasis_coupled) then
1040       call oasis_debug_exit(subname)
1041       return
1042    endif
1043
1044    if (prism_var(var_id)%num > 1) then
1045    ! treat as 1d bundled data
1046       if (size(fld,dim=2) /= prism_var(var_id)%num) then
1047          write(nulprt,*) subname,estr,'called for variable ',trim(prism_var(var_id)%name)
1048          write(nulprt,*) subname,estr,'expecting bundled field with num = ',prism_var(var_id)%num
1049          write(nulprt,*) subname,estr,'passing in field with incorrect 2nd dim size = ',size(fld,dim=2)
1050          call oasis_abort(file=__FILE__,line=__LINE__)
1051       endif
1052
1053       nis = size(fld,dim=1)
1054       ALLOCATE(array(nis))
1055
1056       do n = 1,prism_var(var_id)%num
1057          kinfo = OASIS_OK
1058          CALL oasis_get_worker(var_id,kstep,array,kinfo,varnum=n)
1059          IF (kinfo /= OASIS_OK) THEN
1060             fld(:,n) = array(:)
1061          ENDIF
1062       enddo
1063
1064       deallocate(array)
1065
1066    else
1067    ! treat as 2d unbundled data
1068
1069       nis = size(fld,dim=1)
1070       njs = size(fld,dim=2)
1071       ns = nis*njs
1072
1073       ALLOCATE(array(ns))
1074
1075       CALL oasis_get_worker(var_id,kstep,array,kinfo)
1076
1077       IF (kinfo /= OASIS_OK) THEN
1078          fld(:,:) = RESHAPE(array(:),SHAPE(fld))
1079       ENDIF
1080
1081       deallocate(array)
1082    endif
1083
1084    call oasis_debug_exit(subname)
1085
1086  END SUBROUTINE oasis_get_r28
1087
1088!-------------------------------------------------------------------
1089!---------------------------------------------------------------------
1090
1091!> Receive 8 byte real 2D bundled data
1092
1093  SUBROUTINE oasis_get_r38(var_id,kstep,fld,kinfo)
1094
1095    IMPLICIT none
1096    !-------------------------------------
1097    integer(kind=ip_i4_p) , intent(in) :: var_id      !< variable id
1098    integer(kind=ip_i4_p) , intent(in) :: kstep       !< model time in seconds
1099    real(kind=ip_double_p), intent(inout) :: fld(:,:,:) !< field data
1100    integer(kind=ip_i4_p) , intent(out):: kinfo       !< return code
1101    !-------------------------------------
1102    integer(kind=ip_i4_p) :: ns,nis,njs,n
1103    REAL(kind=ip_r8_p), ALLOCATABLE :: array(:)
1104    character(len=*),parameter :: subname = '(oasis_get_r38)'
1105    !-------------------------------------
1106
1107    call oasis_debug_enter(subname)
1108    kinfo = OASIS_OK
1109    if (.not. oasis_coupled) then
1110       call oasis_debug_exit(subname)
1111       return
1112    endif
1113
1114    if (prism_var(var_id)%num > 1) then
1115    ! treat as 2d bundled data
1116       if (size(fld,dim=3) /= prism_var(var_id)%num) then
1117          write(nulprt,*) subname,estr,'called for variable ',trim(prism_var(var_id)%name)
1118          write(nulprt,*) subname,estr,'expecting bundled field with num = ',prism_var(var_id)%num
1119          write(nulprt,*) subname,estr,'passing in field with incorrect 3rd dim size = ',size(fld,dim=3)
1120          call oasis_abort(file=__FILE__,line=__LINE__)
1121       endif
1122
1123       nis = size(fld,dim=1)
1124       njs = size(fld,dim=2)
1125       ns = nis*njs
1126
1127       ALLOCATE(array(ns))
1128
1129       do n = 1,prism_var(var_id)%num
1130          kinfo = OASIS_OK
1131          CALL oasis_get_worker(var_id,kstep,array,kinfo,varnum=n)
1132          IF (kinfo /= OASIS_OK) THEN
1133             fld(:,:,n) = RESHAPE(array(:),SHAPE(fld(:,:,n)))
1134          ENDIF
1135       enddo
1136
1137       deallocate(array)
1138
1139    else
1140       WRITE(nulprt,*) subname,estr,' Dimension sizes incorrect'
1141       call oasis_abort(file=__FILE__,line=__LINE__)
1142
1143    endif
1144
1145    call oasis_debug_exit(subname)
1146
1147  END SUBROUTINE oasis_get_r38
1148
1149!-------------------------------------------------------------------
1150!> Receive subroutine that actually does the work on 8 byte 1D data
1151
1152  SUBROUTINE oasis_get_worker(var_id,kstep,fld,kinfo,varnum)
1153
1154    IMPLICIT none
1155    !-------------------------------------
1156    integer(kind=ip_i4_p) , intent(in) :: var_id     !< variable id
1157    integer(kind=ip_i4_p) , intent(in) :: kstep      !< model time in seconds
1158    real(kind=ip_double_p), intent(inout) :: fld(:)  !< field data
1159    integer(kind=ip_i4_p) , intent(out):: kinfo      !< return code
1160    integer(kind=ip_i4_p) , optional   :: varnum     !< variable num in bundled field
1161    !-------------------------------------
1162    integer(kind=ip_i4_p) :: nfld,ncpl
1163    integer(kind=ip_i4_p) :: lvarnum
1164    character(len=*),parameter :: subname = '(oasis_get_worker)'
1165    !-------------------------------------
1166
1167    call oasis_debug_enter(subname)
1168    kinfo = OASIS_OK
1169    if (.not. oasis_coupled) then
1170       call oasis_debug_exit(subname)
1171       return
1172    endif
1173
1174    if (.not. enddef_called) then
1175       write(nulprt,*) subname,estr,'called before oasis_enddef'
1176       call oasis_abort(file=__FILE__,line=__LINE__)
1177    endif
1178
1179    if (var_id == OASIS_Var_Uncpl) then
1180       write(nulprt,*) subname,estr,'oasis_get is called for a variable not in namcouple'
1181       write(nulprt,*) subname,' BE CAREFUL NOT TO USE IT !!!!!'
1182       call oasis_abort(file=__FILE__,line=__LINE__)
1183       call oasis_debug_exit(subname)
1184       return
1185    endif
1186
1187    if (var_id < 1 .or. var_id > prism_nvar) then
1188       write(nulprt,*) subname,estr,'oasis_get is called for a variable not defined'
1189       call oasis_abort(file=__FILE__,line=__LINE__)
1190       call oasis_debug_exit(subname)
1191       return
1192    endif
1193
1194    if (present(varnum)) then
1195       lvarnum = varnum
1196    else
1197       lvarnum = 1
1198    endif
1199
1200    nfld = var_id
1201    ncpl  = prism_var(nfld)%ncpl
1202
1203    if (ncpl <= 0) then
1204       if (OASIS_debug >= 15) write(nulprt,*) subname,' variable not coupled ',&
1205                              trim(prism_var(nfld)%name)
1206       call oasis_debug_exit(subname)
1207       return
1208    endif
1209
1210    CALL oasis_advance_run(OASIS_In,nfld,kstep,kinfo,array1dout=fld,readrest=.FALSE.,varnum=lvarnum)
1211
1212    call oasis_debug_exit(subname)
1213
1214  END SUBROUTINE oasis_get_worker
1215
1216!-------------------------------------------------------------------
1217
1218END MODULE mod_oasis_getput_interface
1219
Note: See TracBrowser for help on using the repository browser.