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 branches/DEV_r2106_LOCEAN2010/NEMO/OPA_SRC/BDY – NEMO

source: branches/DEV_r2106_LOCEAN2010/NEMO/OPA_SRC/BDY/bdyice.F90 @ 2236

Last change on this file since 2236 was 2236, checked in by cetlod, 14 years ago

First guess of NEMO_v3.3

File size: 4.3 KB
Line 
1MODULE bdyice
2   !!======================================================================
3   !!                       ***  MODULE  bdyice  ***
4   !! Unstructured Open Boundary Cond. :  Flow Relaxation Scheme applied sea-ice
5   !!======================================================================
6   !!  History :  3.3  !  2010-09 (D. Storkey)  Original code
7   !!----------------------------------------------------------------------
8#if defined   key_bdy   &&   defined key_lim2
9   !!----------------------------------------------------------------------
10   !!   'key_bdy'            and                 Unstructured Open Boundary Conditions
11   !!   'key_lim2'                                                 LIM-2 sea ice model
12   !!----------------------------------------------------------------------
13   !!   bdy_ice        : Relaxation of tracers on unstructured open boundaries
14   !!----------------------------------------------------------------------
15   USE oce             ! ocean dynamics and tracers variables
16   USE ice_2           ! LIM_2 ice variables
17   USE dom_oce         ! ocean space and time domain variables
18   USE bdy_oce         ! ocean open boundary conditions
19   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
20   USE in_out_manager  ! write to numout file
21   
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC   bdy_ice    ! routine called in sbcmod
26
27   !!----------------------------------------------------------------------
28   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
29   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
30   !!----------------------------------------------------------------------
31CONTAINS
32
33   SUBROUTINE bdy_ice( kt )
34      !!------------------------------------------------------------------------------
35      !!                 ***  SUBROUTINE bdy_ice  ***
36      !!                   
37      !! ** Purpose : Apply the Flow Relaxation Scheme for sea-ice fields in the case
38      !!              of unstructured open boundaries. Currently only tested for LIM2.
39      !!
40      !! Reference : Engedahl H., 1995: Use of the flow relaxation scheme in a three-
41      !!             dimensional baroclinic ocean model with realistic topography. Tellus, 365-382.
42      !!------------------------------------------------------------------------------
43      INTEGER, INTENT( in ) ::   kt   ! model time step index
44      !!
45      INTEGER  ::   jb, jk, jgrd   ! dummy loop indices
46      INTEGER  ::   ii, ij         ! local scalar
47      REAL(wp) ::   zwgt, zwgt1    ! local scalar
48      !!------------------------------------------------------------------------------
49      !
50      jgrd = 1      ! Everything is at T-points here
51      !
52      IF( ln_bdy_ice_frs ) THEN     ! update ice fields by relaxation at the boundary
53         DO jb = 1, nblen(jgrd)
54            DO jk = 1, jpkm1
55               ii    = nbi(jb,jgrd)
56               ij    = nbj(jb,jgrd)
57               zwgt  = nbw(jb,jgrd)
58               zwgt1 = 1.e0 - nbw(jb,jgrd)
59               frld (ii,ij) = ( frld (ii,ij) * zwgt1 + frld_bdy (jb) * zwgt ) * tmask(ii,ij,1)     ! Leads fraction
60               hicif(ii,ij) = ( hicif(ii,ij) * zwgt1 + hicif_bdy(jb) * zwgt ) * tmask(ii,ij,1)     ! Ice depth
61               hsnif(ii,ij) = ( hsnif(ii,ij) * zwgt1 + hsnif_bdy(jb) * zwgt ) * tmask(ii,ij,1)     ! Snow depth
62            END DO
63         END DO
64         CALL lbc_lnk( frld, 'T', 1. )                                         ! lateral boundary conditions
65         CALL lbc_lnk( hicif, 'T', 1. )   ;   CALL lbc_lnk( hsnif, 'T', 1. )
66         !
67      ELSE                          ! we have called this routine without ln_bdy_ice_frs not set
68         IF( kt == nit000 )   CALL ctl_warn( 'E R R O R (possible) called bdy_ice when ln_bdy_ice_frs is false?' )
69      ENDIF
70      !     
71   END SUBROUTINE bdy_ice
72#else
73   !!---------------------------------------------------------------------------------
74   !!   Default option                                                    Empty module
75   !!---------------------------------------------------------------------------------
76CONTAINS
77   SUBROUTINE bdy_ice( kt )      ! Empty routine
78      WRITE(*,*) 'bdy_ice: You should not have seen this print! error?', kt
79   END SUBROUTINE bdy_ice
80#endif
81
82   !!=================================================================================
83END MODULE bdyice
Note: See TracBrowser for help on using the repository browser.