source: lmdz_wrf/WRFV3/external/atm_ocn/atm_comm_pom.F @ 1

Last change on this file since 1 was 1, checked in by lfita, 10 years ago
  • -- --- Opening of the WRF+LMDZ coupling repository --- -- -

WRF: version v3.3
LMDZ: version v1818

More details in:

File size: 16.4 KB
Line 
1      MODULE ATM_cc
2
3      USE CMP_COMM, ONLY: &
4
5     &   MPI_COMM_Atmos => COMM_local, &
6
7     &   Coupler_id, &
8     &   component_master_rank_local, &
9     &   process_rank_local, &
10     &   component_nprocs, &
11     &   ibuffer, &
12
13     &   MPI_INTEGER,MPI_STATUS_SIZE, &
14     &   kind_REAL,kind_alt_REAL, &
15     &   MPI_kind_REAL,MPI_kind_alt_REAL
16
17      implicit none
18
19      integer,parameter:: NSF=4, ND=2
20      real dtc,              &   !<- Coupling period
21     &     dta,              &   !<- AM time step ("physical")
22     &     dta2dtc              !<- AM time step / Coupling period
23      integer i_dtc2dta /100/   !<- Coupling period / AM time step
24      integer &!,dimension(ND)::
25     &ims,ime,jms,jme,its,ite,jts,jte,ids,idf,jds,jdf,  NGP
26      integer kms,kme,kts,kte,kds,kde
27      integer,parameter:: kind_R=kind_alt_REAL
28!     integer,parameter:: kind_tiling=kind_R
29      integer,parameter:: kind_sfcflux=kind_R, &
30     &                    kind_SST=kind_R, &
31     &                    kind_SLM=kind_R, &
32     &                    kind_lonlat=kind_R
33      integer MPI_kind_R, &
34     &MPI_kind_sfcflux,MPI_kind_SST,MPI_kind_SLM,MPI_kind_lonlat
35      integer n_ts(ND) /0,0/, gid
36      integer rc /5/
37      real,parameter:: &
38     &   SLM_OS_value=1.,  &!<-must be real open sea mask value in AM
39     &   unrealistically_low_SST=0.01,  &! <- must be unreal low but &=0.,
40                                       ! see interp. --- check!
41     &   unrealistically_low_SV=-1.E30, &
42                     ! <- must be negative unreal low surface flux
43                     ! or other surface value to be sent
44                     ! to Coupler, see Coupler code
45     &   unrealistically_low_SF=unrealistically_low_SV, & !<- same thing
46     &   unrealistically_low_SVp=0.99*unrealistically_low_SV
47
48      logical initialized /.false./
49      logical PHYS,zeroSF,nrmSF,sendSF,getSST
50
51      TYPE SST_ARRAY
52        real(kind=kind_SST),dimension(:,:),allocatable:: a
53      END TYPE SST_ARRAY
54      TYPE SF_ARRAY
55        real(kind=kind_sfcflux),dimension(:,:,:),allocatable:: a
56      END TYPE SF_ARRAY
57
58      TYPE (SST_ARRAY), dimension(ND):: SST_cc
59      TYPE (SF_ARRAY), dimension(ND):: sf
60
61      character*12 sgid
62
63!ontrols:
64      integer nunit_announce /6/, VerbLev /3/
65
66      SAVE
67
68      END MODULE ATM_cc
69!
70!***********************************************************************
71!
72      SUBROUTINE ATM_CMP_START(atm_comm)
73
74      USE ATM_cc
75
76      implicit none
77
78      integer Atmos_id /1/, Atmos_master_rank_local /0/
79      character*20 s
80      integer atm_comm
81!
82
83                      !<-id of OM as a component of the coupled system
84      call CMP_INIT(Atmos_id,1)
85                             !<-"flexibility level"
86      if (Coupler_id.ge.0) VerbLev=min(VerbLev,ibuffer(4))
87
88      call CMP_INTRO(Atmos_master_rank_local)
89
90      initialized=.true.
91
92      write(s,'(i2)') VerbLev
93      call ATM_ANNOUNCE('back from CMP_INTRO, VerbLev='//s,2)
94
95      if (kind_R.eq.kind_REAL) then
96        MPI_kind_R=MPI_kind_REAL
97      else
98        MPI_kind_R=MPI_kind_alt_REAL
99      end if
100      if (kind_sfcflux.eq.kind_REAL) then
101        MPI_kind_sfcflux=MPI_kind_REAL
102      else
103        MPI_kind_sfcflux=MPI_kind_alt_REAL
104      end if
105      if (kind_SST.eq.kind_REAL) then
106        MPI_kind_SST=MPI_kind_REAL
107      else
108        MPI_kind_SST=MPI_kind_alt_REAL
109      end if
110      if (kind_SLM.eq.kind_REAL) then
111        MPI_kind_SLM=MPI_kind_REAL
112      else
113        MPI_kind_SLM=MPI_kind_alt_REAL
114      end if
115      if (kind_lonlat.eq.kind_REAL) then
116        MPI_kind_lonlat=MPI_kind_REAL
117      else
118        MPI_kind_lonlat=MPI_kind_alt_REAL
119      end if
120      atm_comm=MPI_COMM_Atmos
121      return
122      END
123!
124!***********************************************************************
125!
126      SUBROUTINE ATM_INIT_CHECK(s)
127
128      USE ATM_cc, ONLY: initialized,rc
129
130      implicit none
131
132      character*(*) s
133
134      if (.not. initialized) call GLOB_ABORT(1,s,rc)
135
136      return
137      END
138!
139!***********************************************************************
140!
141      subroutine ATM_TSTEP_INIT(NTSD,NPHS,gid_,dta_, &
142     &ids_,idf_,jds_,jdf_,its_,ite_,jts_,jte_,ims_,ime_,jms_,jme_, &
143       !<-"domain"         !<-"tile"           !<-"memory" (tile+halo)
144     &kds_,kde_,kts_,kte_,kms_,kme_, &
145     &HLON,HLAT,VLON,VLAT, &
146     &SLM, &
147     &i_parent_start,j_parent_start)
148
149      USE ATM_cc
150
151      implicit none
152
153      integer NTSD,NPHS,gid_
154      real dta_
155      integer ids_,idf_,jds_,jdf_,its_,ite_,jts_,jte_, &
156     &ims_,ime_,jms_,jme_,kds_,kde_,kts_,kte_,kms_,kme_
157      real(kind=kind_lonlat),dimension(ims_:ime_,jms_:jme_):: &
158     &HLON,HLAT,VLON,VLAT
159      real(kind=kind_SLM),dimension(ims_:ime_,jms_:jme_):: SLM
160      integer i_parent_start,j_parent_start
161
162      integer KDT,buf(2) /0,0/
163      character*24 s
164      character*80 s1
165
166      SAVE
167!
168
169      gid=gid_
170      call GLOB_ABORT((gid-1)*(gid-2), &
171     &'Abort: in ATM_TSTEP_INIT gid is neither 1 nor 2',rc)
172      KDT=NTSD/NPHS+1
173      PHYS=MOD(NTSD,NPHS).eq.0 ! .and. gid.eq.1 <-removed to bring MG in
174      dta=dta_
175
176      write(s1,'("gid=",i1," NTSD=",i5," NPHS=",i3," KDT=",i5,'// &
177     &'" PHYS=",L1)') gid,NTSD,NPHS,KDT,PHYS
178      call ATM_ANNOUNCE('ATM_TSTEP_INIT entered: '//trim(s1),3)
179
180!     IF (n_ts.eq.-1 .and. PHYS) THEN
181!       PHYS=.false.
182!       n_ts=0   ! init. value must be -1 . But if PHYS does not need
183!                ! this correction, init. value must be 0 (whereas this
184!                ! IF statement may stay)
185!     END IF
186      if (.not.PHYS) then
187        zeroSF=.false.
188        nrmSF=.false.
189        sendSF=.false.
190        RETURN
191      end if
192
193      n_ts(gid)=n_ts(gid)+1  ! init. value must be 0   ***0***
194      write(s,'(2i8)') KDT,n_ts(gid)
195      write(sgid,'(" grid id = ",i1)') gid
196      call ATM_ANNOUNCE('ATM_TSTEP_INIT working:'// &
197     &sgid//'; KDT, n_ts: '//s,3)
198      call GLOB_ABORT(KDT-n_ts(gid), &
199     &'Abort: in ATM_TSTEP_INIT KDT, n_ts(gid) differ '//s,rc)
200
201      call ATM_RECVdtc
202
203      zeroSF=((n_ts(gid)-1)/i_dtc2dta)*i_dtc2dta .eq. n_ts(gid)-1
204      nrmSF=(n_ts(gid)/i_dtc2dta)*i_dtc2dta .eq. n_ts(gid)
205      sendSF=(n_ts(gid)/i_dtc2dta)*i_dtc2dta .eq. n_ts(gid)
206                                    !<-check, this depends
207                                    ! on where ATM_SENDFLUXES is called.
208                                    ! MOD(n_ts,i_dtc2dta).eq.0 should
209                                    ! be good for calling it after
210                                    ! ATM_DOFLUXES at the same t.s.
211
212      ids=ids_
213      idf=idf_
214      jds=jds_
215      jdf=jdf_
216      its=its_
217      ite=ite_
218      jts=jts_
219      jte=jte_
220      ims=ims_
221      ime=ime_
222      jms=jms_
223      jme=jme_
224
225      kds=kds_
226      kde=kde_
227      kts=kts_
228      kms=kms_
229      kme=kme_
230      kte=kte_
231
232      NGP=(idf-ids+1)*(jdf-jds+1)
233
234      call ATM_ANNOUNCE('ATM_TSTEP_INIT to allocate sf, SST_cc',3)
235
236      IF (n_ts(gid).eq.1) THEN
237        allocate(sf(gid)%a(ims:ime,jms:jme,NSF))
238        allocate(SST_cc(gid)%a(ims:ime,jms:jme))
239      END IF
240
241      if (gid.eq.2) then
242        write(s,'(2i8)') i_parent_start,j_parent_start
243        if (zeroSF) then
244          buf(1)=i_parent_start
245          buf(2)=j_parent_start
246          call CMP_INTEGER_SEND(buf,2)
247          call ATM_ANNOUNCE( &
248     &    'ATM_TSTEP_INIT: i_parent_start, j_parent_start sent '//s,3)
249        else
250          call GLOB_ABORT(abs(i_parent_start-buf(1))+abs(j_parent_start- &
251     &    buf(2)),'NESTED GRID MOVED DURING C TIME STEP: ABORTED '// &
252     &    s,rc)
253        end if
254      end if
255
256      CALL ATM_SENDGRIDS(HLON,HLAT,VLON,VLAT)
257
258      CALL ATM_SENDSLM(SLM)
259
260      if (VerbLev.ge.2) print*,'AM: ATM_TSTEP_INIT: returning ',gid, &
261     &n_ts(gid),ids,idf,jds,jdf,its,ite,jts,jte,ims,ime,jms,jme,NGP,NSF
262
263      RETURN
264      end
265!
266!***********************************************************************
267!
268      SUBROUTINE ATM_RECVdtc
269
270      USE ATM_cc
271
272      implicit none
273
274      real(kind=kind_R) buf(1),dtc2dta
275      integer ierr,i
276      logical first/.true./
277      character*20 s
278      SAVE
279!
280
281      write(s,'(1pe20.12)') dta
282      call ATM_ANNOUNCE('ATM_RECVdtc: AM time step dta='//s,3)
283
284      IF (first) THEN
285        call ATM_ANNOUNCE( &
286     &  'ATM_RECVdtc: to receive C time step; AM time step dta='//s,2)
287
288        call CMP_gnr_RECV(buf,1,MPI_kind_R)
289
290        call MPI_BCAST(buf,1,MPI_kind_R, &
291     &  component_master_rank_local,MPI_COMM_Atmos,ierr)
292        call ATM_ANNOUNCE('ATM_RECVdtc: C time step broadcast',2)
293        dtc=buf(1)
294
295        if (Coupler_id.lt.0) then
296          if (gid.eq.1) then
297            dtc=dta*2            ! just having in mind that with gid=1
298          else                   ! dta value is 5 times its value with
299            dtc=dta*10           ! gid=2 (at this moment, 270s and 54s
300          end if                 ! respectively)
301          write(s,'(1pe20.12)') dtc
302          call ATM_ANNOUNCE('ATM_RECVdtc: C time step assigned '// &
303     &    trim(s)//' : standalone mode',2)
304        else
305          write(s,'(1pe20.12)') buf
306          call ATM_ANNOUNCE( &
307     &    'ATM_RECVdtc: C time step dtc='//s//' received',2)
308        end if
309      END IF
310
311      dtc2dta=dtc/dta
312      i_dtc2dta=nint(dtc2dta)
313      if (abs(i_dtc2dta-dtc2dta).gt.1.E-5) call GLOB_ABORT(1, &
314     &'AM: ABORTED: dtc is not a multiple of dta',1)
315
316      i=3
317      if (n_ts(gid).eq.1) i=2
318      if (i_dtc2dta.eq.0) then
319        i_dtc2dta=4
320        call ATM_ANNOUNCE('ratio of C/AM time steps =0, assigned 4 .'// &
321     &  ' This should only occur in standalone mode and ONLY IF dtc '// &
322     &  'HAS NOT BEEN ASSIGNED A POSITIVE VALUE: ** ATTENTION **',i)
323      else
324        write(s,'(i2)') i_dtc2dta
325        call ATM_ANNOUNCE('ratio of C/AM time steps: '//trim(s),i)
326      end if
327
328      dta2dtc=1./i_dtc2dta
329
330      first=.false.
331
332      RETURN
333      END
334!
335!***********************************************************************
336!
337      SUBROUTINE ATM_SENDGRIDS(HLON,HLAT,VLON,VLAT)
338
339      USE ATM_cc
340
341      implicit none
342
343      real(kind=kind_lonlat),dimension(ims:ime,jms:jme):: &
344     &HLON,HLAT,VLON,VLAT
345
346      real(kind=kind_lonlat),dimension(ids:idf,jds:jdf):: &
347     &ALONt,ALATt,ALONv,ALATv
348
349      integer buf(2)
350!
351
352!     IF (gid.ne.1) RETURN ! only "parent grid" dim. and coor. are sent
353
354      IF (.not.PHYS .or. n_ts(gid).ne.1) RETURN
355     
356!temporarily excluded      if (Coupler_id.lt.0) return    !   <- standalone mode
357
358      buf(1)=idf-ids+1
359      buf(2)=jdf-jds+1
360      call ATM_ANNOUNCE('to send grid dimensions,'//sgid,1)
361      call CMP_INTEGER_SEND(buf,2)
362      call ATM_ANNOUNCE('grid dimensions sent,'//sgid,1)
363
364!     IF (gid.eq.1) THEN    !  only "parent grid" coordinates are sent
365
366        call ASSEMBLE(ALONt,HLON,kind_lonlat)
367        call ASSEMBLE(ALATt,HLAT,kind_lonlat)
368        call ASSEMBLE(ALONv,VLON,kind_lonlat)
369        call ASSEMBLE(ALATv,VLAT,kind_lonlat)
370
371        call ATM_ANNOUNCE('(BP) to send grid arrays (4 MPI calls)',2)
372
373        call CMP_gnr_SEND(ALONt,NGP,MPI_kind_lonlat)
374        call CMP_gnr_SEND(ALATt,NGP,MPI_kind_lonlat)
375        call CMP_gnr_SEND(ALONv,NGP,MPI_kind_lonlat)
376        call CMP_gnr_SEND(ALATv,NGP,MPI_kind_lonlat)
377
378        call ATM_ANNOUNCE('the 4 grid arrays sent',1)
379
380!     END IF
381
382      call ATM_ANNOUNCE('(BP) ATM_SENDGRIDS: returning',2)
383
384      return
385      END
386!
387!***********************************************************************
388!
389      SUBROUTINE ATM_SENDSLM(SLM)
390
391      USE ATM_cc
392
393      implicit none
394
395      real(kind=kind_SLM),dimension(ims:ime,jms:jme):: SLM
396
397      real(kind=kind_SLM),dimension(ids:idf,jds:jdf):: SLM_g
398      integer buf(2)
399!
400
401!     IF (gid.ne.1) RETURN  !  only "parent grid" mask is sent
402      IF (.not.PHYS .or. n_ts(gid).ne.1) RETURN
403     
404!temporarily excluded      if (Coupler_id.lt.0) return    !   <- standalone mode
405
406      call ASSEMBLE(SLM_g,SLM,kind_SLM)
407
408      call ATM_ANNOUNCE('(BP) to send SLM',2)
409
410      call CMP_gnr_SEND(SLM_g,NGP,MPI_kind_SLM)
411      call CMP_gnr_SEND(SLM_g,NGP,MPI_kind_SLM)
412           ! Coupler requires as many copies of mask as there are grids
413
414      call ATM_ANNOUNCE('(BP) ATM_SENDSLM: returning',2)
415
416      return
417      END
418!
419!***********************************************************************
420!
421      SUBROUTINE ATM_GETSST(SST,SLM)
422
423      USE ATM_cc
424
425      implicit none
426
427      real(kind=kind_SST) SST(ims:ime,jms:jme)
428      real(kind=kind_SLM) SLM(ims:ime,jms:jme)
429
430      integer i,j
431      real(kind=kind_SST) SST_g(ids:idf,jds:jdf)
432!
433
434      IF (.not.PHYS) RETURN
435
436      call ATM_ANNOUNCE('ATM_GETSST entered (PHYS=.true.)',3)
437
438      getSST=((n_ts(gid)-1)/i_dtc2dta)*i_dtc2dta .eq. n_ts(gid)-1
439      if (getSST.neqv.zeroSF) then
440        call GLOB_ABORT(1,'getSST differs from zeroSF, which screws'// &
441     &  ' up the design for exchanges with C',rc)
442      end if
443
444      if (getSST) then
445        if (n_ts(gid).eq.1 .and. gid.eq.1) then
446          call ATM_ANNOUNCE('ATM_GETSST: to send ref. SST'//sgid,2)
447          call ASSEMBLE(SST_g,SST,kind_SST)
448          call CMP_gnr_SEND(SST_g,NGP,MPI_kind_SST)
449          call ATM_ANNOUNCE('ATM_GETSST: ref. SST sent'//sgid,2)
450        end if
451        call ATM_ANNOUNCE('ATM_GETSST: to receive SST',3)
452        call CMP_gnr_RECV(SST_g,NGP,MPI_kind_SST)
453        call DISASSEMBLE(SST_g,SST_cc(gid)%a,kind_SST)
454        call ATM_ANNOUNCE('ATM_GETSST: SST received',3)
455      end if
456     
457      if (Coupler_id.lt.0) return    !   <- standalone mode
458
459      do j=jts,jte
460      do i=its,ite
461        if (abs(SLM(i,j)-SLM_OS_value).lt.0.01) then
462                                  ! i.e. if it is OS (open sea) AMGP
463                                  !
464          if (SST_cc(gid)%a(i,j).gt.unrealistically_low_SST)  &
465                                          ! i.e. if there is a valid
466                                          ! result of interpolation from
467                                          ! OMG for this AMGP
468     &       SST(i,j)=SST_cc(gid)%a(i,j)
469        end if
470      end do
471      end do
472
473      return
474      END
475!
476!***********************************************************************
477!
478      SUBROUTINE ATM_DOFLUXES(TWBS,QWBS,RLWIN,RSWIN,RADOT,RSWOUT, &
479!    &USTAR,U10,V10,PINT,PREC)
480     &TX,TY,PINT,PREC)
481
482      USE ATM_cc
483
484      implicit none
485
486      real(kind=kind_sfcflux),dimension(ims:ime,jms:jme):: &
487     &TWBS,QWBS,RLWIN,RSWIN,RADOT,RSWOUT,TX,TY,PINT,PREC
488!    &TWBS,QWBS,RLWIN,RSWIN,RADOT,RSWOUT,USTAR,U10,V10,PINT,PREC
489!       Act. arg. for PINT is a 3d array - so this only is OK if
490!       Ps=Act.arg.(:,:.1) - actually, Ps=PINT(:,1,:)
491
492      real(kind=kind_sfcflux),dimension(ims:ime,jms:jme):: SWR,R
493      real dtainv
494!
495
496      IF (.not.PHYS) RETURN
497
498      call ATM_ANNOUNCE('ATM_DOFLUXES entered',3)
499
500      dtainv=1./dta
501
502      if (zeroSF) sf(gid)%a=0.
503
504      SWR=-RSWIN+RSWOUT          ! Check sign! here SWR is meant to be
505                                 ! positive upward
506
507!     R=SWR+RADOT-RLWIN          ! Check sign! here R (net radiation)
508                                 ! is meant to be positive upward
509
510      sf(gid)%a(:,:,1)=sf(gid)%a(:,:,1)-TWBS-QWBS+RADOT-RLWIN
511                                       ! -TWBS (-QWBS) is supposed to
512                                       ! be sensible (latent) heat flux,
513                                       ! positive upward
514      sf(gid)%a(:,:,2)=sf(gid)%a(:,:,2)+SWR
515
516      sf(gid)%a(:,:,3)=sf(gid)%a(:,:,3)-TX
517      sf(gid)%a(:,:,4)=sf(gid)%a(:,:,4)-TY
518                     ! <- signs for stress components are     changed
519                     ! so it is -stress
520
521      if (nrmSF) then
522        sf(gid)%a=sf(gid)%a*dta2dtc
523      end if
524
525      call ATM_ANNOUNCE('ATM_DOFLUXES to return',3)
526
527      return
528      END
529!
530!***********************************************************************
531!
532      SUBROUTINE ATM_SENDFLUXES
533
534      USE ATM_cc
535
536      implicit none
537
538      real(kind=kind_sfcflux) F(ids:idf,jds:jdf)
539      integer n
540!
541
542      if (.not.PHYS) RETURN
543
544      if (.not.sendSF) then
545        call ATM_ANNOUNCE( &
546     &  'ATM_SENDLUXES entered with PHYS but not sendSF: returning'// &
547     &  sgid,3)
548        RETURN
549      end if
550
551      call ATM_ANNOUNCE('In ATM_SENDLUXES'//sgid,3)
552
553      do n=1,NSF
554        call ASSEMBLE(F,sf(gid)%a(:,:,n),kind_sfcflux)
555        call CMP_gnr_SEND(F,NGP,MPI_kind_sfcflux)
556      end do
557
558      call ATM_ANNOUNCE('ATM_SENDFLUXES to return'//sgid,3)
559
560      return
561      END
562!
563!***********************************************************************
564!
565      SUBROUTINE ATM_ANNOUNCE(s,DbgLev)
566
567      USE ATM_cc, ONLY: nunit_announce,VerbLev,MPI_COMM_Atmos
568
569      implicit none
570
571      character*(*) s
572      integer DbgLev
573
574      integer ierr
575!
576      if (DbgLev.le.VerbLev) then
577        if (s(1:5).eq.'(BP) ') then
578          call MPI_BARRIER(MPI_COMM_Atmos,ierr)
579        end if
580        CALL CMP_ANNOUNCE(nunit_announce,'AM: '//s)
581      end if
582
583      return
584      END
Note: See TracBrowser for help on using the repository browser.