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

source: branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90 @ 4730

Last change on this file since 4730 was 4730, checked in by vancop, 10 years ago

coupled interface modifications for LIM3

  • Property svn:keywords set to Id
File size: 9.4 KB
Line 
1MODULE sbc_ice
2   !!======================================================================
3   !!                 ***  MODULE  sbc_ice  ***
4   !! Surface module - LIM-3: parameters & variables defined in memory
5   !!======================================================================
6   !! History :  3.0  ! 2006-08  (G. Madec)  Surface module
7   !!            3.2  ! 2009-06  (S. Masson) merge with ice_oce
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
10   !!----------------------------------------------------------------------
11#if defined key_lim3 || defined key_lim2 || defined key_cice
12   !!----------------------------------------------------------------------
13   !!   'key_lim2' or 'key_lim3' :             LIM-2 or LIM-3 sea-ice model
14   !!----------------------------------------------------------------------
15   USE par_oce          ! ocean parameters
16# if defined key_lim3
17   USE par_ice          ! LIM-3 parameters
18# endif
19# if defined key_lim2
20   USE par_ice_2        ! LIM-2 parameters
21   USE ice_2
22# endif
23# if defined key_cice 
24   USE ice_domain_size, only: ncat 
25#endif
26   USE lib_mpp          ! MPP library
27   USE in_out_manager   ! I/O manager
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC sbc_ice_alloc ! called in iceini(_2).F90
33
34# if defined  key_lim2
35   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .TRUE.   !: LIM-2 ice model
36   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3
37   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE
38#  if defined key_lim2_vp
39   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = 'I'      !: VP : 'I'-grid ice-velocity (B-grid lower left corner)
40#  else
41   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = 'C'      !: EVP: 'C'-grid ice-velocity
42#  endif
43# endif
44# if defined  key_lim3
45   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .FALSE.  !: no LIM-2
46   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .TRUE.   !: LIM-3 ice model
47   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE
48   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = 'C'      !: 'C'-grid ice-velocity
49# endif
50# if defined  key_cice
51   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .FALSE.  !: no LIM-2
52   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3
53   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .TRUE.   !: CICE ice model
54   CHARACTER(len=1), PUBLIC            ::   cp_ice_msh = 'F'      !: 'F'-grid ice-velocity
55# endif
56
57#if defined key_lim3 || defined key_lim2 
58   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qns_ice            !: non solar heat flux over ice                  [W/m2]
59   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice            !: solar heat flux over ice                      [W/m2]
60   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice_mean       !: daily mean solar heat flux over ice       [W/m2]
61   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qla_ice            !: latent flux over ice                          [W/m2]
62   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   dqla_ice           !: latent sensibility over ice                 [W/m2/K]
63   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   dqns_ice           !: non solar heat flux over ice (LW+SEN+LA)    [W/m2/K]
64   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tn_ice             !: ice surface temperature                          [K]
65   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   alb_ice            !: ice albedo                                       [-]
66
67   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   utau_ice           !: atmos-ice u-stress. VP: I-pt ; EVP: U,V-pts   [N/m2]
68   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   vtau_ice           !: atmos-ice v-stress. VP: I-pt ; EVP: U,V-pts   [N/m2]
69   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr1_i0             !: Solar surface transmission parameter, thick ice  [-]
70   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr2_i0             !: Solar surface transmission parameter, thin ice   [-]
71   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_ice            !: sublimation-snow budget over ice             [kg/m2]
72
73# if defined key_lim3
74   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   tatm_ice           !: air temperature [K]
75   REAL(wp), PUBLIC, SAVE                                ::   cldf_ice = 0.81    !: cloud fraction over sea ice, summer CLIO value   [-]
76# endif
77
78#elif defined key_cice
79   !
80   ! for consistency with LIM, these are declared with three dimensions
81   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qlw_ice            !: incoming long-wave
82   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qla_ice            !: latent flux over ice           [W/m2]
83   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice            !: solar heat flux over ice       [W/m2]
84   !
85   ! other forcing arrays are two dimensional
86   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ss_iou             !: x ice-ocean surface stress at NEMO U point
87   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ss_iov             !: y ice-ocean surface stress at NEMO V point
88   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_ice            !: sublimation-snow budget over ice    [kg/m2]
89   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   tatm_ice           !: air temperature
90   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qatm_ice           !: specific humidity
91   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndi_ice           !: i wind at T point
92   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndj_ice           !: j wind at T point
93   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nfrzmlt            !: NEMO frzmlt
94   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iu              !: ice fraction at NEMO U point
95   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iv              !: ice fraction at NEMO V point
96   !
97   ! finally, arrays corresponding to different ice categories
98   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i                !: category ice fraction
99   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   topmelt            !: category topmelt
100   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   botmelt            !: category botmelt
101#endif
102
103   !!----------------------------------------------------------------------
104   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
105   !! $Id$
106   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
107   !!----------------------------------------------------------------------
108CONTAINS
109
110   INTEGER FUNCTION sbc_ice_alloc()
111      !!----------------------------------------------------------------------
112      !!                     ***  FUNCTION sbc_ice_alloc  ***
113      !!----------------------------------------------------------------------
114      INTEGER :: ierr(2)
115      !!----------------------------------------------------------------------
116      ierr(:) = 0
117
118#if defined key_lim3 || defined key_lim2
119      ALLOCATE( qns_ice (jpi,jpj,jpl) , qsr_ice (jpi,jpj,jpl) ,     &
120         &      qla_ice (jpi,jpj,jpl) , dqla_ice(jpi,jpj,jpl) ,     &
121         &      dqns_ice(jpi,jpj,jpl) , tn_ice  (jpi,jpj,jpl) ,     &
122         &      alb_ice (jpi,jpj,jpl) ,                             &
123         &      utau_ice(jpi,jpj)     , vtau_ice(jpi,jpj)     ,     &
124         &      fr1_i0  (jpi,jpj)     , fr2_i0  (jpi,jpj)     ,     &
125#if defined key_lim3
126         &      emp_ice(jpi,jpj)      , tatm_ice(jpi,jpj)     , STAT= ierr(1) )
127#else
128         &      emp_ice(jpi,jpj)                              , STAT= ierr(1) )
129#endif
130#elif defined key_cice
131      ALLOCATE( qla_ice(jpi,jpj,1)    , qlw_ice(jpi,jpj,1)    , qsr_ice(jpi,jpj,1)    , &
132                wndi_ice(jpi,jpj)     , tatm_ice(jpi,jpj)     , qatm_ice(jpi,jpj)     , &
133                wndj_ice(jpi,jpj)     , nfrzmlt(jpi,jpj)      , ss_iou(jpi,jpj)       , &
134                ss_iov(jpi,jpj)       , fr_iu(jpi,jpj)        , fr_iv(jpi,jpj)        , &
135                a_i(jpi,jpj,ncat)     , topmelt(jpi,jpj,ncat) , botmelt(jpi,jpj,ncat), STAT= ierr(1) )
136#endif
137         !
138#if defined key_lim2
139      IF( ltrcdm2dc_ice )THEN
140         ALLOCATE( qsr_ice_mean (jpi,jpj,jpl), STAT=ierr(2) )
141      ENDIF
142#endif
143         !
144      sbc_ice_alloc = MAXVAL( ierr )
145      IF( lk_mpp            )   CALL mpp_sum ( sbc_ice_alloc )
146      IF( sbc_ice_alloc > 0 )   CALL ctl_warn('sbc_ice_alloc: allocation of arrays failed')
147   END FUNCTION sbc_ice_alloc
148
149#else
150   !!----------------------------------------------------------------------
151   !!   Default option                      NO LIM 2.0 or 3.0 or CICE sea-ice model
152   !!----------------------------------------------------------------------
153   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .FALSE.  !: no LIM-2 ice model
154   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3 ice model
155   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE  ice model
156   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = '-'      !: no grid ice-velocity
157#endif
158
159   !!======================================================================
160END MODULE sbc_ice
Note: See TracBrowser for help on using the repository browser.