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.
sbcice_if.F90 in trunk/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMO/OPA_SRC/SBC/sbcice_if.F90 @ 1200

Last change on this file since 1200 was 1200, checked in by rblod, 16 years ago

Adapt Agrif to the new SBC and correct several bugs for agrif (restart writing and reading), see ticket #133
Note : this fix does not work yet on NEC computerq (sxf90/360)

  • Property svn:keywords set to Id
File size: 7.0 KB
Line 
1MODULE sbcice_if
2   !!======================================================================
3   !!                       ***  MODULE  sbcice  ***
4   !! Surface module :  update surface ocean boundary condition over ice
5   !!                   covered area using ice-if model
6   !!======================================================================
7   !! History :  3.0   !  2006-06  (G. Madec)  Original code
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   sbc_ice_if     : update sbc in ice-covered area
12   !!----------------------------------------------------------------------
13   USE oce             ! ocean dynamics and tracers
14   USE dom_oce         ! ocean space and time domain
15   USE phycst          ! physical constants
16   USE eosbn2          ! equation of state
17   USE sbc_oce         ! surface boundary condition: ocean fields
18   USE fldread         ! read input field
19   USE iom             ! I/O manager library
20   USE in_out_manager  ! I/O manager
21
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC   sbc_ice_if      ! routine called in sbcmod
26
27   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_ice   ! structure of input ice-cover (file informations, fields read)
28   
29   !! * Substitutions
30#  include "domzgr_substitute.h90"
31   !!----------------------------------------------------------------------
32   !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)
33   !! $Id$
34   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
35   !!----------------------------------------------------------------------
36
37CONTAINS
38
39   SUBROUTINE sbc_ice_if( kt )
40      !!---------------------------------------------------------------------
41      !!                     ***  ROUTINE sbc_ice_if  ***
42      !!
43      !! ** Purpose :   handle surface boundary condition over ice cover area
44      !!      when sea-ice model are not used
45      !!
46      !! ** Method  : - read sea-ice cover climatology
47      !!              - blah blah blah, ...
48      !!
49      !! ** Action  :   utau, vtau : remain unchanged
50      !!                qns, qsr   : update heat flux below sea-ice
51      !!                emp, emps  : update freshwater flux below sea-ice
52      !!                fr_i       : update the ice fraction
53      !!---------------------------------------------------------------------
54      INTEGER, INTENT(in)          ::   kt         ! ocean time step
55      !
56      INTEGER  ::   ji, jj     ! dummy loop indices
57      INTEGER  ::   ierror     ! return error code
58      REAL(wp) ::   ztrp, zsice, zt_fzp, zfr_obs
59      REAL(wp) ::   zqri, zqrj, zqrp, zqi
60      !!
61      CHARACTER(len=100) ::   cn_dir              ! Root directory for location of ice-if files
62      TYPE(FLD_N)        ::   sn_ice              ! informations about the fields to be read
63      NAMELIST/namsbc_iif/ cn_dir, sn_ice
64      !!---------------------------------------------------------------------
65      !                                         ! ====================== !
66      IF( kt == nit000 ) THEN                   !  First call kt=nit000  !
67         !                                      ! ====================== !
68         ! set file information
69         cn_dir = './'        ! directory in which the model is executed
70         ! ... default values (NB: frequency positive => hours, negative => months)
71         !             !   file    ! frequency !  variable  ! time intep !  clim  ! 'yearly' or !
72         !             !   name    !  (hours)  !   name     !   (T/F)    !  (T/F) !  'monthly'  !
73         sn_ice = FLD_N('ice_cover',    -1.    ,  'ice_cov' ,  .true.    , .true. ,   'yearly'  )
74
75         REWIND ( numnam )               ! ... read in namlist namiif
76         READ   ( numnam, namsbc_iif )
77
78         ALLOCATE( sf_ice(1), STAT=ierror )
79         IF( ierror > 0 ) THEN
80            CALL ctl_stop( 'sbc_ice_if: unable to allocate sf_ice structure' )   ;   RETURN
81         ENDIF
82         ALLOCATE( sf_ice(1)%fnow(jpi,jpj) )
83         ALLOCATE( sf_ice(1)%fdta(jpi,jpj,2) )
84
85
86         ! fill sf_ice with sn_ice and control print
87         CALL fld_fill( sf_ice, (/ sn_ice /), cn_dir, 'sbc_ice_if', 'ice-if sea-ice model', 'namsbc_iif' )
88         !
89      ENDIF
90
91      CALL fld_read( kt, nn_fsbc, sf_ice )           ! Read input fields and provides the
92      !                                              ! input fields at the current time-step
93     
94      IF( MOD( kt-1, nn_fsbc) == 0 ) THEN
95         !
96         ztrp = -40.             ! restoring terme for temperature (w/m2/k)
97         zsice = - 0.04 / 0.8    ! ratio of isohaline compressibility over isotherme compressibility
98                                 ! ( d rho / dt ) / ( d rho / ds )      ( s = 34, t = -1.8 )
99         
100         fr_i(:,:) = tfreez( sss_m ) * tmask(:,:,1)      ! sea surface freezing temperature [Celcius]
101
102         ! Flux and ice fraction computation
103!CDIR COLLAPSE
104         DO jj = 1, jpj
105            DO ji = 1, jpi
106               !
107               zt_fzp  = fr_i(ji,jj)                        ! freezing point temperature
108               zfr_obs = sf_ice(1)%fnow(ji,jj)              ! observed ice cover
109               !                                            ! ocean ice fraction (0/1) from the freezing point temperature
110               IF( sst_m(ji,jj) <= zt_fzp ) THEN   ;   fr_i(ji,jj) = 1.e0
111               ELSE                                ;   fr_i(ji,jj) = 0.e0
112               ENDIF
113
114               tn(ji,jj,1) = MAX( tn(ji,jj,1), zt_fzp )     ! avoid over-freezing point temperature
115
116               qsr(ji,jj) = ( 1. - zfr_obs ) * qsr(ji,jj)   ! solar heat flux : zero below observed ice cover
117
118               !                                            ! non solar heat flux : add a damping term
119               !      # ztrp*(t-(tgel-1.))  if observed ice and no opa ice   (zfr_obs=1 fr_i=0)
120               !      # ztrp*min(0,t-tgel)  if observed ice and opa ice      (zfr_obs=1 fr_i=1)
121               zqri = ztrp * ( tb(ji,jj,1) - ( zt_fzp - 1.) )
122               zqrj = ztrp * MIN( 0., tb(ji,jj,1) - zt_fzp )
123               zqrp = ( zfr_obs * ( (1. - fr_i(ji,jj) ) * zqri    &
124                 &                 +      fr_i(ji,jj)   * zqrj ) ) * tmask(ji,jj,1)
125
126               !                                            ! non-solar heat flux
127               !      # qns unchanged              if no climatological ice              (zfr_obs=0)
128               !      # qns = zqrp                 if climatological ice and no opa ice  (zfr_obs=1, fr_i=0)
129               !      # qns = zqrp -2(-4) watt/m2  if climatological ice and opa ice     (zfr_obs=1, fr_i=1)
130               !                                   (-2=arctic, -4=antarctic)   
131               zqi = -3. + SIGN( 1.e0, ff(ji,jj) )
132               qns(ji,jj) = ( ( 1.- zfr_obs ) * qns(ji,jj)                             &
133                  &          +      zfr_obs   * fr_i(ji,jj) * zqi ) * tmask(ji,jj,1)   &
134                  &       + zqrp
135            END DO
136         END DO
137         !
138      ENDIF
139      !
140   END SUBROUTINE sbc_ice_if
141
142   !!======================================================================
143END MODULE sbcice_if
Note: See TracBrowser for help on using the repository browser.