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/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/BDY/bdyice.F90 @ 2287

Last change on this file since 2287 was 2287, checked in by smasson, 14 years ago

update licence of all NEMO files...

  • Property svn:keywords set to Id
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   !! $Id$
30   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
31   !!----------------------------------------------------------------------
32CONTAINS
33
34   SUBROUTINE bdy_ice( kt )
35      !!------------------------------------------------------------------------------
36      !!                 ***  SUBROUTINE bdy_ice  ***
37      !!                   
38      !! ** Purpose : Apply the Flow Relaxation Scheme for sea-ice fields in the case
39      !!              of unstructured open boundaries. Currently only tested for LIM2.
40      !!
41      !! Reference : Engedahl H., 1995: Use of the flow relaxation scheme in a three-
42      !!             dimensional baroclinic ocean model with realistic topography. Tellus, 365-382.
43      !!------------------------------------------------------------------------------
44      INTEGER, INTENT( in ) ::   kt   ! model time step index
45      !!
46      INTEGER  ::   jb, jk, jgrd   ! dummy loop indices
47      INTEGER  ::   ii, ij         ! local scalar
48      REAL(wp) ::   zwgt, zwgt1    ! local scalar
49      !!------------------------------------------------------------------------------
50      !
51      jgrd = 1      ! Everything is at T-points here
52      !
53      IF( ln_bdy_ice_frs ) THEN     ! update ice fields by relaxation at the boundary
54         DO jb = 1, nblen(jgrd)
55            DO jk = 1, jpkm1
56               ii    = nbi(jb,jgrd)
57               ij    = nbj(jb,jgrd)
58               zwgt  = nbw(jb,jgrd)
59               zwgt1 = 1.e0 - nbw(jb,jgrd)
60               frld (ii,ij) = ( frld (ii,ij) * zwgt1 + frld_bdy (jb) * zwgt ) * tmask(ii,ij,1)     ! Leads fraction
61               hicif(ii,ij) = ( hicif(ii,ij) * zwgt1 + hicif_bdy(jb) * zwgt ) * tmask(ii,ij,1)     ! Ice depth
62               hsnif(ii,ij) = ( hsnif(ii,ij) * zwgt1 + hsnif_bdy(jb) * zwgt ) * tmask(ii,ij,1)     ! Snow depth
63            END DO
64         END DO
65         CALL lbc_lnk( frld, 'T', 1. )                                         ! lateral boundary conditions
66         CALL lbc_lnk( hicif, 'T', 1. )   ;   CALL lbc_lnk( hsnif, 'T', 1. )
67         !
68      ELSE                          ! we have called this routine without ln_bdy_ice_frs not set
69         IF( kt == nit000 )   CALL ctl_warn( 'E R R O R (possible) called bdy_ice when ln_bdy_ice_frs is false?' )
70      ENDIF
71      !     
72   END SUBROUTINE bdy_ice
73#else
74   !!---------------------------------------------------------------------------------
75   !!   Default option                                                    Empty module
76   !!---------------------------------------------------------------------------------
77CONTAINS
78   SUBROUTINE bdy_ice( kt )      ! Empty routine
79      WRITE(*,*) 'bdy_ice: You should not have seen this print! error?', kt
80   END SUBROUTINE bdy_ice
81#endif
82
83   !!=================================================================================
84END MODULE bdyice
Note: See TracBrowser for help on using the repository browser.