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.
limflx.F90 in trunk/NEMO/LIM_SRC – NEMO

source: trunk/NEMO/LIM_SRC/limflx.F90 @ 701

Last change on this file since 701 was 701, checked in by smasson, 16 years ago

sbc(1.1): put back $

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 11.0 KB
Line 
1MODULE limflx
2   !!======================================================================
3   !!                       ***  MODULE limflx   ***
4   !!           computation of the flux at the sea ice/ocean interface
5   !!======================================================================
6#if defined key_ice_lim
7   !!----------------------------------------------------------------------
8   !!   'key_ice_lim'                                     LIM sea-ice model
9   !!----------------------------------------------------------------------
10   !!   lim_flx  : flux at the ice / ocean interface
11   !!----------------------------------------------------------------------
12   !! * Modules used
13   USE par_oce          ! ocean parameters
14   USE phycst           ! physical constants
15   USE ocfzpt           ! surface ocean freezing point
16   USE ice_oce          ! sea-ice variable
17   USE flx_oce          ! sea-ice/ocean forcings variables
18   USE ice              ! LIM sea-ice variables
19   USE flxblk           ! bulk formulea
20   USE lbclnk           ! ocean lateral boundary condition
21   USE in_out_manager   ! I/O manager
22   USE albedo           ! albedo parameters
23   USE prtctl           ! Print control
24
25   IMPLICIT NONE
26   PRIVATE
27
28   !! * Routine accessibility
29   PUBLIC lim_flx       ! called by lim_step
30
31   !! * Module variables
32   REAL(wp)  ::           &  ! constant values
33      epsi16 = 1.e-16  ,  &
34      rzero  = 0.e0    ,  &
35      rone   = 1.e0
36
37   !! * Substitutions
38#  include "vectopt_loop_substitute.h90"
39   !!----------------------------------------------------------------------
40   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)
41   !! $Id$
42   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
43   !!----------------------------------------------------------------------
44CONTAINS
45
46   SUBROUTINE lim_flx
47      !!-------------------------------------------------------------------
48      !!                ***  ROUTINE lim_flx ***
49      !! 
50      !! ** Purpose : Computes the mass and heat fluxes to the ocean
51      !!         
52      !! ** Action  : - Initialisation of some variables
53      !!              - comput. of the fluxes at the sea ice/ocean interface
54      !!     
55      !! ** Outputs : - fsolar  : solar heat flux at sea ice/ocean interface
56      !!              - fnsolar : non solar heat flux
57      !!              - fsalt   : salt flux at sea ice/ocean interface
58      !!              - fmass   : freshwater flux at sea ice/ocean interface
59      !!
60      !! ** References :
61      !!       H. Goosse et al. 1996, Bul. Soc. Roy. Sc. Liege, 65, 87-90
62      !!         original    : 00-01 (LIM)
63      !!         addition    : 02-07 (C. Ethe, G. Madec)
64      !!---------------------------------------------------------------------
65      !! * Local variables
66      INTEGER ::   ji, jj         ! dummy loop indices
67
68      INTEGER ::   &
69         ifvt, i1mfr, idfr ,   &  ! some switches
70         iflt, ial, iadv, ifral, ifrdv
71     
72      REAL(wp) ::   &
73         zinda  ,              &  ! switch for testing the values of ice concentration
74         z1mthcm                  ! 1 - thcm
75!!         zfcm1  ,              &  ! solar  heat fluxes
76!!         zfcm2  ,              &  !  non solar heat fluxes
77#if defined key_lim_fdd   
78      REAL(wp) ::   &
79         zfons,                &  ! salt exchanges at the ice/ocean interface
80         zpme                     ! freshwater exchanges at the ice/ocean interface
81#else
82      REAL(wp) ::   &
83         zprs  , zfons,        &  ! salt exchanges at the ice/ocean interface
84         zpmess                   ! freshwater exchanges at the ice/ocean interface
85#endif
86      REAL(wp), DIMENSION(jpi,jpj) ::  &
87         zfcm1  ,              &  ! solar  heat fluxes
88         zfcm2                    !  non solar heat fluxes     
89#if defined key_coupled   
90      REAL(wp), DIMENSION(jpi,jpj) ::  &
91         zalb  ,               &  ! albedo of ice under overcast sky
92         zalcn ,               &  ! albedo of ocean under overcast sky
93         zalbp ,               &  ! albedo of ice under clear sky
94         zaldum                   ! albedo of ocean under clear sky
95#endif
96      !!---------------------------------------------------------------------
97     
98      !---------------------------------!
99      !      Sea ice/ocean interface    !
100      !---------------------------------!
101       
102       
103      !      heat flux at the ocean surface
104      !-------------------------------------------------------
105       
106      DO jj = 1, jpj
107         DO ji = 1, jpi
108!!sm            zinda   = 1.0 - MAX( rzero , SIGN( rone , - ( 1.0 - pfrld(ji,jj) ) ) )
109!!sm            ifvt    = zinda  *  MAX( rzero , SIGN( rone, -phicif(ji,jj) ) )
110!!sm            i1mfr   = 1.0 - MAX( rzero , SIGN( rone ,  - ( 1.0 - frld(ji,jj) ) ) )
111!!sm            idfr    = 1.0 - MAX( rzero , SIGN( rone , frld(ji,jj) - pfrld(ji,jj) ) )
112
113            zinda   = 1.0 - AINT( pfrld(ji,jj) )                   !   = 0. if pure ocean else 1. (at previous time)
114
115            i1mfr   = 1.0 - AINT(  frld(ji,jj) )                   !   = 0. if pure ocean else 1. (at current  time)
116
117            IF( phicif(ji,jj) <= 0. ) THEN   ;   ifvt = zinda      !   = 1. if (snow and no ice at previous time) else 0. ???
118            ELSE                             ;   ifvt = 0.
119            ENDIF
120
121            IF( frld(ji,jj) >= pfrld(ji,jj) ) THEN   ;   idfr = 0.  !   = 0. if lead fraction increases from previous to current
122            ELSE                                     ;   idfr = 1.   
123            ENDIF
124
125            iflt    = zinda  * (1 - i1mfr) * (1 - ifvt )    !   = 1. if ice (not only snow) at previous and pure ocean at current
126
127            ial     = ifvt   * i1mfr    +    ( 1 - ifvt ) * idfr
128!                 snow no ice   ice         ice or nothing  lead fraction increases
129!                 at previous   now           at previous
130!                -> ice aera increases  ???         -> ice aera decreases ???
131
132            iadv    = ( 1  - i1mfr ) * zinda 
133!                     pure ocean      ice at
134!                     at current      previous
135!                        -> = 1. if ice disapear between previous and current
136
137            ifral   = ( 1  - i1mfr * ( 1 - ial ) ) 
138!                            ice at     ???
139!                            current         
140!                         -> ???
141 
142            ifrdv   = ( 1  - ifral * ( 1 - ial ) ) * iadv 
143!                                                    ice disapear                           
144!
145!
146            z1mthcm =   1. - thcm(ji,jj)       
147            !   computation the solar flux at ocean surface
148            zfcm1(ji,jj)   = pfrld(ji,jj) * qsr_oce(ji,jj)  + ( 1. - pfrld(ji,jj) ) * fstric(ji,jj)
149            !  computation the non solar heat flux at ocean surface
150            zfcm2(ji,jj) =  - z1mthcm * zfcm1(ji,jj)   &
151               &           + iflt    * ( fscmbq(ji,jj) + ffltbif(ji,jj) )                            &
152               &           + ifral   * ( ial * qcmif(ji,jj) + (1 - ial) * qldif(ji,jj) ) / rdt_ice   &
153               &           + ifrdv   * ( qfvbq(ji,jj) + qdtcn(ji,jj) ) / rdt_ice
154
155            fsbbq(ji,jj) = ( 1.0 - ( ifvt + iflt ) ) * fscmbq(ji,jj)     ! ???
156           
157            fsolar (ji,jj) = zfcm1(ji,jj)                                       ! solar heat flux
158
159            fnsolar(ji,jj) = zfcm2(ji,jj) - fdtcn(ji,jj)                        ! non solar heat flux
160         END DO
161      END DO
162 
163       
164      !      mass flux at the ocean surface
165      !-------------------------------------------------------
166       
167      DO jj = 1, jpj
168         DO ji = 1, jpi
169#if defined key_lim_fdd
170            !  case of realistic freshwater flux (Tartinville et al., 2001)
171           
172            !  computing freshwater exchanges at the ice/ocean interface
173            zpme = - evap(ji,jj) * frld(ji,jj)            &   !  evaporation over oceanic fraction
174               &   + tprecip(ji,jj)                            &   !  total precipitation
175               &   - sprecip(ji,jj) * ( 1. - pfrld(ji,jj) )  &   !  remov. snow precip over ice
176               &   - rdmsnif(ji,jj) / rdt_ice                   !  freshwaterflux due to snow melting
177           
178            !  computing salt exchanges at the ice/ocean interface
179            zfons =  ( soce - sice ) * ( rdmicif(ji,jj) / rdt_ice ) 
180           
181            !  converting the salt flux from ice to a freshwater flux from ocean
182            fsalt(ji,jj) = zfons / ( sss_io(ji,jj) + epsi16 )
183           
184            !  freshwater masses
185            fmass(ji,jj) = - zpme 
186#else
187            !  case of freshwater flux equivalent as salt flux
188            !  dilution effect due to evaporation and precipitation
189            zprs  = ( tprecip(ji,jj) - sprecip(ji,jj) * ( 1. - pfrld(ji,jj) ) ) * soce 
190            !  freshwater flux
191            zfons = rdmicif(ji,jj) * ( soce - sice )  &  !  fwf : ice formation and melting
192               &   -  dmgwi(ji,jj) * sice             &  !  fwf : salt flx needed to bring the fresh snow to sea/ice salinity
193               &   + rdmsnif(ji,jj) * soce               !  fwf to ocean due to snow melting
194            !  salt exchanges at the ice/ocean interface
195            zpmess         =  zprs - zfons / rdt_ice - evap(ji,jj) * soce * frld(ji,jj)
196            fsalt(ji,jj) =  - zpmess
197#endif
198         END DO
199      END DO
200
201
202      !-------------------------------------------------------------------!
203      !  computation of others transmitting variables from ice to ocean   !
204      !------------------------------------------ ------------------------!
205
206      !-----------------------------------------------!
207      !   Storing the transmitted variables           !
208      !-----------------------------------------------!
209
210      freeze(:,:) = 1.0 - frld(:,:)       ! Sea ice cover           
211      tn_ice(:,:) = sist(:,:)             ! Ice surface temperature                     
212
213#if defined key_coupled           
214      zalb  (:,:) = 0.e0
215      zalcn (:,:) = 0.e0
216      zalbp (:,:) = 0.e0
217      zaldum(:,:) = 0.e0
218
219      !------------------------------------------------!
220      !  2) Computation of snow/ice and ocean albedo   !
221      !------------------------------------------------!
222      CALL flx_blk_albedo( zalb, zalcn, zalbp, zaldum )
223
224      alb_ice(:,:) =  0.5 * zalbp(:,:) + 0.5 * zalb (:,:)   ! Ice albedo                       
225#endif
226
227      IF(ln_ctl) THEN
228         CALL prt_ctl(tab2d_1=fsolar, clinfo1=' lim_flx: fsolar : ', tab2d_2=fnsolar, clinfo2=' fnsolar : ')
229         CALL prt_ctl(tab2d_1=fmass , clinfo1=' lim_flx: fmass  : ', tab2d_2=fsalt  , clinfo2=' fsalt   : ')
230         CALL prt_ctl(tab2d_1=freeze, clinfo1=' lim_flx: freeze : ', tab2d_2=tn_ice , clinfo2=' tn_ice  : ')
231      ENDIF
232   
233    END SUBROUTINE lim_flx
234
235#else
236   !!----------------------------------------------------------------------
237   !!   Default option :        Dummy module           NO LIM sea-ice model
238   !!----------------------------------------------------------------------
239CONTAINS
240   SUBROUTINE lim_flx         ! Dummy routine
241   END SUBROUTINE lim_flx
242#endif 
243
244   !!======================================================================
245END MODULE limflx
Note: See TracBrowser for help on using the repository browser.