1 | MODULE bdyice_lim2 |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE bdyice_lim2 *** |
---|
4 | !! Unstructured Open Boundary Cond. : Open boundary conditions for sea-ice (LIM2) |
---|
5 | !!====================================================================== |
---|
6 | !! History : 3.3 ! 2010-09 (D. Storkey) Original code |
---|
7 | !! 3.4 ! 2011 (D. Storkey) rewrite in preparation for OBC-BDY merge |
---|
8 | !!---------------------------------------------------------------------- |
---|
9 | #if defined key_bdy && defined key_lim2 |
---|
10 | !!---------------------------------------------------------------------- |
---|
11 | !! 'key_bdy' and Unstructured Open Boundary Conditions |
---|
12 | !! 'key_lim2' LIM-2 sea ice model |
---|
13 | !!---------------------------------------------------------------------- |
---|
14 | !! bdy_ice_lim_2 : Application of open boundaries to ice |
---|
15 | !! bdy_ice_frs : Application of Flow Relaxation Scheme |
---|
16 | !!---------------------------------------------------------------------- |
---|
17 | USE timing ! Timing |
---|
18 | USE oce ! ocean dynamics and tracers variables |
---|
19 | USE ice_2 ! LIM_2 ice variables |
---|
20 | USE dom_oce ! ocean space and time domain variables |
---|
21 | USE bdy_oce ! ocean open boundary conditions |
---|
22 | USE lbclnk ! ocean lateral boundary conditions (or mpp link) |
---|
23 | USE in_out_manager ! write to numout file |
---|
24 | USE lib_mpp ! distributed memory computing |
---|
25 | |
---|
26 | IMPLICIT NONE |
---|
27 | PRIVATE |
---|
28 | |
---|
29 | PUBLIC bdy_ice_lim_2 ! routine called in sbcmod |
---|
30 | |
---|
31 | !!---------------------------------------------------------------------- |
---|
32 | !! NEMO/OPA 3.3 , NEMO Consortium (2010) |
---|
33 | !! $Id: bdyice.F90 2715 2011-03-30 15:58:35Z rblod $ |
---|
34 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
35 | !!---------------------------------------------------------------------- |
---|
36 | CONTAINS |
---|
37 | |
---|
38 | SUBROUTINE bdy_ice_lim_2( kt ) |
---|
39 | !!---------------------------------------------------------------------- |
---|
40 | !! *** SUBROUTINE bdy_ice_lim_2 *** |
---|
41 | !! |
---|
42 | !! ** Purpose : - Apply open boundary conditions for ice (LIM2) |
---|
43 | !! |
---|
44 | !!---------------------------------------------------------------------- |
---|
45 | INTEGER, INTENT( in ) :: kt ! Main time step counter |
---|
46 | !! |
---|
47 | INTEGER :: ib_bdy ! Loop index |
---|
48 | |
---|
49 | DO ib_bdy=1, nb_bdy |
---|
50 | |
---|
51 | SELECT CASE( nn_ice_lim2(ib_bdy) ) |
---|
52 | CASE(jp_none) |
---|
53 | CYCLE |
---|
54 | CASE(jp_frs) |
---|
55 | CALL bdy_ice_frs( idx_bdy(ib_bdy), dta_bdy(ib_bdy) ) |
---|
56 | CASE DEFAULT |
---|
57 | CALL ctl_stop( 'bdy_ice_lim_2 : unrecognised option for open boundaries for ice fields' ) |
---|
58 | END SELECT |
---|
59 | ENDDO |
---|
60 | |
---|
61 | END SUBROUTINE bdy_ice_lim_2 |
---|
62 | |
---|
63 | SUBROUTINE bdy_ice_frs( idx, dta ) |
---|
64 | !!------------------------------------------------------------------------------ |
---|
65 | !! *** SUBROUTINE bdy_ice_frs *** |
---|
66 | !! |
---|
67 | !! ** Purpose : Apply the Flow Relaxation Scheme for sea-ice fields in the case |
---|
68 | !! of unstructured open boundaries. Currently only tested for LIM2. |
---|
69 | !! |
---|
70 | !! Reference : Engedahl H., 1995: Use of the flow relaxation scheme in a three- |
---|
71 | !! dimensional baroclinic ocean model with realistic topography. Tellus, 365-382. |
---|
72 | !!------------------------------------------------------------------------------ |
---|
73 | TYPE(OBC_INDEX), INTENT(in) :: idx ! OBC indices |
---|
74 | TYPE(OBC_DATA), INTENT(in) :: dta ! OBC external data |
---|
75 | !! |
---|
76 | INTEGER :: jb, jk, jgrd ! dummy loop indices |
---|
77 | INTEGER :: ii, ij ! local scalar |
---|
78 | REAL(wp) :: zwgt, zwgt1 ! local scalar |
---|
79 | !!------------------------------------------------------------------------------ |
---|
80 | ! |
---|
81 | IF( nn_timing == 1 ) CALL timing_start('bdy_ice_frs') |
---|
82 | ! |
---|
83 | jgrd = 1 ! Everything is at T-points here |
---|
84 | ! |
---|
85 | DO jb = 1, idx%nblen(jgrd) |
---|
86 | DO jk = 1, jpkm1 |
---|
87 | ii = idx%nbi(jb,jgrd) |
---|
88 | ij = idx%nbj(jb,jgrd) |
---|
89 | zwgt = idx%nbw(jb,jgrd) |
---|
90 | zwgt1 = 1.e0 - idx%nbw(jb,jgrd) |
---|
91 | frld (ii,ij) = ( frld (ii,ij) * zwgt1 + dta%frld (jb) * zwgt ) * tmask(ii,ij,1) ! Leads fraction |
---|
92 | hicif(ii,ij) = ( hicif(ii,ij) * zwgt1 + dta%hicif(jb) * zwgt ) * tmask(ii,ij,1) ! Ice depth |
---|
93 | hsnif(ii,ij) = ( hsnif(ii,ij) * zwgt1 + dta%hsnif(jb) * zwgt ) * tmask(ii,ij,1) ! Snow depth |
---|
94 | END DO |
---|
95 | END DO |
---|
96 | CALL lbc_lnk( frld, 'T', 1. ) ! lateral boundary conditions |
---|
97 | CALL lbc_lnk( hicif, 'T', 1. ) ; CALL lbc_lnk( hsnif, 'T', 1. ) |
---|
98 | ! |
---|
99 | IF( nn_timing == 1 ) CALL timing_stop('bdy_ice_frs') |
---|
100 | ! |
---|
101 | END SUBROUTINE bdy_ice_frs |
---|
102 | #else |
---|
103 | !!--------------------------------------------------------------------------------- |
---|
104 | !! Default option Empty module |
---|
105 | !!--------------------------------------------------------------------------------- |
---|
106 | CONTAINS |
---|
107 | SUBROUTINE bdy_ice_lim_2( kt ) ! Empty routine |
---|
108 | WRITE(*,*) 'bdy_ice_frs_lim_2: You should not have seen this print! error?', kt |
---|
109 | END SUBROUTINE bdy_ice_lim_2 |
---|
110 | #endif |
---|
111 | |
---|
112 | !!================================================================================= |
---|
113 | END MODULE bdyice_lim2 |
---|