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

source: branches/UKMO/2014_Surge_Modelling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_if.F90 @ 5728

Last change on this file since 5728 was 4624, checked in by acc, 10 years ago

#1305. Fix slow start-up problems on some systems by introducing and using lwm logical to restrict output of merged namelists to the first (or only) processor. lwm is true only on the first processor regardless of ln_ctl. Small changes to all flavours of nemogcm.F90 are also required to write namctl and namcfg after the call to mynode which now opens output.namelist.dyn and writes nammpp.

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