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/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_if.F90

Last change on this file was 11101, checked in by frrh, 5 years ago

Merge changes from Met Office GMED ticket 450 to reduce unnecessary
text output from NEMO.
This output, which is typically not switchable, is rarely of interest
in normal (non-debugging) runs and simply redunantley consumes extra
file space.
Further, the presence of this text output has been shown to
significantly degrade performance of models which are run during
Met Office HPC RAID (disk) checks.
The new code introduces switches which are configurable via the
changes made in the associated Met Office MOCI ticket 399.

File size: 7.5 KB
RevLine 
[888]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   !!======================================================================
[3625]7   !! History :  3.0  !  2006-06  (G. Madec)  Original code
[888]8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
[3625]11   !!   sbc_ice_if    : update sbc in ice-covered area
[888]12   !!----------------------------------------------------------------------
[3625]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
[4990]18#if defined key_lim3
19   USE ice    , ONLY :   a_i 
20#else
21   USE sbc_ice, ONLY :   a_i 
22#endif
[3625]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) 
[888]28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   sbc_ice_if      ! routine called in sbcmod
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   !!----------------------------------------------------------------------
[2528]39   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[1152]40   !! $Id$
[2715]41   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[888]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      !!
[1037]55      !! ** Action  :   utau, vtau : remain unchanged
[1695]56      !!                taum, wndm : remain unchanged
[1037]57      !!                qns, qsr   : update heat flux below sea-ice
[3625]58      !!                emp, sfx   : update freshwater flux below sea-ice
[1037]59      !!                fr_i       : update the ice fraction
[888]60      !!---------------------------------------------------------------------
[2715]61      INTEGER, INTENT(in) ::   kt   ! ocean time step
[888]62      !
[1037]63      INTEGER  ::   ji, jj     ! dummy loop indices
64      INTEGER  ::   ierror     ! return error code
[4147]65      INTEGER  ::   ios        ! Local integer output status for namelist read
[1037]66      REAL(wp) ::   ztrp, zsice, zt_fzp, zfr_obs
67      REAL(wp) ::   zqri, zqrj, zqrp, zqi
68      !!
[888]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
[4147]77         REWIND( numnam_ref )              ! Namelist namsbc_iif in reference namelist : Ice if file
78         READ  ( numnam_ref, namsbc_iif, IOSTAT = ios, ERR = 901)
79901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_iif in reference namelist', lwp )
[888]80
[4147]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', lwp )
[11101]84         IF(lwm .AND. nprint > 2) WRITE ( numond, namsbc_iif )
[888]85
86         ALLOCATE( sf_ice(1), STAT=ierror )
[2715]87         IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_if: unable to allocate sf_ice structure' )
[2528]88         ALLOCATE( sf_ice(1)%fnow(jpi,jpj,1) )
[2715]89         IF( sn_ice%ln_tint )   ALLOCATE( sf_ice(1)%fdta(jpi,jpj,1,2) )
[888]90
[1133]91         ! fill sf_ice with sn_ice and control print
92         CALL fld_fill( sf_ice, (/ sn_ice /), cn_dir, 'sbc_ice_if', 'ice-if sea-ice model', 'namsbc_iif' )
[888]93         !
94      ENDIF
95
96      CALL fld_read( kt, nn_fsbc, sf_ice )           ! Read input fields and provides the
97      !                                              ! input fields at the current time-step
98     
99      IF( MOD( kt-1, nn_fsbc) == 0 ) THEN
100         !
101         ztrp = -40.             ! restoring terme for temperature (w/m2/k)
102         zsice = - 0.04 / 0.8    ! ratio of isohaline compressibility over isotherme compressibility
103                                 ! ( d rho / dt ) / ( d rho / ds )      ( s = 34, t = -1.8 )
[1037]104         
[6498]105         CALL eos_fzp( sss_m(:,:), fr_i(:,:) )       ! sea surface freezing temperature [Celcius]
106         fr_i(:,:) = fr_i(:,:) * tmask(:,:,1)
[4161]107
[5407]108         IF( ln_cpl )   a_i(:,:,1) = fr_i(:,:)         
[1037]109
110         ! Flux and ice fraction computation
[888]111         DO jj = 1, jpj
112            DO ji = 1, jpi
[1037]113               !
114               zt_fzp  = fr_i(ji,jj)                        ! freezing point temperature
[2528]115               zfr_obs = sf_ice(1)%fnow(ji,jj,1)            ! observed ice cover
[1037]116               !                                            ! ocean ice fraction (0/1) from the freezing point temperature
117               IF( sst_m(ji,jj) <= zt_fzp ) THEN   ;   fr_i(ji,jj) = 1.e0
118               ELSE                                ;   fr_i(ji,jj) = 0.e0
119               ENDIF
[888]120
[3294]121               tsn(ji,jj,1,jp_tem) = MAX( tsn(ji,jj,1,jp_tem), zt_fzp )     ! avoid over-freezing point temperature
[888]122
[1037]123               qsr(ji,jj) = ( 1. - zfr_obs ) * qsr(ji,jj)   ! solar heat flux : zero below observed ice cover
[888]124
[1037]125               !                                            ! non solar heat flux : add a damping term
126               !      # ztrp*(t-(tgel-1.))  if observed ice and no opa ice   (zfr_obs=1 fr_i=0)
127               !      # ztrp*min(0,t-tgel)  if observed ice and opa ice      (zfr_obs=1 fr_i=1)
[3294]128               zqri = ztrp * ( tsb(ji,jj,1,jp_tem) - ( zt_fzp - 1.) )
129               zqrj = ztrp * MIN( 0., tsb(ji,jj,1,jp_tem) - zt_fzp )
[1037]130               zqrp = ( zfr_obs * ( (1. - fr_i(ji,jj) ) * zqri    &
131                 &                 +      fr_i(ji,jj)   * zqrj ) ) * tmask(ji,jj,1)
[888]132
[1037]133               !                                            ! non-solar heat flux
134               !      # qns unchanged              if no climatological ice              (zfr_obs=0)
135               !      # qns = zqrp                 if climatological ice and no opa ice  (zfr_obs=1, fr_i=0)
136               !      # qns = zqrp -2(-4) watt/m2  if climatological ice and opa ice     (zfr_obs=1, fr_i=1)
137               !                                   (-2=arctic, -4=antarctic)   
[888]138               zqi = -3. + SIGN( 1.e0, ff(ji,jj) )
[1037]139               qns(ji,jj) = ( ( 1.- zfr_obs ) * qns(ji,jj)                             &
140                  &          +      zfr_obs   * fr_i(ji,jj) * zqi ) * tmask(ji,jj,1)   &
[888]141                  &       + zqrp
142            END DO
143         END DO
144         !
145      ENDIF
146      !
147   END SUBROUTINE sbc_ice_if
148
149   !!======================================================================
150END MODULE sbcice_if
Note: See TracBrowser for help on using the repository browser.