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 branches/UKMO/test_moci_test_suite_namelist_read/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/test_moci_test_suite_namelist_read/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_if.F90 @ 9366

Last change on this file since 9366 was 9366, checked in by andmirek, 6 years ago

#2050 first version. Compiled OK in moci test suite

File size: 8.3 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#if defined key_lim3
19   USE ice    , ONLY :   a_i 
20#else
21   USE sbc_ice, ONLY :   a_i 
22#endif
23   USE fldread        ! read input field
24   USE iom            ! I/O manager library
25   USE in_out_manager ! I/O manager
26   USE lib_mpp        ! MPP library
27   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
28
29   IMPLICIT NONE
30   PRIVATE
31   PUBLIC   sbc_ice_if      ! routine called in sbcmod
32   PRIVATE  if_namelist
33
34   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_ice   ! structure of input ice-cover (file informations, fields read)
35   
36   !! * Substitutions
37#  include "domzgr_substitute.h90"
38   !!----------------------------------------------------------------------
39   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
40   !! $Id$
41   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
42   !!----------------------------------------------------------------------
43CONTAINS
44
45   SUBROUTINE sbc_ice_if( kt )
46      !!---------------------------------------------------------------------
47      !!                     ***  ROUTINE sbc_ice_if  ***
48      !!
49      !! ** Purpose :   handle surface boundary condition over ice cover area
50      !!      when sea-ice model are not used
51      !!
52      !! ** Method  : - read sea-ice cover climatology
53      !!              - blah blah blah, ...
54      !!
55      !! ** Action  :   utau, vtau : remain unchanged
56      !!                taum, wndm : remain unchanged
57      !!                qns, qsr   : update heat flux below sea-ice
58      !!                emp, sfx   : update freshwater flux below sea-ice
59      !!                fr_i       : update the ice fraction
60      !!---------------------------------------------------------------------
61      INTEGER, INTENT(in) ::   kt   ! ocean time step
62      !
63      INTEGER  ::   ji, jj     ! dummy loop indices
64      INTEGER  ::   ierror     ! return error code
65      INTEGER  ::   ios        ! Local integer output status for namelist read
66      REAL(wp) ::   ztrp, zsice, zt_fzp, zfr_obs
67      REAL(wp) ::   zqri, zqrj, zqrp, zqi
68      !!
69      CHARACTER(len=100) ::   cn_dir              ! Root directory for location of ice-if files
70      TYPE(FLD_N)        ::   sn_ice              ! informations about the fields to be read
71      NAMELIST/namsbc_iif/ cn_dir, sn_ice
72      !!---------------------------------------------------------------------
73      !                                         ! ====================== !
74      IF( kt == nit000 ) THEN                   !  First call kt=nit000  !
75         !                                      ! ====================== !
76         ! set file information
77         IF(lwm) THEN
78            REWIND( numnam_ref )              ! Namelist namsbc_iif in reference namelist : Ice if file
79            READ  ( numnam_ref, namsbc_iif, IOSTAT = ios, ERR = 901)
80901         IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_iif in reference namelist', lwm )
81            REWIND( numnam_cfg )              ! Namelist Namelist namsbc_iif in configuration namelist : Ice if file
82            READ  ( numnam_cfg, namsbc_iif, IOSTAT = ios, ERR = 902 )
83902         IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_iif in configuration namelist', lwm )
84         ENDIF
85
86         IF(lwm) WRITE ( numond, namsbc_iif )
87
88         CALL if_namelist(cn_dir, sn_ice)
89
90         ALLOCATE( sf_ice(1), STAT=ierror )
91         IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_if: unable to allocate sf_ice structure' )
92         ALLOCATE( sf_ice(1)%fnow(jpi,jpj,1) )
93         IF( sn_ice%ln_tint )   ALLOCATE( sf_ice(1)%fdta(jpi,jpj,1,2) )
94
95         ! fill sf_ice with sn_ice and control print
96         CALL fld_fill( sf_ice, (/ sn_ice /), cn_dir, 'sbc_ice_if', 'ice-if sea-ice model', 'namsbc_iif' )
97         !
98      ENDIF
99      lspr = .FALSE. 
100      CALL fld_read( kt, nn_fsbc, sf_ice )           ! Read input fields and provides the
101      !                                              ! input fields at the current time-step
102      lspr = .FALSE.
103     
104      IF( MOD( kt-1, nn_fsbc) == 0 ) THEN
105         !
106         ztrp = -40.             ! restoring terme for temperature (w/m2/k)
107         zsice = - 0.04 / 0.8    ! ratio of isohaline compressibility over isotherme compressibility
108                                 ! ( d rho / dt ) / ( d rho / ds )      ( s = 34, t = -1.8 )
109         
110         CALL eos_fzp( sss_m(:,:), fr_i(:,:) )       ! sea surface freezing temperature [Celcius]
111         fr_i(:,:) = fr_i(:,:) * tmask(:,:,1)
112
113         IF( ln_cpl )   a_i(:,:,1) = fr_i(:,:)         
114
115         ! Flux and ice fraction computation
116         DO jj = 1, jpj
117            DO ji = 1, jpi
118               !
119               zt_fzp  = fr_i(ji,jj)                        ! freezing point temperature
120               zfr_obs = sf_ice(1)%fnow(ji,jj,1)            ! observed ice cover
121               !                                            ! ocean ice fraction (0/1) from the freezing point temperature
122               IF( sst_m(ji,jj) <= zt_fzp ) THEN   ;   fr_i(ji,jj) = 1.e0
123               ELSE                                ;   fr_i(ji,jj) = 0.e0
124               ENDIF
125
126               tsn(ji,jj,1,jp_tem) = MAX( tsn(ji,jj,1,jp_tem), zt_fzp )     ! avoid over-freezing point temperature
127
128               qsr(ji,jj) = ( 1. - zfr_obs ) * qsr(ji,jj)   ! solar heat flux : zero below observed ice cover
129
130               !                                            ! non solar heat flux : add a damping term
131               !      # ztrp*(t-(tgel-1.))  if observed ice and no opa ice   (zfr_obs=1 fr_i=0)
132               !      # ztrp*min(0,t-tgel)  if observed ice and opa ice      (zfr_obs=1 fr_i=1)
133               zqri = ztrp * ( tsb(ji,jj,1,jp_tem) - ( zt_fzp - 1.) )
134               zqrj = ztrp * MIN( 0., tsb(ji,jj,1,jp_tem) - zt_fzp )
135               zqrp = ( zfr_obs * ( (1. - fr_i(ji,jj) ) * zqri    &
136                 &                 +      fr_i(ji,jj)   * zqrj ) ) * tmask(ji,jj,1)
137
138               !                                            ! non-solar heat flux
139               !      # qns unchanged              if no climatological ice              (zfr_obs=0)
140               !      # qns = zqrp                 if climatological ice and no opa ice  (zfr_obs=1, fr_i=0)
141               !      # qns = zqrp -2(-4) watt/m2  if climatological ice and opa ice     (zfr_obs=1, fr_i=1)
142               !                                   (-2=arctic, -4=antarctic)   
143               zqi = -3. + SIGN( 1.e0, ff(ji,jj) )
144               qns(ji,jj) = ( ( 1.- zfr_obs ) * qns(ji,jj)                             &
145                  &          +      zfr_obs   * fr_i(ji,jj) * zqi ) * tmask(ji,jj,1)   &
146                  &       + zqrp
147            END DO
148         END DO
149         !
150      ENDIF
151      !
152   END SUBROUTINE sbc_ice_if
153
154   SUBROUTINE if_namelist(cd_dir, sd_ice)
155     !!---------------------------------------------------------------------
156     !!                   ***  ROUTINE if_namelist  ***
157     !!                     
158     !! ** Purpose :   Broadcast namelist variables read by procesor lwm
159     !!
160     !! ** Method  :   use lib_mpp
161     !!----------------------------------------------------------------------
162      CHARACTER(len=100), INTENT(INOUT)  ::   cd_dir    ! Root directory for location of ice-if files
163      TYPE(FLD_N),        INTENT(INOUT)  ::   sd_ice    ! informations about the fields to be read
164
165#if defined key_mpp_mpi
166      CALL mpp_bcast(cd_dir, 100)
167      CALL fld_n_bcast(sd_ice)
168#endif
169   END SUBROUTINE if_namelist
170   !!======================================================================
171END MODULE sbcice_if
Note: See TracBrowser for help on using the repository browser.