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.
sbc_ice.F90 in branches/UKMO/dev_merge_2017_CICE_interface/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_merge_2017_CICE_interface/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90 @ 9675

Last change on this file since 9675 was 9675, checked in by dancopsey, 6 years ago

Apply changes as suggested by Alex West - renaming coupling variables.

File size: 14.0 KB
RevLine 
[888]1MODULE sbc_ice
2   !!======================================================================
3   !!                 ***  MODULE  sbc_ice  ***
[2715]4   !! Surface module - LIM-3: parameters & variables defined in memory
[888]5   !!======================================================================
[2715]6   !! History :  3.0  ! 2006-08  (G. Madec)  Surface module
7   !!            3.2  ! 2009-06  (S. Masson) merge with ice_oce
[3294]8   !!            3.3.1! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation
9   !!            3.4  ! 2011-11  (C. Harris) CICE added as an option
[888]10   !!----------------------------------------------------------------------
[9019]11#if defined key_lim3 || defined key_cice
[888]12   !!----------------------------------------------------------------------
[9019]13   !!   'key_lim3' or 'key_cice' :              LIM-3 or CICE sea-ice model
[888]14   !!----------------------------------------------------------------------
15   USE par_oce          ! ocean parameters
[4990]16   USE sbc_oce          ! surface boundary condition: ocean
[1465]17# if defined key_lim3
[5123]18   USE ice              ! LIM-3 parameters
[1465]19# endif
[4990]20# if defined key_cice
[3294]21   USE ice_domain_size, only: ncat 
22#endif
[2715]23   USE lib_mpp          ! MPP library
24   USE in_out_manager   ! I/O manager
[888]25
26   IMPLICIT NONE
27   PRIVATE
28
[9019]29   PUBLIC   sbc_ice_alloc   ! called in sbcmod.F90 or sbcice_cice.F90
[2715]30
[1465]31# if defined  key_lim3
[2528]32   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .TRUE.   !: LIM-3 ice model
[3294]33   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE
[2528]34   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = 'C'      !: 'C'-grid ice-velocity
[1465]35# endif
[3294]36# if defined  key_cice
37   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3
38   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .TRUE.   !: CICE ice model
39   CHARACTER(len=1), PUBLIC            ::   cp_ice_msh = 'F'      !: 'F'-grid ice-velocity
40# endif
[1465]41
[4990]42   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qns_ice        !: non solar heat flux over ice                  [W/m2]
43   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice        !: solar heat flux over ice                      [W/m2]
[9675]44   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   zevap_ice        !: latent flux over ice                          [W/m2]
[4990]45   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   dqla_ice       !: latent sensibility over ice                 [W/m2/K]
46   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   dqns_ice       !: non solar heat flux over ice (LW+SEN+LA)    [W/m2/K]
[9675]47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t1_ice         !: ice surface temperature                          [K]
[4990]48   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   alb_ice        !: ice albedo                                       [-]
[888]49
[9019]50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qml_ice        !: heat available for snow / ice surface melting     [W/m2]
51   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qcn_ice        !: heat conduction flux in the layer below surface   [W/m2]
52   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice_tr     !: solar flux transmitted below the ice surface      [W/m2]
53
[4990]54   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   utau_ice       !: atmos-ice u-stress. VP: I-pt ; EVP: U,V-pts   [N/m2]
55   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   vtau_ice       !: atmos-ice v-stress. VP: I-pt ; EVP: U,V-pts   [N/m2]
[5407]56   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_ice        !: sublimation - precip over sea ice          [kg/m2/s]
[888]57
[5407]58#if defined  key_lim3
59   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   evap_ice       !: sublimation                              [kg/m2/s]
60   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   devap_ice      !: sublimation sensitivity                [kg/m2/s/K]
61   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qns_oce        !: non solar heat flux over ocean              [W/m2]
62   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qsr_oce        !: non solar heat flux over ocean              [W/m2]
63   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qemp_oce       !: heat flux of precip and evap over ocean     [W/m2]
64   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qemp_ice       !: heat flux of precip and evap over ice       [W/m2]
[6416]65   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qevap_ice      !: heat flux of evap over ice                  [W/m2]
66   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qprec_ice      !: enthalpy of precip over ice                 [J/m3]
[5407]67   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_oce        !: evap - precip over ocean                 [kg/m2/s]
68   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndm_ice       !: wind speed module at T-point                 [m/s]
[9019]69   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sstfrz         !: wind speed module at T-point                 [m/s]
70   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tsfc_ice       !: sea ice surface skin temperature (on categories)
[5407]71#endif
72
[4990]73#if defined key_cice
[3294]74   !
75   ! for consistency with LIM, these are declared with three dimensions
76   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qlw_ice            !: incoming long-wave
77   !
78   ! other forcing arrays are two dimensional
79   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ss_iou             !: x ice-ocean surface stress at NEMO U point
80   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ss_iov             !: y ice-ocean surface stress at NEMO V point
81   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qatm_ice           !: specific humidity
82   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndi_ice           !: i wind at T point
83   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndj_ice           !: j wind at T point
84   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nfrzmlt            !: NEMO frzmlt
85   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iu              !: ice fraction at NEMO U point
86   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iv              !: ice fraction at NEMO V point
[9500]87   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sstfrz             !: sea surface freezing temperature
88   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tsfc_ice           !: sea-ice surface skin temperature (on categories)
[9675]89   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   cnd_ice             !: sea-ice surface layer thermal conductivity (on cats)
[9500]90
[4990]91   ! variables used in the coupled interface
92   INTEGER , PUBLIC, PARAMETER ::   jpl = ncat
93   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   u_ice, v_ice          ! jpi, jpj
[9675]94   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  a_ip, v_ip ! Meltpond fraction and depth
[4990]95   
[9500]96   !
97   
98   !
99#if defined key_asminc
100   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ndaice_da          !: NEMO fresh water flux to ocean due to data assim
101   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nfresh_da          !: NEMO salt flux to ocean due to data assim
102   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nfsalt_da          !: NEMO ice concentration change/second from data assim
103#endif
104     
105   
[4990]106   ! already defined in ice.F90 for LIM3
107   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  a_i
[9019]108   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  h_i, h_s
[3294]109
[4990]110   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   tatm_ice       !: air temperature [K]
111#endif
112
113   REAL(wp), PUBLIC, SAVE ::   cldf_ice = 0.81    !: cloud fraction over sea ice, summer CLIO value   [-]
114
[9019]115   !! arrays relating to embedding ice in the ocean
116   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass        !: mass of snow and ice at current  ice time step   [Kg/m2]
117   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass_b      !: mass of snow and ice at previous ice time step   [Kg/m2]
118   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_fmass       !: time evolution of mass of snow+ice               [Kg/m2/s]
119
[2715]120   !!----------------------------------------------------------------------
121   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
[9499]122   !! $Id$
[2715]123   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
124   !!----------------------------------------------------------------------
125CONTAINS
126
127   INTEGER FUNCTION sbc_ice_alloc()
128      !!----------------------------------------------------------------------
129      !!                     ***  FUNCTION sbc_ice_alloc  ***
130      !!----------------------------------------------------------------------
[9019]131      INTEGER :: ierr(4)
[4306]132      !!----------------------------------------------------------------------
133      ierr(:) = 0
134
[9019]135      ALLOCATE( snwice_mass(jpi,jpj) , snwice_mass_b(jpi,jpj), snwice_fmass(jpi,jpj) , STAT=ierr(1) )
136
[5407]137#if defined key_lim3
[9019]138      ALLOCATE( qns_ice (jpi,jpj,jpl) , qsr_ice  (jpi,jpj,jpl) ,     &
[9675]139         &      zevap_ice (jpi,jpj,jpl) , dqla_ice (jpi,jpj,jpl) ,     &
140         &      dqns_ice(jpi,jpj,jpl) , t1_ice   (jpi,jpj,jpl) , alb_ice   (jpi,jpj,jpl) ,   &
[9019]141         &      qml_ice (jpi,jpj,jpl) , qcn_ice  (jpi,jpj,jpl) , qsr_ice_tr(jpi,jpj,jpl) ,   &
142         &      utau_ice(jpi,jpj)     , vtau_ice (jpi,jpj)     , wndm_ice  (jpi,jpj)     ,   &
143         &      evap_ice(jpi,jpj,jpl) , devap_ice(jpi,jpj,jpl) , qprec_ice (jpi,jpj)     ,   &
144         &      qemp_ice(jpi,jpj)     , qevap_ice(jpi,jpj,jpl) , qemp_oce  (jpi,jpj)     ,   &
145         &      qns_oce (jpi,jpj)     , qsr_oce  (jpi,jpj)     , emp_oce   (jpi,jpj)     ,   &
146         &      emp_ice (jpi,jpj)     , tsfc_ice (jpi,jpj,jpl) , sstfrz    (jpi,jpj)     , STAT= ierr(2) )
[5407]147#endif
[4990]148
149#if defined key_cice
[9675]150      ALLOCATE( zevap_ice(jpi,jpj,ncat) , qlw_ice(jpi,jpj,1)    , qsr_ice(jpi,jpj,1)    , &
[3294]151                wndi_ice(jpi,jpj)     , tatm_ice(jpi,jpj)     , qatm_ice(jpi,jpj)     , &
152                wndj_ice(jpi,jpj)     , nfrzmlt(jpi,jpj)      , ss_iou(jpi,jpj)       , &
153                ss_iov(jpi,jpj)       , fr_iu(jpi,jpj)        , fr_iv(jpi,jpj)        , &
[9675]154                a_i(jpi,jpj,ncat)     , qml_ice(jpi,jpj,ncat) , qcn_ice(jpi,jpj,ncat) , &
[9503]155#if defined key_asminc
156               ndaice_da(jpi,jpj)    , nfresh_da(jpi,jpj)    , nfsalt_da(jpi,jpj)    , &
157#endif
158               sstfrz(jpi,jpj)       , STAT= ierr(2) )
[9675]159      IF( ln_cpl )   ALLOCATE( u_ice(jpi,jpj)        , t1_ice (jpi,jpj,jpl)    , &
[9503]160         &                     v_ice(jpi,jpj)        , alb_ice(jpi,jpj,1)      , &
161         &                     emp_ice(jpi,jpj)      , qns_ice(jpi,jpj,1)      , dqns_ice(jpi,jpj,1)   , &
[9675]162         &                     a_ip(jpi,jpj,jpl)      , v_ip(jpi,jpj,jpl)     , tsfc_ice(jpi,jpj,jpl) , &
163         &                     cnd_ice(jpi,jpj,jpl) ,    STAT=ierr(3) )
[9019]164      IF( ln_cpl )   ALLOCATE( h_i(jpi,jpj,jpl) , h_s(jpi,jpj,jpl) , STAT=ierr(4) )
[3294]165#endif
[4990]166
[4306]167      sbc_ice_alloc = MAXVAL( ierr )
[2715]168      IF( lk_mpp            )   CALL mpp_sum ( sbc_ice_alloc )
169      IF( sbc_ice_alloc > 0 )   CALL ctl_warn('sbc_ice_alloc: allocation of arrays failed')
170   END FUNCTION sbc_ice_alloc
171
[888]172#else
173   !!----------------------------------------------------------------------
[9019]174   !!   Default option                      NO LIM3 or CICE sea-ice model
[888]175   !!----------------------------------------------------------------------
[9019]176   USE lib_mpp          ! MPP library
[4990]177   USE in_out_manager   ! I/O manager
[9019]178
179   IMPLICIT NONE
180   PRIVATE
181
182   PUBLIC   sbc_ice_alloc   !
183
[2528]184   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3 ice model
[3294]185   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE  ice model
[2528]186   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = '-'      !: no grid ice-velocity
[9019]187   REAL(wp)        , PUBLIC, PARAMETER ::   cldf_ice = 0.81       !: cloud fraction over sea ice, summer CLIO value   [-]
[4990]188   INTEGER         , PUBLIC, PARAMETER ::   jpl = 1 
[9019]189   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   u_ice, v_ice                        ! jpi, jpj
[9675]190   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t1_ice, alb_ice, qns_ice, dqns_ice  ! (jpi,jpj,jpl)
[4990]191   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i
192   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_ice
193   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice
[9019]194   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   h_i, h_s
[9675]195   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qml_ice, qcn_ice
[9019]196   !
197   !! arrays related to embedding ice in the ocean.
198   !! These arrays need to be declared even if no ice model is required.
199   !! In the no ice model or traditional levitating ice cases they contain only zeros
200   !! ---------------------
201   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass        !: mass of snow and ice at current  ice time step   [Kg/m2]
202   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass_b      !: mass of snow and ice at previous ice time step   [Kg/m2]
203   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_fmass       !: time evolution of mass of snow+ice               [Kg/m2/s]
204   !!----------------------------------------------------------------------
205CONTAINS
206
207   INTEGER FUNCTION sbc_ice_alloc()
208      !!----------------------------------------------------------------------
209      !!                     ***  FUNCTION sbc_ice_alloc  ***
210      !!----------------------------------------------------------------------
211      INTEGER :: ierr(1)
212      !!----------------------------------------------------------------------
213      ierr(:) = 0
214      ALLOCATE( snwice_mass(jpi,jpj) , snwice_mass_b(jpi,jpj), snwice_fmass(jpi,jpj) , STAT=ierr(1) )
215      sbc_ice_alloc = MAXVAL( ierr )
216      IF( lk_mpp            )   CALL mpp_sum ( sbc_ice_alloc )
217      IF( sbc_ice_alloc > 0 )   CALL ctl_warn('sbc_ice_alloc: allocation of arrays failed')
218   END FUNCTION sbc_ice_alloc
[888]219#endif
220
[1469]221   !!======================================================================
[888]222END MODULE sbc_ice
Note: See TracBrowser for help on using the repository browser.