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 @ 9819

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

Added a bunch of fixes and a nemo2cice print statement.

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