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.
Changeset 1859 for branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2 – NEMO

Ignore:
Timestamp:
2010-05-06T10:40:07+02:00 (14 years ago)
Author:
gm
Message:

ticket:#665 step 2 & 3: heat content in qns & new forcing terms

Location:
branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2/ice_2.F90

    r1858 r1859  
    1515   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    1616   !!---------------------------------------------------------------------- 
    17    !! * Modules used 
    1817   USE par_ice_2          ! LIM sea-ice parameters 
    1918 
     
    3433   INTEGER , PUBLIC ::   nbitdr = 250       !: maximum number of iterations for relaxation 
    3534   REAL(wp), PUBLIC ::   rdt_ice            !: ice time step 
     35   REAL(wp), PUBLIC ::   r1_rdt_ice         !: =1/rdt_ice 
    3636   REAL(wp), PUBLIC ::   epsd   = 1.0e-20   !: tolerance parameter for dynamic 
    3737   REAL(wp), PUBLIC ::   alpha  = 0.5       !: coefficient for semi-implicit coriolis 
  • branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2/iceini_2.F90

    r1857 r1859  
    1111   !!   'key_lim2' :                                  LIM 2.0 sea-ice model 
    1212   !!---------------------------------------------------------------------- 
     13   !!   ice_init_2     : LIM-2 sea-ice model initialization 
    1314   !!---------------------------------------------------------------------- 
    14    !!   ice_init_2       : sea-ice model initialization 
    15    !!   ice_run_2        : Definition some run parameter for ice model 
    16    !!---------------------------------------------------------------------- 
    17    USE dom_oce 
    18    USE dom_ice_2 
    19    USE sbc_oce         ! surface boundary condition: ocean 
    20    USE sbc_ice         ! surface boundary condition: ice 
    21    USE phycst          ! Define parameters for the routines 
    22    USE ice_2 
    23    USE limmsh_2 
    24    USE limistate_2 
    25    USE limrst_2    
    26    USE in_out_manager 
     15   USE dom_oce         ! ocean domain 
     16   USE dom_ice_2       ! LIM-2 : ice domain 
     17   USE sbc_oce         ! ocean surface boundary condition 
     18   USE sbc_ice         ! ice   surface boundary condition 
     19   USE phycst          ! physical constant 
     20   USE ice_2           ! LIM-2 variables 
     21   USE limmsh_2        ! LIM-2 mesh 
     22   USE limistate_2     ! LIM-2 inital state 
     23   USE limrst_2        ! LIM-2 restart 
     24   USE in_out_manager  ! I/O manager 
    2725       
    2826   IMPLICIT NONE 
    2927   PRIVATE 
    3028 
    31    PUBLIC   ice_init_2               ! called by sbcice_lim_2.F90 
     29   PUBLIC   ice_init_2   ! called by sbcice_lim_2.F90 
    3230 
    3331   !!---------------------------------------------------------------------- 
    34    !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)  
     32   !! NEMO/LIM 3.3,  UCL-LOCEAN-IPSL (2010)  
    3533   !! $Id$  
    36    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     34   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    3735   !!---------------------------------------------------------------------- 
    3836 
     
    4341      !!                  ***  ROUTINE ice_init_2  *** 
    4442      !! 
    45       !! ** purpose :    
     43      !! ** purpose :   LIM-2 sea-ice model initialisation 
     44      !! 
     45      !! ** input   :   namelist_ice file 
     46      !!                namelist namicerun (inside namelist_ice file) 
    4647      !!---------------------------------------------------------------------- 
    47       ! 
    48       ! Open the namelist file  
    49       CALL ctl_opn( numnam_ice, 'namelist_ice', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp )       
    50       CALL ice_run_2                    !  read in namelist some run parameters 
    51                   
    52       ! Louvain la Neuve Ice model 
    53       rdt_ice = nn_fsbc * rdttra(1) 
    54  
    55       CALL lim_msh_2                  ! ice mesh initialization 
    56       
    57       ! Initial sea-ice state 
    58       IF( .NOT.ln_rstart ) THEN 
    59          CALL lim_istate_2            ! start from rest: sea-ice deduced from sst 
    60       ELSE 
    61          CALL lim_rst_read_2          ! start from a restart file 
    62       ENDIF 
    63        
    64       tn_ice(:,:,1) = sist(:,:)         ! initialisation of ice temperature    
    65       fr_i  (:,:) = 1.0 - frld(:,:)   ! initialisation of sea-ice fraction     
    66       ! 
    67    END SUBROUTINE ice_init_2 
    68  
    69  
    70    SUBROUTINE ice_run_2 
    71       !!------------------------------------------------------------------- 
    72       !!                  ***  ROUTINE ice_run_2 *** 
    73       !!                  
    74       !! ** Purpose :   Definition some run parameter for ice model 
    75       !! 
    76       !! ** Method  :   Read the namicerun namelist and check the parameter  
    77       !!       values called at the first timestep (nit000) 
    78       !! 
    79       !! ** input   :   Namelist namicerun 
    80       !!------------------------------------------------------------------- 
    8148      NAMELIST/namicerun/ cn_icerst_in, cn_icerst_out, ln_limdyn, ln_limdmp, acrit, hsndif, hicdif 
    8249      !!------------------------------------------------------------------- 
    83       !                     
    84       REWIND ( numnam_ice )                       ! Read Namelist namicerun  
     50      ! 
     51      !                                    ! Open the ice namelist file  
     52      CALL ctl_opn( numnam_ice, 'namelist_ice', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp )    
     53      ! 
     54      REWIND ( numnam_ice )                ! Read Namelist namicerun  
    8555      READ   ( numnam_ice , namicerun ) 
    86  
    87       IF(lwp) THEN 
     56      ! 
     57      IF(lwp) THEN                         ! control print 
    8858         WRITE(numout,*) 
    8959         WRITE(numout,*) 'ice_run : ice share parameters for dynamics/advection/thermo of sea-ice' 
     
    9565         WRITE(numout,*) '   computation of temp. in ice  (=0) or not (=9999) hicdif = ', hicdif 
    9666      ENDIF 
     67      !          
     68      rdt_ice    = nn_fsbc * rdttra(1)     ! set ice time step to surface tracer time step 
     69      r1_rdt_ice = 1.e0 / rdt_ice 
    9770      ! 
    98    END SUBROUTINE ice_run_2 
     71      CALL lim_msh_2                       ! ice mesh initialization 
     72      ! 
     73      !                                    ! Initial sea-ice state 
     74      IF( .NOT.ln_rstart ) THEN   ;   CALL lim_istate_2        ! start from rest: sea-ice deduced from sst 
     75      ELSE                        ;   CALL lim_rst_read_2      ! start from a restart file 
     76      ENDIF 
     77      ! 
     78      tn_ice(:,:,1) = sist(:,:)            ! set initial ice temperature   
     79      ! 
     80      fr_i  (:,:) = 1.0 - frld(:,:)        ! set initial ice fraction     
     81      ! 
     82   END SUBROUTINE ice_init_2 
    9983 
    10084#else 
  • branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2/limsbc_2.F90

    r1858 r1859  
    44   !!           computation of the flux at the sea ice/ocean interface 
    55   !!====================================================================== 
    6    !! History : LIM  ! 2000-01 (H. Goosse) Original code 
    7    !!           2.0  ! 2002-07 (C. Ethe, G. Madec) re-writing F90 
    8    !!            -   ! 2006-07 (G. Madec) surface module 
    9    !!           2.1  ! 2010-05  (Y. Aksenov, M. Vancoppenolle, G. Madec) add heat content exchanges 
     6   !! History :  1.0  !  2000-01  (H. Goosse) Original code 
     7   !!            2.0  !  2002-07  (C. Ethe, G. Madec) re-writing F90 
     8   !!             -   !  2006-07  (G. Madec) surface module 
     9   !!             -   !  2008-07  (C. Talandier,G.  Madec) 2D fields for soce and sice 
     10   !!            2.1  !  2010-05  (Y. Aksenov G. Madec) salt flux + heat associated with emp 
    1011   !!---------------------------------------------------------------------- 
    1112#if defined key_lim2 
     
    1718   USE par_oce          ! ocean parameters 
    1819   USE dom_oce          ! ocean domain 
    19    USE sbc_ice          ! surface boundary condition 
    20    USE sbc_oce          ! surface boundary condition 
     20   USE sbc_ice          ! ice   surface boundary condition 
     21   USE sbc_oce          ! ocean surface boundary condition 
    2122   USE phycst           ! physical constants 
    22    USE ice_2            ! LIM sea-ice variables 
     23   USE albedo           ! albedo parameters 
     24   USE ice_2            ! LIM-2 sea-ice variables 
    2325 
    2426   USE lbclnk           ! ocean lateral boundary condition 
    2527   USE in_out_manager   ! I/O manager 
     28   USE iom              !  
     29   USE prtctl           ! Print control 
    2630   USE diaar5, ONLY :   lk_diaar5 
    27    USE iom              !  
    28    USE albedo           ! albedo parameters 
    29    USE prtctl           ! Print control 
    3031   USE cpl_oasis3, ONLY : lk_cpl 
    3132 
     
    3334   PRIVATE 
    3435 
    35    PUBLIC lim_sbc_2     ! called by sbc_ice_lim_2 
     36   PUBLIC   lim_sbc_2   ! called by sbc_ice_lim_2 
    3637 
    3738   REAL(wp)  ::   epsi16 = 1.e-16  ! constant values 
    3839   REAL(wp)  ::   rzero  = 0.e0     
    3940   REAL(wp)  ::   rone   = 1.e0 
    40    REAL(wp), DIMENSION(jpi,jpj)  ::   soce_r 
    41    REAL(wp), DIMENSION(jpi,jpj)  ::   sice_r 
     41   REAL(wp), DIMENSION(jpi,jpj)  ::   soce_r, sice_r   ! ocean and ice 2D constant salinity fields (used if lk_vvl=F) 
    4242 
    4343   !! * Substitutions 
    4444#  include "vectopt_loop_substitute.h90" 
    4545   !!---------------------------------------------------------------------- 
    46    !!   LIM 2.0,  UCL-LOCEAN-IPSL (2006)  
     46   !! NEMO/LIM 3.3,  UCL-LOCEAN-IPSL (2010)  
    4747   !! $Id$ 
    4848   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    6262      !!              - Update  
    6363      !!      
    64       !! ** Outputs : - qsr     : sea heat flux:     solar  
    65       !!              - qns     : sea heat flux: non solar 
    66       !!              - emp     : freshwater budget: volume flux  
    67       !!              - emps    : freshwater budget: concentration/dillution  
     64      !! ** Outputs : - qsr     : solar heat flux 
     65      !!              - qns     : non-solar heat flux including heat content of mass flux 
     66      !!              - emp     : mass flux 
     67      !!              - emps    : salt flux due to Freezing/Melting  
    6868      !!              - utau    : sea surface i-stress (ocean referential) 
    6969      !!              - vtau    : sea surface j-stress (ocean referential) 
     
    7575      !!              Tartinville et al. 2001 Ocean Modelling, 3, 95-108. 
    7676      !!--------------------------------------------------------------------- 
    77       INTEGER ::   kt    ! number of iteration 
     77      INTEGER, INTENT(in) ::   kt    ! number of iteration 
    7878      !! 
    79       INTEGER  ::   ji, jj           ! dummy loop indices 
    80       INTEGER  ::   ifvt, i1mfr, idfr               ! some switches 
    81       INTEGER  ::   iflt, ial, iadv, ifral, ifrdv 
    82       INTEGER  ::   ii0, ii1, ij0, ij1  ! temporary integers 
    83       REAL(wp) ::   zrdtir           ! 1. / rdt_ice 
    84       REAL(wp) ::   zqsr  , zqns     ! solar & non solar heat flux 
    85       REAL(wp) ::   zinda            ! switch for testing the values of ice concentration 
    86       REAL(wp) ::   zfons            ! salt exchanges at the ice/ocean interface 
    87       REAL(wp) ::   zemp             ! freshwater exchanges at the ice/ocean interface 
    88       REAL(wp) ::   zfrldu, zfrldv   ! lead fraction at U- & V-points 
    89       REAL(wp) ::   zutau , zvtau    ! lead fraction at U- & V-points 
    90       REAL(wp) ::   zu_io , zv_io    ! 2 components of the ice-ocean velocity 
    91 ! interface 2D --> 3D 
    92       REAL(wp), DIMENSION(jpi,jpj,1) ::   zalb     ! albedo of ice under overcast sky 
    93       REAL(wp), DIMENSION(jpi,jpj,1) ::   zalbp    ! albedo of ice under clear sky 
     79      INTEGER  ::   ji, jj                     ! dummy loop indices 
     80      INTEGER  ::   ifvt, idfr , iadv, i1mfr   ! local integers 
     81      INTEGER  ::   iflt, ifrdv, ial , ifral   !   -      - 
     82      INTEGER  ::   ii0, ii1, ij0, ij1         !   -      - 
     83      REAL(wp) ::   zqsr, zqns, zqhc, zemp     ! local scalars 
     84      REAL(wp) ::   zinda, zswitch, zcd        !   -      - 
     85      REAL(wp) ::   zfrldu, zutau, zu_io       !   -      - 
     86      REAL(wp) ::   zfrldv, zvtau, zv_io       !   -      - 
     87      REAL(wp) ::   zemp_snw, zfmm, zfsalt     !   -      - 
    9488      REAL(wp) ::   zsang, zmod, zztmp, zfm 
    95       REAL(wp), DIMENSION(jpi,jpj) ::   ztio_u, ztio_v   ! component of ocean stress below sea-ice at I-point 
    96       REAL(wp), DIMENSION(jpi,jpj) ::   ztiomi           ! module    of ocean stress below sea-ice at I-point 
    97       REAL(wp), DIMENSION(jpi,jpj) ::   zqnsoce          ! save qns before its modification by ice model 
    98  
     89      REAL(wp), DIMENSION(jpi,jpj,1) ::   zalb, zalbp    ! 3D workspace 
     90      REAL(wp), DIMENSION(jpi,jpj) ::   ztio_u, ztio_v   ! 2D workspace 
     91      REAL(wp), DIMENSION(jpi,jpj) ::   ztiomi, zqnsoce  !  -      - 
    9992      !!--------------------------------------------------------------------- 
    100       
    101       zrdtir = 1. / rdt_ice 
    102        
     93            
    10394      IF( kt == nit000 ) THEN 
    10495         IF(lwp) WRITE(numout,*) 
    10596         IF(lwp) WRITE(numout,*) 'lim_sbc_2 : LIM 2.0 sea-ice - surface boundary condition' 
    10697         IF(lwp) WRITE(numout,*) '~~~~~~~~~   ' 
    107  
    108          soce_r(:,:) = soce 
    109          sice_r(:,:) = sice 
    110          ! 
    111          IF( cp_cfg == "orca"  .AND. jp_cfg == 2 ) THEN 
    112             !                                        ! ======================= 
    113             !                                        !  ORCA_R2 configuration 
    114             !                                        ! ======================= 
    115             ii0 = 145   ;   ii1 = 180        ! Baltic Sea 
     98         !                              ! 2D fields for constant ice and ocean salinities 
     99         soce_r(:,:) = soce             !    in order to use different value in the Baltic sea 
     100         sice_r(:,:) = sice             !    which is much less salty than polar regions 
     101         ! 
     102         IF( cp_cfg == "orca" ) THEN    ! ORCA configuration 
     103            IF( jp_cfg == 2       ) THEN     !  ORCA_R2 configuration 
     104            ii0 = 145   ;   ii1 = 180              ! Baltic Sea 
    116105            ij0 = 113   ;   ij1 = 130   ;   soce_r(mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 4.e0 
    117                                             sice_r(mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 2.e0 
     106                                            sice_r(mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.50 
     107!!gm add here the R1 R05 and R025  cases 
     108!!          ELSEIF( jp_cfg == 1   ) THEN           !  ORCA_R1   configuration 
     109!!          ELSEIF( jp_cfg == 05  ) THEN           !  ORCA_R05  configuration 
     110!!          ELSEIF( jp_cfg == 025 ) THEN           !  ORCA_R025 configuration 
     111!! 
     112!!gm or better introduce the baltic change as a function of lat/lon of the baltic sea 
     113!!end gm 
     114            ENDIF 
    118115         ENDIF 
    119116         ! 
    120117      ENDIF 
    121118 
    122       !------------------------------------------! 
    123       !      heat flux at the ocean surface      ! 
    124       !------------------------------------------! 
    125  
    126 !!gm 
    127 !!gm CAUTION    
    128 !!gm re-verifies the non solar expression, especially over open ocen 
    129 !!gm 
    130       zqnsoce(:,:) = qns(:,:) 
     119      zqnsoce(:,:) = qns(:,:)      ! save non-solar flux prior to its modification by ice-ocean fluxes (diag.) 
     120      ! 
     121      zswitch = 1       ! standard levitating sea-ice : salt exchange only 
     122      ! 
     123!!gm ice embedment 
     124!      SELECT CASE( nn_ice_embd )       ! levitating/embedded sea-ice 
     125!      CASE( 0    )   ;   zswitch = 1       ! standard levitating sea-ice : salt exchange only 
     126!      CASE( 1, 2 )   ;   zswitch = 0       ! other levitating sea-ice or embedded sea-ice : salt and volume fluxes 
     127!      END SELECT                           !     
     128!!gm end embedment 
     129 
    131130      DO jj = 1, jpj 
    132131         DO ji = 1, jpi 
     132            !                          !------------------------------------------! 
     133            !                          !      heat flux at the ocean surface      ! 
     134            !                          !------------------------------------------! 
    133135            zinda   = 1.0   - MAX( rzero , SIGN( rone, - ( 1.0 - pfrld(ji,jj) )   ) ) 
    134136            ifvt    = zinda * MAX( rzero , SIGN( rone,  - phicif(ji,jj)           ) ) 
     
    138140            ial     = ifvt   * i1mfr + ( 1 - ifvt ) * idfr 
    139141            iadv    = ( 1  - i1mfr ) * zinda 
    140             ifral   = ( 1  - i1mfr * ( 1 - ial ) )    
    141             ifrdv   = ( 1  - ifral * ( 1 - ial ) ) * iadv  
    142  
    143 !!$            zinda   = 1.0 - AINT( pfrld(ji,jj) )                   !   = 0. if pure ocean else 1. (at previous time) 
    144 !!$ 
    145 !!$            i1mfr   = 1.0 - AINT(  frld(ji,jj) )                   !   = 0. if pure ocean else 1. (at current  time) 
    146 !!$ 
    147 !!$            IF( phicif(ji,jj) <= 0. ) THEN   ;   ifvt = zinda      !   = 1. if (snow and no ice at previous time) else 0. ??? 
    148 !!$            ELSE                             ;   ifvt = 0. 
    149 !!$            ENDIF 
    150 !!$ 
    151 !!$            IF( frld(ji,jj) >= pfrld(ji,jj) ) THEN   ;   idfr = 0.  !   = 0. if lead fraction increases from previous to current 
    152 !!$            ELSE                                     ;   idfr = 1.    
    153 !!$            ENDIF 
    154 !!$ 
    155 !!$            iflt    = zinda  * (1 - i1mfr) * (1 - ifvt )    !   = 1. if ice (not only snow) at previous and pure ocean at current 
    156 !!$ 
     142            ifral   = ( 1  - i1mfr * ( 1 - ial ) ) 
     143            ifrdv   = ( 1  - ifral * ( 1 - ial ) ) * iadv 
     144 
     145!!gm  attempt to understand and comment the tricky flags used here.... 
     146! 
     147!gm      zinda   = 1.0 - AINT( pfrld(ji,jj) )    ! = 0. free-ice ocean else 1. (after ice adv, but before ice thermo) 
     148!gm      i1mfr   = 1.0 - AINT(  frld(ji,jj) )    ! = 0. free-ice ocean else 1. (after ice thermo) 
     149! 
     150!gm      IF( phicif(ji,jj) <= 0. ) THEN   ;   ifvt = zinda   ! = 1. if (snow and no ice at previous time) else 0. ??? 
     151!gm      ELSE                             ;   ifvt = 0.      ! correspond to a overmelting of snow in surface ablation 
     152!gm      ENDIF                                               !  
     153! 
     154!gm      IF( frld(ji,jj) >= pfrld(ji,jj) ) THEN   ;   idfr = 0.  !   = 0. if lead fraction increases due to ice thermo 
     155!gm      ELSE                                     ;   idfr = 1.    
     156!gm      ENDIF 
     157! 
     158!!$      iflt    = zinda  * (1 - i1mfr) * (1 - ifvt ) ! = 1. if ice (not only snow) at previous and pure ocean at current 
     159! 
    157160!!$            ial     = ifvt   * i1mfr    +    ( 1 - ifvt ) * idfr 
    158161!!$!                 snow no ice   ice         ice or nothing  lead fraction increases 
    159162!!$!                 at previous   now           at previous 
    160163!!$!                -> ice aera increases  ???         -> ice aera decreases ??? 
    161 !!$ 
     164! 
    162165!!$            iadv    = ( 1  - i1mfr ) * zinda   
    163166!!$!                     pure ocean      ice at 
    164167!!$!                     at current      previous 
    165168!!$!                        -> = 1. if ice disapear between previous and current 
    166 !!$ 
     169! 
    167170!!$            ifral   = ( 1  - i1mfr * ( 1 - ial ) )   
    168171!!$!                            ice at     ??? 
    169172!!$!                            current          
    170173!!$!                         -> ??? 
    171 !!$  
     174! 
    172175!!$            ifrdv   = ( 1  - ifral * ( 1 - ial ) ) * iadv  
    173176!!$!                                                    ice disapear                            
    174 !!$ 
    175 !!$ 
    176  
    177             !   computation the solar flux at ocean surface 
     177! 
     178            ! 
     179            ! - computation the solar flux at ocean surface 
    178180#if defined key_coupled  
    179181            zqsr = qsr_tot(ji,jj) + ( fstric(ji,jj) - qsr_ice(ji,jj,1) ) * ( 1.0 - pfrld(ji,jj) ) 
     
    181183            zqsr = pfrld(ji,jj) * qsr(ji,jj)  + ( 1.  - pfrld(ji,jj) ) * fstric(ji,jj) 
    182184#endif             
    183             !  computation the non solar heat flux at ocean surface 
     185            ! 
     186            ! - computation the non solar heat flux at ocean surface 
    184187            zqns    =  - ( 1. - thcm(ji,jj) ) * zqsr   &   ! part of the solar energy used in leads 
    185                &       + iflt    * ( fscmbq(ji,jj) + ffltbif(ji,jj) )                            & 
    186                &       + ifral   * ( ial * qcmif(ji,jj) + (1 - ial) * qldif(ji,jj) ) * zrdtir    & 
    187                &       + ifrdv   * ( qfvbq(ji,jj) + qdtcn(ji,jj) ) * zrdtir 
    188  
    189             fsbbq(ji,jj) = ( 1.0 - ( ifvt + iflt ) ) * fscmbq(ji,jj)     ! ??? 
    190              
    191             qsr  (ji,jj) = zqsr                                          ! solar heat flux  
    192             qns  (ji,jj) = zqns - fdtcn(ji,jj)                           ! non solar heat flux 
     188               &       + iflt    * ( fscmbq(ji,jj) + ffltbif(ji,jj) )                                & 
     189               &       + ifral   * ( ial * qcmif(ji,jj) + (1 - ial) * qldif(ji,jj) ) * r1_rdt_ice    & 
     190               &       + ifrdv   * (       qfvbq(ji,jj) +             qdtcn(ji,jj) ) * r1_rdt_ice 
     191 
     192            ! - store residual heat flux (put in the ocean at the next time-step) 
     193            fsbbq(ji,jj) = ( 1.0 - ( ifvt + iflt ) ) * fscmbq(ji,jj)   ! ??? 
     194            ! 
     195            ! - heat content of mass exchanged between ocean and sea-ice 
     196            zqhc = ( rdq_snw(ji,jj) + rdq_ice(ji,jj) ) * r1_rdt_ice    ! heat flux due to sown & ice heat content exchanges 
     197            !             
     198            qsr(ji,jj) = zqsr                                          ! solar heat flux  
     199            qns(ji,jj) = zqns - fdtcn(ji,jj) + zqhc                    ! non solar heat flux 
     200   
     201            !                          !------------------------------------------! 
     202            !                          !      mass flux at the ocean surface      ! 
     203            !                          !------------------------------------------! 
     204            ! 
     205            ! mass flux at the ocean-atmosphere interface (open ocean fraction = leads area) 
     206#if defined key_coupled 
     207            !                                                       ! coupled mode:  
     208            zemp = + emp_tot(ji,jj)                              &       ! net mass flux over the grid cell (ice+ocean area) 
     209               &   - emp_ice(ji,jj) * ( 1. - pfrld(ji,jj) )              ! minus the mass flux intercepted by sea-ice 
     210#else 
     211            !                                                       ! forced  mode:  
     212            zemp = + emp(ji,jj)     *         frld(ji,jj)      &         ! mass flux over open ocean fraction  
     213               &   - tprecip(ji,jj) * ( 1. -  frld(ji,jj) )    &         ! liquid precip. over ice reaches directly the ocean 
     214               &   + sprecip(ji,jj) * ( 1. - pfrld(ji,jj) )    &         ! snow is intercepted by sea-ice (previous frld) 
     215#endif             
     216            ! 
     217            ! mass flux at the ocean/ice interface (sea ice fraction) 
     218            zemp_snw = rdm_snw(ji,jj) * r1_rdt_ice                  ! snow melting = pure water that enters the ocean 
     219            zfmm     = rdm_ice(ji,jj) * r1_rdt_ice                  ! Freezing minus Melting (F-M) 
     220 
     221            ! salt flux at the ice/ocean interface (sea ice fraction) [PSU*kg/m2/s] 
     222            zfsalt = - sice_r(ji,jj) * zfmm                         ! F-M salt exchange 
     223            zcd    =   soce_r(ji,jj) * zfmm                         ! concentration/dilution term due to F-M 
     224            ! 
     225            ! salt flux only       : add concentration dilution term in salt flux  and no  F-M term in volume flux 
     226            ! salt and mass fluxes : non concentartion dilution term in salt flux  and add F-M term in volume flux 
     227            emps(ji,jj) = zfsalt +                  zswitch  * zcd   ! salt flux (+ C/D if no ice/ocean mass exchange) 
     228            emp (ji,jj) = zemp   + zemp_snw + ( 1.- zswitch) * zfmm  ! mass flux (- F/M mass flux if no ice/ocean mass exchange) 
     229            ! 
    193230         END DO 
    194231      END DO 
     232 
    195233 
    196234      CALL iom_put( 'hflx_ice_cea', - fdtcn(:,:) )       
    197235      CALL iom_put( 'qns_io_cea', qns(:,:) - zqnsoce(:,:) * pfrld(:,:) )       
    198236      CALL iom_put( 'qsr_io_cea', fstric(:,:) * (1. - pfrld(:,:)) ) 
    199  
    200       !------------------------------------------! 
    201       !      mass flux at the ocean surface      ! 
    202       !------------------------------------------! 
    203  
    204 !!gm 
    205 !!gm CAUTION    
    206 !!gm re-verifies the emp & emps expression, especially the absence of 1-frld on zfm 
    207 !!gm 
    208       DO jj = 1, jpj 
    209          DO ji = 1, jpi 
    210              
    211 #if defined key_coupled 
    212           zemp = emp_tot(ji,jj) - emp_ice(ji,jj) * ( 1. - pfrld(ji,jj) )    &   !  
    213              &   + rdm_snw(ji,jj) * zrdtir                                      !  freshwaterflux due to snow melting  
    214 #else 
    215 !!$            !  computing freshwater exchanges at the ice/ocean interface 
    216 !!$            zpme = - evap(ji,jj)    *   frld(ji,jj)           &   !  evaporation over oceanic fraction 
    217 !!$               &   + tprecip(ji,jj)                           &   !  total precipitation 
    218 !!$               &   - sprecip(ji,jj) * ( 1. - pfrld(ji,jj) )   &   !  remov. snow precip over ice 
    219 !!$               &   - rdm_snw(ji,jj) / rdt_ice                     !  freshwaterflux due to snow melting  
    220             !  computing freshwater exchanges at the ice/ocean interface 
    221             zemp = + emp(ji,jj)     *         frld(ji,jj)      &   !  e-p budget over open ocean fraction  
    222                &   - tprecip(ji,jj) * ( 1. -  frld(ji,jj) )    &   !  liquid precipitation reaches directly the ocean 
    223                &   + sprecip(ji,jj) * ( 1. - pfrld(ji,jj) )    &   !  taking into account change in ice cover within the time step 
    224                &   + rdm_snw(ji,jj) * zrdtir                       !  freshwaterflux due to snow melting  
    225                !                                                   !  ice-covered fraction: 
    226 #endif             
    227  
    228             !  computing salt exchanges at the ice/ocean interface 
    229             zfons =  ( soce_r(ji,jj) - sice_r(ji,jj) ) * ( rdm_ice(ji,jj) * zrdtir )  
    230              
    231             !  converting the salt flux from ice to a freshwater flux from ocean 
    232             zfm  = zfons / ( sss_m(ji,jj) + epsi16 ) 
    233              
    234             emps(ji,jj) = zemp + zfm      ! surface ocean concentration/dilution effect (use on SSS evolution) 
    235             emp (ji,jj) = zemp            ! surface ocean volume flux (use on sea-surface height evolution) 
    236  
    237          END DO 
    238       END DO 
    239237 
    240238      IF( lk_diaar5 ) THEN 
     
    250248      IF ( ln_limdyn ) THEN                        ! Update the stress over ice-over area (only in ice-dynamic case) 
    251249         !                                         ! otherwise the atmosphere-ocean stress is used everywhere 
    252  
     250         ! 
    253251         ! ... ice stress over ocean with a ice-ocean rotation angle (at I-point) 
    254252!CDIR NOVERRCHK 
     
    290288            END DO 
    291289         END DO 
    292  
    293          ! boundary condition on the stress (utau,vtau,taum) 
    294          CALL lbc_lnk( utau, 'U', -1. ) 
    295          CALL lbc_lnk( vtau, 'V', -1. ) 
     290         CALL lbc_lnk( utau, 'U', -1. )   ;   CALL lbc_lnk( vtau, 'V', -1. )         ! lateral boundary conditions 
    296291         CALL lbc_lnk( taum, 'T',  1. ) 
    297  
     292         ! 
    298293      ENDIF 
    299294 
    300295      !-----------------------------------------------! 
    301       !   Coupling variables                          ! 
     296      !   Storing the transmitted variables           ! 
    302297      !-----------------------------------------------! 
    303  
    304       IF ( lk_cpl ) THEN            
    305          ! Ice surface temperature  
     298!!gm where this is done ?????   ==>>> limthd_2   not logic ??? 
     299!!gm      fr_i(:,:) = 1.0 - frld(:,:)       ! sea-ice fraction 
     300!!gm 
     301 
     302      IF ( lk_cpl ) THEN      ! coupled mode : 
    306303         tn_ice(:,:,1) = sist(:,:)          ! sea-ice surface temperature        
    307          ! Computation of snow/ice and ocean albedo 
     304         !                                  ! snow/ice and ocean albedo 
    308305         CALL albedo_ice( tn_ice, reshape( hicif, (/jpi,jpj,1/) ), reshape( hsnif, (/jpi,jpj,1/) ), zalbp, zalb ) 
    309306         alb_ice(:,:,1) =  0.5 * ( zalbp(:,:,1) + zalb (:,:,1) )   ! Ice albedo (mean clear and overcast skys) 
     307         ! 
    310308         CALL iom_put( "icealb_cea", alb_ice(:,:,1) * fr_i(:,:) )  ! ice albedo 
    311309      ENDIF 
     
    318316         CALL prt_ctl(tab2d_1=fr_i  , clinfo1=' lim_sbc: fr_i   : ', tab2d_2=tn_ice(:,:,1), clinfo2=' tn_ice  : ') 
    319317      ENDIF  
    320     
    321     END SUBROUTINE lim_sbc_2 
     318      ! 
     319   END SUBROUTINE lim_sbc_2 
    322320 
    323321#else 
  • branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2/thd_ice_2.F90

    r1858 r1859  
    88   !!           2.1  ! 2010-05  (Y. Aksenov, M. Vancoppenolle, G. Madec) add heat content exchanges 
    99   !!---------------------------------------------------------------------- 
    10    !!   LIM 2.0, UCL-LOCEAN-IPSL (2005) 
     10   !! NEMO/LIM 3.3, UCL-LOCEAN-IPSL (2010) 
    1111   !! $Id$ 
    12    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
     12   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    1313   !!---------------------------------------------------------------------- 
    14    !! * Modules used 
    1514   USE par_ice_2 
    1615 
Note: See TracChangeset for help on using the changeset viewer.