New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
bdyice.F90 in NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/BDY – NEMO

source: NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/BDY/bdyice.F90 @ 11071

Last change on this file since 11071 was 11071, checked in by girrmann, 5 years ago

dev_r10984_HPC-13 : step 2, remove unneeded communications, see #2285

  • Property svn:keywords set to Id
File size: 22.0 KB
Line 
1MODULE bdyice
2   !!======================================================================
3   !!                       ***  MODULE  bdyice  ***
4   !! Unstructured Open Boundary Cond. :  Open boundary conditions for sea-ice (SI3)
5   !!======================================================================
6   !!  History :  3.3  !  2010-09 (D. Storkey)  Original code
7   !!             3.4  !  2012-01 (C. Rousset)  add new sea ice model
8   !!             4.0  !  2018    (C. Rousset)  SI3 compatibility
9   !!----------------------------------------------------------------------
10#if defined key_si3
11   !!----------------------------------------------------------------------
12   !!   'key_si3'                                          SI3 sea ice model
13   !!----------------------------------------------------------------------
14   !!   bdy_ice        : Application of open boundaries to ice
15   !!   bdy_ice_frs    : Application of Flow Relaxation Scheme
16   !!----------------------------------------------------------------------
17   USE oce             ! ocean dynamics and tracers variables
18   USE ice             ! sea-ice: variables
19   USE icevar          ! sea-ice: operations
20   USE icecor          ! sea-ice: corrections
21   USE icectl          ! sea-ice: control prints
22   USE phycst          ! physical constant
23   USE eosbn2          ! equation of state
24   USE par_oce         ! ocean parameters
25   USE dom_oce         ! ocean space and time domain variables
26   USE sbc_oce         ! Surface boundary condition: ocean fields
27   USE bdy_oce         ! ocean open boundary conditions
28   !
29   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
30   USE in_out_manager  ! write to numout file
31   USE lib_mpp         ! distributed memory computing
32   USE lib_fortran     ! to use key_nosignedzero
33   USE timing          ! Timing
34
35   IMPLICIT NONE
36   PRIVATE
37
38   PUBLIC   bdy_ice     ! routine called in sbcmod
39   PUBLIC   bdy_ice_dyn ! routine called in icedyn_rhg_evp
40
41   !!----------------------------------------------------------------------
42   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
43   !! $Id$
44   !! Software governed by the CeCILL license (see ./LICENSE)
45   !!----------------------------------------------------------------------
46CONTAINS
47
48   SUBROUTINE bdy_ice( kt )
49      !!----------------------------------------------------------------------
50      !!                  ***  SUBROUTINE bdy_ice  ***
51      !!
52      !! ** Purpose : Apply open boundary conditions for sea ice
53      !!
54      !!----------------------------------------------------------------------
55      INTEGER, INTENT(in) ::   kt   ! Main time step counter
56      !
57      INTEGER ::   jbdy                               ! BDY set index
58      LOGICAL, DIMENSION(4)       :: llsend1, llrecv1   ! indicate how communications are to be carried out
59      !!----------------------------------------------------------------------
60      ! controls
61      IF( ln_timing    )   CALL timing_start('bdy_ice_thd')                                                            ! timing
62      IF( ln_icediachk )   CALL ice_cons_hsm(0,'bdy_ice_thd', rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft) ! conservation
63      !
64      CALL ice_var_glo2eqv
65      !
66      DO jbdy = 1, nb_bdy
67         !
68         SELECT CASE( cn_ice(jbdy) )
69         CASE('none')   ;   CYCLE
70         CASE('frs' )   ;   CALL bdy_ice_frs( idx_bdy(jbdy), dta_bdy(jbdy), kt, jbdy )
71         CASE DEFAULT
72            CALL ctl_stop( 'bdy_ice : unrecognised option for open boundaries for ice fields' )
73         END SELECT
74         !
75      END DO
76      !
77      ! Update bdy points
78      llsend1(:) = .false.
79      llrecv1(:) = .false.
80      DO jbdy = 1, nb_bdy
81         IF( cn_ice(jbdy) == 'frs' ) THEN
82            llsend1(:) = llsend1(:) .OR. lsend_bdyint(jbdy,1,:)   ! possibly every direction, T points
83            llrecv1(:) = llrecv1(:) .OR. lrecv_bdyint(jbdy,1,:)   ! possibly every direction, T points
84         END IF
85      END DO
86      IF( ANY(llsend1) .OR. ANY(llrecv1) ) THEN   ! if need to send/recv in at least one direction
87         ! exchange 3d arrays
88         CALL lbc_bdy_lnk_multi( 'bdyice', llsend1, llrecv1, a_i , 'T', 1., h_i , 'T', 1., h_s , 'T', 1. &
89              &                                            , oa_i, 'T', 1., a_ip, 'T', 1., v_ip, 'T', 1. &
90              &                                            , s_i , 'T', 1., t_su, 'T', 1., v_i , 'T', 1. &
91              &                                            , v_s , 'T', 1., sv_i, 'T', 1.                )
92         ! exchange 4d arrays
93         CALL lbc_bdy_lnk_multi( 'bdyice', llsend1, llrecv1, t_s , 'T', 1., e_s , 'T', 1. )   ! third dimension = 1
94         CALL lbc_bdy_lnk_multi( 'bdyice', llsend1, llrecv1, t_i , 'T', 1., e_i , 'T', 1. )   ! third dimension = jpk
95      END IF
96      !
97      CALL ice_cor( kt , 0 )      ! -- In case categories are out of bounds, do a remapping
98      !                           !    i.e. inputs have not the same ice thickness distribution (set by rn_himean)
99      !                           !         than the regional simulation
100      CALL ice_var_agg(1)
101      !
102      ! controls
103      IF( ln_icediachk )   CALL ice_cons_hsm(1,'bdy_ice_thd', rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft) ! conservation
104      IF( ln_icectl    )   CALL ice_prt     ( kt, iiceprt, jiceprt, 1, ' - ice thermo bdy - ' )                        ! prints
105      IF( ln_timing    )   CALL timing_stop ('bdy_ice_thd')                                                            ! timing
106      !
107   END SUBROUTINE bdy_ice
108
109
110   SUBROUTINE bdy_ice_frs( idx, dta, kt, jbdy )
111      !!------------------------------------------------------------------------------
112      !!                 ***  SUBROUTINE bdy_ice_frs  ***
113      !!                   
114      !! ** Purpose : Apply the Flow Relaxation Scheme for sea-ice fields
115      !!
116      !! Reference : Engedahl H., 1995: Use of the flow relaxation scheme in a three-
117      !!             dimensional baroclinic ocean model with realistic topography. Tellus, 365-382.
118      !!------------------------------------------------------------------------------
119      TYPE(OBC_INDEX), INTENT(in) ::   idx     ! OBC indices
120      TYPE(OBC_DATA),  INTENT(in) ::   dta     ! OBC external data
121      INTEGER,         INTENT(in) ::   kt      ! main time-step counter
122      INTEGER,         INTENT(in) ::   jbdy    ! BDY set index
123      !
124      INTEGER  ::   jpbound            ! 0 = incoming ice
125      !                                ! 1 = outgoing ice
126      INTEGER  ::   i_bdy, jgrd        ! dummy loop indices
127      INTEGER  ::   ji, jj, jk, jl, ib, jb
128      REAL(wp) ::   zwgt, zwgt1        ! local scalar
129      REAL(wp) ::   ztmelts, zdh
130      REAL(wp), POINTER  :: flagu, flagv              ! short cuts
131      !!------------------------------------------------------------------------------
132      !
133      jgrd = 1      ! Everything is at T-points here
134      !
135      DO jl = 1, jpl
136         DO i_bdy = 1, idx%nblenrim(jgrd)
137            ji    = idx%nbi(i_bdy,jgrd)
138            jj    = idx%nbj(i_bdy,jgrd)
139            zwgt  = idx%nbw(i_bdy,jgrd)
140            zwgt1 = 1.e0 - idx%nbw(i_bdy,jgrd)
141            a_i(ji,jj,jl) = ( a_i(ji,jj,jl) * zwgt1 + dta%a_i(i_bdy,jl) * zwgt ) * tmask(ji,jj,1)  ! Leads fraction
142            h_i(ji,jj,jl) = ( h_i(ji,jj,jl) * zwgt1 + dta%h_i(i_bdy,jl) * zwgt ) * tmask(ji,jj,1)  ! Ice depth
143            h_s(ji,jj,jl) = ( h_s(ji,jj,jl) * zwgt1 + dta%h_s(i_bdy,jl) * zwgt ) * tmask(ji,jj,1)  ! Snow depth
144
145            ! -----------------
146            ! Pathological case
147            ! -----------------
148            ! In case a) snow load would be in excess or b) ice is coming into a warmer environment that would lead to
149            ! very large transformation from snow to ice (see icethd_dh.F90)
150
151            ! Then, a) transfer the snow excess into the ice (different from icethd_dh)
152            zdh = MAX( 0._wp, ( rhos * h_s(ji,jj,jl) + ( rhoi - rau0 ) * h_i(ji,jj,jl) ) * r1_rau0 )
153            ! Or, b) transfer all the snow into ice (if incoming ice is likely to melt as it comes into a warmer environment)
154            !zdh = MAX( 0._wp, h_s(ji,jj,jl) * rhos / rhoi )
155
156            ! recompute h_i, h_s
157            h_i(ji,jj,jl) = MIN( hi_max(jl), h_i(ji,jj,jl) + zdh )
158            h_s(ji,jj,jl) = MAX( 0._wp, h_s(ji,jj,jl) - zdh * rhoi / rhos ) 
159
160         ENDDO
161      ENDDO
162
163      DO jl = 1, jpl
164         DO i_bdy = 1, idx%nblenrim(jgrd)
165            ji = idx%nbi(i_bdy,jgrd)
166            jj = idx%nbj(i_bdy,jgrd)
167            flagu => idx%flagu(i_bdy,jgrd)
168            flagv => idx%flagv(i_bdy,jgrd)
169            ! condition on ice thickness depends on the ice velocity
170            ! if velocity is outward (strictly), then ice thickness, volume... must be equal to adjacent values
171            jpbound = 0   ;   ib = ji   ;   jb = jj
172            !
173            IF( flagu ==  1. )   THEN
174               IF( ji+1 > jpi )   CYCLE
175               IF( u_ice(ji  ,jj  ) < 0. )   jpbound = 1 ; ib = ji+1
176            END IF
177            IF( flagu == -1. )   THEN
178               IF( ji-1 < 1   )   CYCLE
179               IF( u_ice(ji-1,jj  ) < 0. )   jpbound = 1 ; ib = ji-1
180            END IF
181            IF( flagv ==  1. )   THEN
182               IF( jj+1 > jpj )   CYCLE
183               IF( v_ice(ji  ,jj  ) < 0. )   jpbound = 1 ; jb = jj+1
184            END IF
185            IF( flagv == -1. )   THEN
186               IF( jj-1 < 1   )   CYCLE
187               IF( v_ice(ji  ,jj-1) < 0. )   jpbound = 1 ; jb = jj-1
188            END IF
189            !
190            IF( nn_ice_dta(jbdy) == 0 )   jpbound = 0 ; ib = ji ; jb = jj   ! case ice boundaries = initial conditions
191            !                                                               !      do not make state variables dependent on velocity
192            !
193            IF( a_i(ib,jb,jl) > 0._wp ) THEN   ! there is ice at the boundary
194               !
195               a_i(ji,jj,jl) = a_i(ib,jb,jl) ! concentration
196               h_i(ji,jj,jl) = h_i(ib,jb,jl) ! thickness ice
197               h_s(ji,jj,jl) = h_s(ib,jb,jl) ! thickness snw
198               !
199               SELECT CASE( jpbound )
200                  !
201               CASE( 0 )   ! velocity is inward
202                  !
203                  oa_i(ji,jj,  jl) = rn_ice_age(jbdy) * a_i(ji,jj,jl) ! age
204                  a_ip(ji,jj,  jl) = 0._wp                            ! pond concentration
205                  v_ip(ji,jj,  jl) = 0._wp                            ! pond volume
206                  t_su(ji,jj,  jl) = rn_ice_tem(jbdy)                 ! temperature surface
207                  t_s (ji,jj,:,jl) = rn_ice_tem(jbdy)                 ! temperature snw
208                  t_i (ji,jj,:,jl) = rn_ice_tem(jbdy)                 ! temperature ice
209                  s_i (ji,jj,  jl) = rn_ice_sal(jbdy)                 ! salinity
210                  sz_i(ji,jj,:,jl) = rn_ice_sal(jbdy)                 ! salinity profile
211                  !
212               CASE( 1 )   ! velocity is outward
213                  !
214                  oa_i(ji,jj,  jl) = oa_i(ib,jb,  jl) ! age
215                  a_ip(ji,jj,  jl) = a_ip(ib,jb,  jl) ! pond concentration
216                  v_ip(ji,jj,  jl) = v_ip(ib,jb,  jl) ! pond volume
217                  t_su(ji,jj,  jl) = t_su(ib,jb,  jl) ! temperature surface
218                  t_s (ji,jj,:,jl) = t_s (ib,jb,:,jl) ! temperature snw
219                  t_i (ji,jj,:,jl) = t_i (ib,jb,:,jl) ! temperature ice
220                  s_i (ji,jj,  jl) = s_i (ib,jb,  jl) ! salinity
221                  sz_i(ji,jj,:,jl) = sz_i(ib,jb,:,jl) ! salinity profile
222                  !
223               END SELECT
224               !
225               IF( nn_icesal == 1 ) THEN     ! if constant salinity
226                  s_i (ji,jj  ,jl) = rn_icesal
227                  sz_i(ji,jj,:,jl) = rn_icesal
228               ENDIF
229               !
230               ! global fields
231               v_i (ji,jj,jl) = h_i(ji,jj,jl) * a_i(ji,jj,jl)                       ! volume ice
232               v_s (ji,jj,jl) = h_s(ji,jj,jl) * a_i(ji,jj,jl)                       ! volume snw
233               sv_i(ji,jj,jl) = MIN( s_i(ji,jj,jl) , sss_m(ji,jj) ) * v_i(ji,jj,jl) ! salt content
234               DO jk = 1, nlay_s
235                  e_s(ji,jj,jk,jl) = rhos * ( rcpi * ( rt0 - t_s(ji,jj,jk,jl) ) + rLfus )   ! enthalpy in J/m3
236                  e_s(ji,jj,jk,jl) = e_s(ji,jj,jk,jl) * v_s(ji,jj,jl) * r1_nlay_s           ! enthalpy in J/m2
237               END DO               
238               DO jk = 1, nlay_i
239                  ztmelts          = - rTmlt  * sz_i(ji,jj,jk,jl)             ! Melting temperature in C
240                  t_i(ji,jj,jk,jl) = MIN( t_i(ji,jj,jk,jl), ztmelts + rt0 )   ! Force t_i to be lower than melting point => likely conservation issue
241                  !
242                  e_i(ji,jj,jk,jl) = rhoi * ( rcpi  * ( ztmelts - ( t_i(ji,jj,jk,jl) - rt0 ) )           &   ! enthalpy in J/m3
243                     &                      + rLfus * ( 1._wp - ztmelts / ( t_i(ji,jj,jk,jl) - rt0 ) )   &
244                     &                      - rcp   *   ztmelts )                 
245                  e_i(ji,jj,jk,jl) = e_i(ji,jj,jk,jl) * v_i(ji,jj,jl) * r1_nlay_i                            ! enthalpy in J/m2
246               END DO
247               !
248            ELSE   ! no ice at the boundary
249               !
250               a_i (ji,jj,  jl) = 0._wp
251               h_i (ji,jj,  jl) = 0._wp
252               h_s (ji,jj,  jl) = 0._wp
253               oa_i(ji,jj,  jl) = 0._wp
254               a_ip(ji,jj,  jl) = 0._wp
255               v_ip(ji,jj,  jl) = 0._wp
256               t_su(ji,jj,  jl) = rt0
257               t_s (ji,jj,:,jl) = rt0
258               t_i (ji,jj,:,jl) = rt0 
259               
260               IF( nn_icesal == 1 ) THEN     ! if constant salinity
261                  s_i (ji,jj  ,jl) = rn_icesal
262                  sz_i(ji,jj,:,jl) = rn_icesal
263               ELSE                          ! if variable salinity
264                  s_i (ji,jj,jl)   = rn_simin
265                  sz_i(ji,jj,:,jl) = rn_simin
266               ENDIF
267               !
268               ! global fields
269               v_i (ji,jj,  jl) = 0._wp
270               v_s (ji,jj,  jl) = 0._wp
271               sv_i(ji,jj,  jl) = 0._wp
272               e_s (ji,jj,:,jl) = 0._wp
273               e_i (ji,jj,:,jl) = 0._wp
274
275            ENDIF
276                       
277         END DO
278         !
279      END DO ! jl
280      !     
281   END SUBROUTINE bdy_ice_frs
282
283
284   SUBROUTINE bdy_ice_dyn( cd_type )
285      !!------------------------------------------------------------------------------
286      !!                 ***  SUBROUTINE bdy_ice_dyn  ***
287      !!                   
288      !! ** Purpose : Apply dynamics boundary conditions for sea-ice.
289      !!
290      !! ** Method :  if this adjacent grid point is not ice free, then u_ice and v_ice take its value
291      !!              if                          is     ice free, then u_ice and v_ice are unchanged by BDY
292      !!                                                           they keep values calculated in rheology
293      !!
294      !!------------------------------------------------------------------------------
295      CHARACTER(len=1), INTENT(in)  ::   cd_type   ! nature of velocity grid-points
296      !
297      INTEGER  ::   i_bdy, jgrd      ! dummy loop indices
298      INTEGER  ::   ji, jj           ! local scalar
299      INTEGER  ::   jbdy             ! BDY set index
300      REAL(wp) ::   zmsk1, zmsk2, zflag
301      LOGICAL, DIMENSION(4) :: llsend2, llrecv2, llsend3, llrecv3  ! indicate how communications are to be carried out
302      !!------------------------------------------------------------------------------
303      IF( ln_timing )   CALL timing_start('bdy_ice_dyn')
304      !
305      DO jbdy=1, nb_bdy
306         !
307         SELECT CASE( cn_ice(jbdy) )
308         !
309         CASE('none')
310            CYCLE
311            !
312         CASE('frs')
313            !
314            IF( nn_ice_dta(jbdy) == 0 ) CYCLE            ! case ice boundaries = initial conditions
315            !                                            !      do not change ice velocity (it is only computed by rheology)
316            SELECT CASE ( cd_type )
317            !     
318            CASE ( 'U' ) 
319               jgrd = 2      ! u velocity
320               DO i_bdy = 1, idx_bdy(jbdy)%nblenrim(jgrd)
321                  ji    = idx_bdy(jbdy)%nbi(i_bdy,jgrd)
322                  jj    = idx_bdy(jbdy)%nbj(i_bdy,jgrd)
323                  zflag = idx_bdy(jbdy)%flagu(i_bdy,jgrd)
324                  !     i-1  i   i    |  !        i  i i+1 |  !          i  i i+1 |
325                  !      >  ice  >    |  !        o  > ice |  !          o  >  o  |     
326                  ! => set at u_ice(i-1) !  => set to O       !  => unchanged
327                  IF( zflag == -1. .AND. ji > 1 .AND. ji < jpi )   THEN 
328                     IF    ( vt_i(ji  ,jj) > 0. )   THEN   ;   u_ice(ji,jj) = u_ice(ji-1,jj) 
329                     ELSEIF( vt_i(ji+1,jj) > 0. )   THEN   ;   u_ice(ji,jj) = 0._wp
330                     END IF
331                  END IF
332                  ! |    i  i+1 i+1        !  |  i   i i+1        !  | i  i i+1
333                  ! |    >  ice  >         !  | ice  >  o         !  | o  >  o   
334                  ! => set at u_ice(i+1)   !     => set to O      !     =>  unchanged
335                  IF( zflag ==  1. .AND. ji+1 < jpi+1 )   THEN
336                     IF    ( vt_i(ji+1,jj) > 0. )   THEN   ;   u_ice(ji,jj) = u_ice(ji+1,jj)
337                     ELSEIF( vt_i(ji  ,jj) > 0. )   THEN   ;   u_ice(ji,jj) = 0._wp
338                     END IF
339                  END IF
340                  !
341                  IF( zflag ==  0. )   u_ice(ji,jj) = 0._wp   ! u_ice = 0  if north/south bdy 
342                  !
343               END DO
344               !
345            CASE ( 'V' )
346               jgrd = 3      ! v velocity
347               DO i_bdy = 1, idx_bdy(jbdy)%nblenrim(jgrd)
348                  ji    = idx_bdy(jbdy)%nbi(i_bdy,jgrd)
349                  jj    = idx_bdy(jbdy)%nbj(i_bdy,jgrd)
350                  zflag = idx_bdy(jbdy)%flagv(i_bdy,jgrd)
351                  !    ¨¨¨¨¨¨¨¨¨¨¨¨¨¨¨¨     !  ¨¨¨¨ïce¨¨¨(jj+1)¨¨     ! ¨¨¨¨¨¨ö¨¨¨¨(jj+1)       
352                  !       ^    (jj  )       !       ^    (jj  )       !       ^    (jj  )       
353                  !      ice   (jj  )       !       o    (jj  )       !       o    (jj  )       
354                  !       ^    (jj-1)       !                         !
355                  ! => set to u_ice(jj-1)   !  =>   set to 0          !   => unchanged       
356                  IF( zflag == -1. .AND. jj > 1 .AND. jj < jpj )   THEN                 
357                    IF    ( vt_i(ji,jj  ) > 0. )   THEN   ;   v_ice(ji,jj) = v_ice(ji,jj-1)
358                    ELSEIF( vt_i(ji,jj+1) > 0. )   THEN   ;   v_ice(ji,jj) = 0._wp
359                    END IF
360                  END IF 
361                  !       ^    (jj+1)       !                         !             
362                  !      ice   (jj+1)       !       o    (jj+1)       !       o    (jj+1)       
363                  !       ^    (jj  )       !       ^    (jj  )       !       ^    (jj  )
364                  !   ________________      !  ____ice___(jj  )_      !  _____o____(jj  )
365                  ! => set to u_ice(jj+1)   !    => set to 0          !    => unchanged 
366                  IF( zflag ==  1. .AND. jj < jpj )   THEN             
367                     IF    ( vt_i(ji,jj+1) > 0. )   THEN   ;   v_ice(ji,jj) = v_ice(ji,jj+1)
368                     ELSEIF( vt_i(ji,jj  ) > 0. )   THEN   ;   v_ice(ji,jj) = 0._wp
369                     END IF
370                  END IF                                         
371                  !
372                  IF( zflag ==  0. )   v_ice(ji,jj) = 0._wp   ! v_ice = 0  if west/east bdy 
373                  !
374               END DO
375               !
376            END SELECT
377            !
378         CASE DEFAULT
379            CALL ctl_stop( 'bdy_ice_dyn : unrecognised option for open boundaries for ice fields' )
380         END SELECT
381         !
382      END DO   ! jbdy
383      !
384      SELECT CASE ( cd_type )       
385      CASE ( 'U' ) 
386         llsend2(:) = .false.   ;   llrecv2(:) = .false.
387         DO jbdy = 1, nb_bdy
388            IF( cn_ice(jbdy) == 'frs' .AND. nn_ice_dta(jbdy) /= 0 ) THEN
389               llsend2(:) = llsend2(:) .OR. lsend_bdyint(jbdy,2,:)   ! possibly every direction, U points
390               llsend2(1) = llsend2(1) .OR. lsend_bdyext(jbdy,2,1)   ! neighbour might search point towards bdy on its east
391               llrecv2(:) = llrecv2(:) .OR. lrecv_bdyint(jbdy,2,:)   ! possibly every direction, U points
392               llrecv2(2) = llrecv2(2) .OR. lrecv_bdyext(jbdy,2,2)   ! might search point towards bdy on the east
393            END IF
394         END DO
395         IF( ANY(llsend2) .OR. ANY(llrecv2) ) THEN   ! if need to send/recv in at least one direction
396            CALL lbc_bdy_lnk( 'bdyice', llsend2, llrecv2, u_ice, 'U', -1. )
397         END IF
398      CASE ( 'V' )
399         llsend3(:) = .false.   ;   llrecv3(:) = .false.
400         DO jbdy = 1, nb_bdy
401            IF( cn_ice(jbdy) == 'frs' .AND. nn_ice_dta(jbdy) /= 0 ) THEN
402               llsend3(:) = llsend3(:) .OR. lsend_bdyint(jbdy,3,:)   ! possibly every direction, V points
403               llsend3(3) = llsend3(3) .OR. lsend_bdyext(jbdy,3,3)   ! neighbour might search point towards bdy on its north
404               llrecv3(:) = llrecv3(:) .OR. lrecv_bdyint(jbdy,3,:)   ! possibly every direction, V points
405               llrecv3(4) = llrecv3(4) .OR. lrecv_bdyext(jbdy,3,4)   ! might search point towards bdy on the north
406            END IF
407         END DO
408         IF( ANY(llsend3) .OR. ANY(llrecv3) ) THEN   ! if need to send/recv in at least one direction
409            CALL lbc_bdy_lnk( 'bdyice', llsend3, llrecv3, v_ice, 'V', -1. )
410         END IF
411      END SELECT
412      !
413      IF( ln_timing )   CALL timing_stop('bdy_ice_dyn')
414      !
415    END SUBROUTINE bdy_ice_dyn
416
417#else
418   !!---------------------------------------------------------------------------------
419   !!   Default option                                                    Empty module
420   !!---------------------------------------------------------------------------------
421CONTAINS
422   SUBROUTINE bdy_ice( kt )      ! Empty routine
423      IMPLICIT NONE
424      INTEGER, INTENT( in ) :: kt
425      WRITE(*,*) 'bdy_ice: You should not have seen this print! error?', kt
426   END SUBROUTINE bdy_ice
427#endif
428
429   !!=================================================================================
430END MODULE bdyice
Note: See TracBrowser for help on using the repository browser.