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 833 – NEMO

Changeset 833


Ignore:
Timestamp:
2008-03-07T14:51:35+01:00 (16 years ago)
Author:
rblod
Message:

Merge branche dev_002_LIM back to trunk ticket #70 and #71

Location:
trunk
Files:
3 deleted
24 edited
5 copied

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/C1D_SRC/diawri1d.F90

    r719 r833  
    194194            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    195195 
    196 #if ! defined key_dynspg_rl && defined key_ice_lim 
     196#if ! defined key_dynspg_rl && defined key_lim3 
    197197         ! sowaflup = sowaflep + sorunoff + sowafldp + a term associated to 
    198198         !    internal damping to Levitus that can be diagnosed from others 
     
    238238#endif 
    239239 
    240 #if ( defined key_coupled && ! defined key_ice_lim )  
     240#if ( defined key_coupled && ! defined key_lim3 )  
    241241         CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
    242242            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     
    260260#endif 
    261261 
    262 #if defined key_ice_lim && defined key_coupled 
     262#if defined key_lim3 && defined key_coupled 
    263263         CALL histdef( nid_T,"soicetem" , "Ice Surface Temperature"            , "K"      ,   &  ! tn_ice 
    264264            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     
    365365      CALL histwrite( nid_T, "sosstsst", it, tn(:,:,1)     , ndim_hT, ndex_hT )   ! sea surface temperature 
    366366      CALL histwrite( nid_T, "sosaline", it, sn(:,:,1)     , ndim_hT, ndex_hT )   ! sea surface salinity 
    367 #if ! defined key_dynspg_rl && defined key_ice_lim 
     367#if ! defined key_dynspg_rl && defined key_lim3 
    368368      CALL histwrite( nid_T, "iowaflup", it, fsalt(:,:)    , ndim_hT, ndex_hT )   ! ice=>ocean water flux 
    369369      CALL histwrite( nid_T, "sowaflep", it, fmass(:,:)    , ndim_hT, ndex_hT )   ! atmos=>ocean water flux 
     
    397397      CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
    398398#endif 
    399 #if ( defined key_coupled && ! defined key_ice_lim )  
     399#if ( defined key_coupled && ! defined key_lim3 )  
    400400      CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
    401401      CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
     
    412412      CALL histwrite( nid_T, "sohtc300", it, htc3          , ndim_hT, ndex_hT )   ! first 300m heaat content 
    413413#endif 
    414 #if defined key_ice_lim &&  defined key_coupled  
     414#if defined key_lim3 &&  defined key_coupled  
    415415      CALL histwrite( nid_T, "soicetem", it, tn_ice        , ndim_hT, ndex_hT )   ! surf. ice temperature 
    416416      CALL histwrite( nid_T, "soicealb", it, alb_ice       , ndim_hT, ndex_hT )   ! ice albedo 
  • trunk/NEMO/C1D_SRC/icestp1d.F90

    r719 r833  
    66   !! History :   9.0  !  04-10  (C. Ethe)  from icestp, 1D configuration 
    77   !!---------------------------------------------------------------------- 
    8 #if defined key_cfg_1d && defined key_ice_lim 
     8#if defined key_cfg_1d && defined key_lim3 
    99   !!---------------------------------------------------------------------- 
    1010   !!   'key_cfg_1d'  .AND.                                1D Configuration 
    11    !!   'key_ice_lim'                                     Lim sea-ice model 
     11   !!   'key_lim3'                                     Lim sea-ice model 
    1212   !!---------------------------------------------------------------------- 
    1313   !!---------------------------------------------------------------------- 
  • trunk/NEMO/NST_SRC/agrif_user.F90

    r782 r833  
    6262      USE sol_oce 
    6363      USE in_out_manager 
    64 #if defined key_ice_lim 
     64#if defined key_lim3 || defined key_lim3_old 
    6565      USE ice_oce 
    6666#endif 
  • trunk/NEMO/OPA_SRC/DIA/diawri.F90

    r719 r833  
    245245            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    246246#endif 
    247 #if ! defined key_dynspg_rl && defined key_ice_lim 
     247#if ! defined key_dynspg_rl && ( defined key_lim3 || defined key_lim2 ) 
    248248         ! sowaflup = sowaflep + sorunoff + sowafldp + a term associated to 
    249249         !    internal damping to Levitus that can be diagnosed from others 
     
    291291 
    292292 
    293 #if ( defined key_coupled && ! defined key_ice_lim )  
     293#if defined key_coupled &&  ! defined key_lim3 && ! defined key_lim2   
    294294         CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
    295295            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     
    317317#endif 
    318318 
    319 #if defined key_ice_lim && defined key_coupled 
     319#if ( defined key_lim3  || defined key_lim2 ) && defined key_coupled 
    320320         CALL histdef( nid_T,"soicetem" , "Ice Surface Temperature"            , "K"      ,   &  ! tn_ice 
    321321            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     
    423423      CALL histwrite( nid_T, "sossheig", it, sshn          , ndim_hT, ndex_hT )   ! sea surface height 
    424424#endif 
    425 #if ! defined key_dynspg_rl && defined key_ice_lim 
     425#if ! defined key_dynspg_rl && ( defined key_lim3 || defined key_lim2 ) 
    426426      CALL histwrite( nid_T, "iowaflup", it, fsalt(:,:)    , ndim_hT, ndex_hT )   ! ice=>ocean water flux 
    427427      CALL histwrite( nid_T, "sowaflep", it, fmass(:,:)    , ndim_hT, ndex_hT )   ! atmos=>ocean water flux 
     
    448448      CALL histwrite( nid_T, "sosbhfup", it, qsb           , ndim_hT, ndex_hT )   ! sensible heat flux 
    449449#endif 
    450 #if ( defined key_coupled && ! defined key_ice_lim )  
     450#if  defined key_coupled && ! defined key_lim3 && ! defined key_lim2  
    451451      CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
    452452      CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
     
    466466      CALL histwrite( nid_T, "sohtc300", it, htc3          , ndim_hT, ndex_hT )   ! first 300m heaat content 
    467467#endif 
    468 #if defined key_ice_lim &&  defined key_coupled  
     468#if ( defined key_lim3  ||  defined key_lim2 ) &&  defined key_coupled  
    469469      CALL histwrite( nid_T, "soicetem", it, tn_ice        , ndim_hT, ndex_hT )   ! surf. ice temperature 
    470470      CALL histwrite( nid_T, "soicealb", it, alb_ice       , ndim_hT, ndex_hT )   ! ice albedo 
  • trunk/NEMO/OPA_SRC/DIA/diawri_dimg.h90

    r719 r833  
    187187       !        fsel(:,:,15) = fsel(:,:,15) + fbt(:,:) 
    188188       fsel(:,:,16) = fsel(:,:,16) + emps(:,:) 
    189 #if defined key_ice_lim 
     189#if defined key_lim3 || defined key_lim3_old 
    190190       fsel(:,:,17) = fsel(:,:,17) + fsalt(:,:) 
    191191#endif 
     
    277277          !         fsel(:,:,15) =  fbt(:,:) 
    278278          fsel(:,:,16) =  emps(:,:) * tmask(:,:,1) 
    279 #if defined key_ice_lim 
     279#if defined key_lim3 || defined key_lim3_old 
    280280          fsel(:,:,17) =  fsalt(:,:) * tmask(:,:,1) 
    281281#endif 
  • trunk/NEMO/OPA_SRC/DOM/domain.F90

    r783 r833  
    257257      ENDIF 
    258258 
    259       IF( lk_ice_lim ) THEN 
     259      IF( lk_lim3 .OR. lk_lim2 ) THEN 
    260260         IF(lwp) WRITE(numout,*) '           ice model coupling frequency      nfice  = ', nfice 
    261261         IF( MOD( nitend - nit000 + 1, nfice) /= 0 ) THEN  
  • trunk/NEMO/OPA_SRC/SBC/albedo.F90

    r719 r833  
    3737      c1     = 0.05  ,     &   ! constants values 
    3838      c2     = 0.10  ,     & 
     39#if defined key_lim3 
     40      albice = 0.53  ,     &   !  albedo of melting ice in the arctic and antarctic (Shine & Hendersson-Sellers) 
     41#else 
    3942      albice = 0.50  ,     &   !  albedo of melting ice in the arctic and antarctic (Shine & Hendersson-Sellers) 
     43#endif 
    4044      cgren  = 0.06  ,     &   !  correction of the snow or ice albedo to take into account 
    4145                               !  effects of cloudiness (Grenfell & Perovich, 1984) 
     
    5357CONTAINS 
    5458 
    55 #if defined key_ice_lim 
    56    !!---------------------------------------------------------------------- 
    57    !!   'key_ice_lim'                                         LIM ice model 
     59#if defined key_lim3 || defined key_lim2 
     60   !!---------------------------------------------------------------------- 
     61   !!   'key_lim3' OR 'key_lim2'               LIM 2.0 or LIM 3.0 ice model 
    5862   !!---------------------------------------------------------------------- 
    5963 
     
    7579      !!  8.0   !  01-04  (LIM 1.0) 
    7680      !!  8.5   !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine) 
     81      !!  9.0   !  01-06  (M. Vancoppenolle) LIM 3.0 
    7782      !!---------------------------------------------------------------------- 
    7883      !! * Modules used 
     84#if defined key_lim3 
     85      USE par_ice 
    7986      USE ice                   ! ??? 
     87#elif defined key_lim2 
     88      USE ice_2                 ! ??? 
     89#endif 
    8090 
    8191      !! * Arguments 
     92#if defined key_lim3 
     93      REAL(wp), DIMENSION(jpi,jpj,jpl), INTENT(out) ::  & 
     94#elif defined key_lim2 
    8295      REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  & 
     96#endif 
    8397         palb         ,     &    !  albedo of ice under overcast sky 
     98         palbp                   !  albedo of ice under clear sky  
     99      REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  & 
    84100         palcn        ,     &    !  albedo of ocean under overcast sky 
    85          palbp        ,     &    !  albedo of ice under clear sky  
    86101         palcnp                  !  albedo of ocean under clear sky 
    87102 
    88103      !! * Local variables 
    89104      INTEGER ::    & 
    90          ji, jj                   ! dummy loop indices 
     105         ji, jj, jl               ! dummy loop indices 
    91106      REAL(wp) ::   &  
    92107         zmue14         ,     &   !  zmue**1.4 
     
    96111         zalbpic        ,     &   !  albedo of snow/ice system when ice is free of snow 
    97112         zithsn         ,     &   !  = 1 for hsn >= 0 ( ice is cov. by snow ) ; = 0 otherwise (ice is free of snow) 
    98          zitmlsn        ,     &   !  = 1 freezinz snow (sist >=rt0_snow) ; = 0 melting snow (sist<rt0_snow) 
     113         zitmlsn        ,     &   !  = 1 freezinz snow (t_su >=rt0_snow) ; = 0 melting snow (t_su<rt0_snow) 
    99114         zihsc1         ,     &   !  = 1 hsn <= c1 ; = 0 hsn > c1 
    100115         zihsc2                   !  = 1 hsn >= c2 ; = 0 hsn < c2 
     116#if defined key_lim3 
     117      REAL(wp), DIMENSION(jpi,jpj,jpl) ::  & 
     118#elif defined key_lim2 
    101119      REAL(wp), DIMENSION(jpi,jpj) ::  & 
     120#endif 
    102121         zalbfz         ,     &   !  ( = alphdi for freezing ice ; = albice for melting ice ) 
    103122         zficeth                  !  function of ice thickness 
     123#if defined key_lim3 
     124      LOGICAL , DIMENSION(jpi,jpj,jpl) ::  & 
     125#elif defined key_lim2 
    104126      LOGICAL , DIMENSION(jpi,jpj) ::  & 
     127#endif 
    105128         llmask 
    106129      !!--------------------------------------------------------------------- 
     
    112135      !  Computation of  zficeth 
    113136      !--------------------------  
    114        
     137#if defined key_lim3 
     138      llmask = (ht_s(:,:,:) == 0.e0) .AND. ( t_su(:,:,:) >= rt0_ice ) 
     139#elif defined key_lim2       
    115140      llmask = (hsnif == 0.e0) .AND. ( sist >= rt0_ice ) 
     141#endif 
    116142      WHERE ( llmask )   !  ice free of snow and melts 
    117143         zalbfz = albice 
     
    120146      END WHERE 
    121147       
     148#if defined key_lim3 
     149      DO jl = 1, jpl 
     150         DO jj = 1, jpj 
     151            DO ji = 1, jpi 
     152               IF( ht_i(ji,jj,jl) > 1.5 ) THEN 
     153                  zficeth(ji,jj,jl) = zalbfz(ji,jj,jl) 
     154               ELSEIF( ht_i(ji,jj,jl) > 1.0  .AND. ht_i(ji,jj,jl) <= 1.5 ) THEN 
     155                  zficeth(ji,jj,jl) = 0.472 + 2.0 * ( zalbfz(ji,jj,jl) - 0.472 ) * ( ht_i(ji,jj,jl) - 1.0 ) 
     156               ELSEIF( ht_i(ji,jj,jl) > 0.05 .AND. ht_i(ji,jj,jl) <= 1.0 ) THEN 
     157                  zficeth(ji,jj,jl) = 0.2467 + 0.7049 * ht_i(ji,jj,jl)                               & 
     158                     &                    - 0.8608 * ht_i(ji,jj,jl) * ht_i(ji,jj,jl)                 & 
     159                     &                    + 0.3812 * ht_i(ji,jj,jl) * ht_i(ji,jj,jl) * ht_i (ji,jj,jl) 
     160               ELSE 
     161                  zficeth(ji,jj,jl) = 0.1 + 3.6 * ht_i(ji,jj,jl)  
     162               ENDIF 
     163            END DO 
     164         END DO 
     165      END DO 
     166#elif defined key_lim2       
    122167      DO jj = 1, jpj 
    123168         DO ji = 1, jpi 
     
    135180         END DO 
    136181      END DO 
     182#endif 
    137183       
    138184      !-----------------------------------------------  
     
    142188      !    Albedo of snow-ice for clear sky. 
    143189      !-----------------------------------------------     
     190#if defined key_lim3 
     191      DO jl = 1, jpl 
     192         DO jj = 1, jpj 
     193            DO ji = 1, jpi 
     194               !  Case of ice covered by snow.              
     195             
     196               !  freezing snow         
     197               zihsc1       = 1.0 - MAX ( zzero , SIGN ( zone , - ( ht_s(ji,jj,jl) - c1 ) ) ) 
     198               zalbpsnf     = ( 1.0 - zihsc1 ) * ( zficeth(ji,jj,jl) + ht_s(ji,jj,jl) * ( alphd - zficeth(ji,jj,jl) ) / c1 ) & 
     199                  &                 + zihsc1   * alphd   
     200 
     201               !  melting snow                 
     202               zihsc2       = MAX ( zzero , SIGN ( zone , ht_s(ji,jj,jl) - c2 ) ) 
     203               zalbpsnm     = ( 1.0 - zihsc2 ) * ( albice + ht_s(ji,jj,jl) * ( alphc - albice ) / c2 )                 & 
     204                  &                 + zihsc2   * alphc  
     205 
     206 
     207               zitmlsn      =  MAX ( zzero , SIGN ( zone , t_su(ji,jj,jl) - rt0_snow ) )    
     208               zalbpsn      =  zitmlsn * zalbpsnm + ( 1.0 - zitmlsn ) * zalbpsnf 
     209             
     210               !  Case of ice free of snow. 
     211               zalbpic      = zficeth(ji,jj,jl)  
     212             
     213               ! albedo of the system    
     214               zithsn       = 1.0 - MAX ( zzero , SIGN ( zone , - ht_s(ji,jj,jl) ) ) 
     215               palbp(ji,jj,jl) =  zithsn * zalbpsn + ( 1.0 - zithsn ) *  zalbpic 
     216            END DO 
     217         END DO 
     218      END DO 
     219       
     220      !    Albedo of snow-ice for overcast sky. 
     221      !----------------------------------------------   
     222      palb(:,:,:)   = palbp(:,:,:) + cgren       ! Oberhuber correction 
     223 
     224#elif defined key_lim2       
     225 
    144226      DO jj = 1, jpj 
    145227         DO ji = 1, jpi 
     
    170252      !----------------------------------------------   
    171253      palb(:,:)   = palbp(:,:) + cgren                                            
     254#endif 
    172255       
    173256      !-------------------------------------------- 
  • trunk/NEMO/OPA_SRC/SBC/bulk.F90

    r719 r833  
    5050      !! * Local declarations     
    5151      REAL(wp), DIMENSION(jpi,jpj) ::   zsst  
    52 # if ! defined key_ice_lim 
     52# if ( ! defined key_lim3 && !defined key_lim2 ) 
    5353      INTEGER  ::   ji, jj         ! dummy loop indices   
    5454      REAL(wp) ::   ztgel, zicopa 
     
    6969     ENDIF 
    7070 
    71 # if ! defined key_ice_lim 
     71# if ( ! defined key_lim3 && ! defined key_lim2 ) 
    7272      ! opa model ice freeze()       
    7373      DO jj = 1, jpj 
     
    8787 
    8888         zsst(:,:) = gsst(:,:) / REAL( nfbulk ) * tmask(:,:,1) 
     89 
    8990         CALL flx_blk( zsst )     
    9091      
    9192         gsst(:,:) = 0.     
    9293 
    93 # if ! defined key_ice_lim 
     94# if ( ! defined key_lim3 && ! defined key_lim2 ) 
    9495         IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    9596            CALL prt_ctl_info(' Forcings ') 
  • trunk/NEMO/OPA_SRC/SBC/flx_oce.F90

    r719 r833  
    1313   !! * Modules used 
    1414   USE par_oce          ! ocean parameters 
     15# if defined key_lim3 
     16   USE par_ice 
     17# endif 
    1518 
    1619   IMPLICIT NONE 
     
    3033      p_emp             !: evaporation minus precipitation             
    3134 
    32 #elif defined key_ice_lim || defined key_flx_bulk_monthly || defined key_flx_bulk_daily || defined key_flx_core 
     35#elif defined key_lim3 || defined key_lim2 || defined key_flx_bulk_monthly || defined key_flx_bulk_daily || defined key_flx_core 
     36 
     37#if defined key_lim3  
     38   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl)    ::   &  !: 
     39#else 
    3340   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)    ::   &  !: 
     41#endif 
    3442      qsr_ice  ,      &  !: solar flux over ice 
     43      tn_ice   ,      &  !: ice surface temperature 
     44      qnsr_ice ,      &  !: total non solar heat flux (Longwave downward radiation) over ice 
     45      dqns_ice           !: total non solar sensibility over ice (LW+SEN+LA) 
     46   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)    ::   &  !: 
    3547      qsr_oce  ,      &  !: solar flux over ocean 
    3648      qnsr_oce ,      &  !: total non solar heat flux (Longwave downward radiation) over ocean  
    37       qnsr_ice ,      &  !: total non solar heat flux (Longwave downward radiation) over ice 
    3849      tprecip  ,      &  !: total precipitation ( or liquid precip minus evaporation in coupled mode) 
    3950      sprecip  ,      &  !: solid (snow) precipitation 
    40       dqns_ice ,      &  !: total non solar sensibility over ice (LW+SEN+LA) 
    41       tn_ice   ,      &  !: ice surface temperature 
    4251      evap     ,      &  !: evaporation over ocean 
    4352      fr1_i0   ,      &  !: 1st part of the fraction of sol. rad.  which penetrate inside the ice cover 
    44       fr2_i0   ,      &  !: 2nd part of the fraction of sol. rad.  which penetrate inside the ice cover  
     53      fr2_i0             !: 2nd part of the fraction of sol. rad.  which penetrate inside the ice cover  
    4554#if ! defined key_coupled 
     55#if defined key_lim3  
     56   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl)    ::   &  !: 
     57#else 
     58   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)    ::   &  !: 
     59#endif 
    4660      qla_ice  ,      &  !: latent flux over ice   
    4761      dqla_ice           !: latent sensibility over ice 
    48 #else 
     62#elif  
     63   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)    ::   &  !: 
    4964      rrunoff  ,      &  !: runoff 
    5065      calving  ,      &  !: calving 
  • trunk/NEMO/OPA_SRC/SBC/flxblk.F90

    r789 r833  
    44   !! Ocean forcing:  bulk thermohaline forcing of the ocean (or ice) 
    55   !!===================================================================== 
    6 #if defined key_flx_bulk_monthly || defined key_flx_bulk_daily 
     6#if  defined key_flx_bulk_monthly || defined key_flx_bulk_daily  
    77   !!---------------------------------------------------------------------- 
    88   !!   'key_flx_bulk_monthly'   or                            MONTHLY bulk 
     
    2525   USE albedo 
    2626   USE prtctl          ! Print control 
    27  
     27#if defined key_lim3 
     28   USE par_ice 
     29   USE ice 
     30#elif defined key_lim2 
     31   USE ice_2 
     32#endif 
    2833   IMPLICIT NONE 
    2934   PRIVATE 
     
    7984 
    8085CONTAINS 
     86#if defined key_lim3 
     87 
     88   SUBROUTINE flx_blk( psst ) 
     89      !!--------------------------------------------------------------------------- 
     90      !!                     ***  ROUTINE flx_blk  *** 
     91      !!                  
     92      !!  ** Purpose :   Computation of the heat fluxes at ocean and snow/ice 
     93      !!       surface the solar heat at ocean and snow/ice surfaces and the  
     94      !!       sensitivity of total heat fluxes to the SST variations 
     95      !!          
     96      !!  ** Method  :   The flux of heat at the ice and ocean surfaces are derived 
     97      !!       from semi-empirical ( or bulk ) formulae which relate the flux to  
     98      !!       the properties of the surface and of the lower atmosphere. Here, we 
     99      !!       follow the work of Oberhuber, 1988    
     100      !! 
     101      !!  ** Action  :   call flx_blk_albedo to compute ocean and ice albedo  
     102      !!          computation of snow precipitation 
     103      !!          computation of solar flux at the ocean and ice surfaces 
     104      !!          computation of the long-wave radiation for the ocean and sea/ice 
     105      !!          computation of turbulent heat fluxes over water and ice 
     106      !!          computation of evaporation over water 
     107      !!          computation of total heat fluxes sensitivity over ice (dQ/dT) 
     108      !!          computation of latent heat flux sensitivity over ice (dQla/dT) 
     109      !! 
     110      !! History : 
     111      !!   8.0  !  97-06  (Louvain-La-Neuve)  Original code 
     112      !!   8.5  !  02-09  (C. Ethe , G. Madec )  F90: Free form and module 
     113      !!---------------------------------------------------------------------- 
     114      !! * Arguments 
     115      REAL(wp), INTENT( in ), DIMENSION(jpi,jpj) ::   & 
     116         &                          psst      ! Sea Surface Temperature  
     117 
     118      !! * Local variables 
     119      INTEGER  ::             & 
     120         ji, jj, jl, jt    ,  &  ! dummy loop indices 
     121         indaet            ,  &  !  = -1, 0, 1 for odd, normal and leap years resp. 
     122         iday              ,  &  ! integer part of day 
     123         indxb             ,  &  ! index for budyko coefficient 
     124         indxc                   ! index for cloud depth coefficient 
     125 
     126      REAL(wp)  ::            &  
     127         zalat , zclat     ,  &  ! latitude in degrees  
     128         zmt1, zmt2, zmt3  ,  &  ! tempory air temperatures variables 
     129         ztatm3, ztatm4    ,  &  ! power 3 and 4 of air temperature 
     130         z4tatm3           ,  &  ! 4 * ztatm3 
     131         zcmue             ,  &  ! cosine of local solar altitude 
     132         zcmue2            ,  &  ! root of zcmue1  
     133         zscmue            ,  &  ! square-root of zcmue1  
     134         zpcmue            ,  &  ! zcmue1**1.4 
     135         zdecl             ,  &  ! solar declination 
     136         zsdecl , zcdecl   ,  &  ! sine and cosine of solar declination  
     137         zalbo             ,  &  ! albedo of sea-water 
     138         zalbi             ,  &  ! albedo of ice 
     139         ztamr             ,  &  ! air temperature minus triple point of water (rtt) 
     140         ztaevbk           ,  &  ! part of net longwave radiation 
     141         zevi , zevo       ,  &  ! vapour pressure of ice and ocean  
     142         zind1,zind2,zind3 ,  &  ! switch for testing the values of air temperature 
     143         zinda             ,  &  ! switch for testing the values of sea ice cover 
     144         zpis2             ,  &  ! pi / 2 
     145         z2pi                    ! 2 * pi  
     146 
     147      REAL(wp)  ::            &  
     148         zxday             ,  &  ! day of year 
     149         zdist             ,  &  ! distance between the sun and the earth during the year 
     150         zdaycor           ,  &  ! corr. factor to take into account the variation of  
     151         !                       ! zday when calc. the solar rad.     
     152         zesi, zeso        ,  &  ! vapour pressure of ice and ocean at saturation 
     153         zesi2             ,  &  ! root of zesi  
     154         zqsato            ,  &  ! humidity close to the ocean surface (at saturation)    
     155         zqsati            ,  &  ! humidity close to the ice surface (at saturation)  
     156         zqsati2           ,  &  ! root of  zqsati  
     157         zdesidt           ,  &  ! derivative of zesi, function of ice temperature 
     158         zdteta            ,  &  ! diff. betw. sst and air temperature 
     159         zdeltaq           ,  &  ! diff. betw. spec. hum. and hum. close to the surface 
     160         ztvmoy, zobouks   ,  &  ! tempory scalars 
     161         zpsims, zpsihs, zpsils, zobouku, zxins, zpsimu ,  &  
     162         zpsihu, zpsilu, zstab,zpsim, zpsih, zpsil      ,  &  
     163         zvatmg, zcmn, zchn, zcln, zcmcmn, zdenum       ,  &  
     164         zdtetar, ztvmoyr, zlxins, zcmn2, zchcm, zclcm , zcoef 
     165 
     166      REAL(wp)  ::            &  
     167         zrhova            ,  &  ! air density per wind speed 
     168         zcsho , zcleo     ,  &  ! transfer coefficient over ocean 
     169         zcshi , zclei     ,  &  ! transfer coefficient over ice-free 
     170         zrhovacleo        ,  &  ! air density per wind speed per transfer coef. 
     171         zrhovacsho, zrhovaclei, zrhovacshi, &  
     172         ztice3            ,  &  ! power 3 of ice temperature 
     173         zticemb, zticemb2 ,  &  ! tempory air temperatures variables 
     174         zdqlw_ice         ,  &  ! sensitivity of long-wave flux over ice 
     175         zdqsb_ice         ,  &  ! sensitivity of sensible heat flux over ice 
     176         zdqla_ice         ,  &  ! sensitivity of latent heat flux over ice 
     177         zdl, zdr                ! fractionnal part of latitude 
     178      REAL(wp), DIMENSION(jpi,jpj) :: &  
     179         zpatm            ,  &   ! atmospheric pressure 
     180         zqatm            ,  &   ! specific humidity 
     181         zes              ,  &   ! vapour pressure at saturation 
     182         zev, zevsqr      ,  &   ! vapour pressure and his square-root 
     183         zrhoa            ,  &   ! air density 
     184         ztatm            ,  &   ! air temperature in Kelvins 
     185         zfrld            ,  &   ! fraction of sea ice cover  
     186         zcatm1           ,  &   ! fraction of cloud 
     187         zcldeff                 ! correction factor to account cloud effect 
     188      REAL(wp), DIMENSION(jpi,jpj) ::   &  
     189         zalbocsd         ,  &   ! albedo of ocean 
     190         zalboos          ,  &   ! albedo of ocean under overcast sky 
     191         zalbomu          ,  &   ! albedo of ocean when zcmue is 0.4 
     192         zqsro            ,  &   ! solar radiation over ocean 
     193         zqsrics          ,  &   ! solar radiation over ice under clear sky 
     194         zqsrios          ,  &   ! solar radiation over ice under overcast sky 
     195         zcldcor          ,  &   ! cloud correction 
     196         zlsrise, zlsset  ,  &   ! sunrise and sunset 
     197         zlmunoon         ,  &   ! local noon solar altitude 
     198         zdlha            ,  &   ! length of the ninstr segments of the solar day 
     199         zps              ,  &   ! sine of latitude per sine of solar decli. 
     200         zpc                     ! cosine of latitude per cosine of solar decli.  
     201      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   &  
     202         zalbics          ,  &   ! albedo of ice under clear sky 
     203         zalbios                 ! albedo of ice under overcast sky 
     204 
     205      REAL(wp), DIMENSION(jpi,jpj) ::   &  
     206         zqlw_oce         ,  &   ! long-wave heat flux over ocean 
     207         zqla_oce         ,  &   ! latent heat flux over ocean 
     208         zqsb_oce                ! sensible heat flux over ocean 
     209  
     210      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   &  
     211         zqlw_ice         ,  &   ! long-wave heat flux over ice 
     212         zqla_ice         ,  &   ! latent heat flux over ice 
     213         zqsb_ice                ! sensible heat flux over ice 
     214  
     215      REAL(wp), DIMENSION(jpi,jpj,jpintsr) ::    & 
     216         zlha             ,  &   ! local hour angle 
     217         zalbocs          ,  &   ! tempory var. of ocean albedo under clear sky 
     218         zsqsro           ,  &   ! tempory var. of solar rad. over ocean  
     219         zsqsrics         ,  &   ! temp. var. of solar rad. over ice under clear sky 
     220         zsqsrios                ! temp. var. of solar rad. over ice under overcast sky 
     221      !!--------------------------------------------------------------------- 
     222 
     223      !  Determine cloud optical depths as a function of latitude (Chou et al., 1981). 
     224      !  and the correction factor for taking into account  the effect of clouds  
     225      !------------------------------------------------------ 
     226      IF( lbulk_init ) THEN 
     227         DO jj = 1, jpj   
     228            DO ji = 1 , jpi 
     229               zalat          = ( 90.e0 - ABS( gphit(ji,jj) ) ) /  5.e0 
     230               zclat          = ( 95.e0 -      gphit(ji,jj)   ) / 10.e0 
     231               indxb          = 1 + INT( zalat )  
     232               !  correction factor to account for the effect of clouds  
     233               sbudyko(ji,jj) = budyko(indxb)   
     234               indxc          = 1 + INT( zclat )   
     235               zdl            = zclat - INT( zclat )  
     236               zdr            = 1.0 - zdl 
     237               stauc(ji,jj)   = zdr * tauco( indxc ) + zdl * tauco( indxc + 1 )  
     238            END DO 
     239         END DO 
     240         IF( nleapy == 1 ) THEN 
     241            yearday = 366.e0 
     242         ELSE IF( nleapy == 0 ) THEN 
     243            yearday = 365.e0 
     244         ELSEIF( nleapy == 30) THEN 
     245            yearday = 360.e0 
     246         ENDIF 
     247         lbulk_init = .FALSE. 
     248      ENDIF 
     249 
     250      zqlw_oce(:,:) = 0.e0 
     251      zqla_oce(:,:) = 0.e0 
     252      zqsb_oce(:,:) = 0.e0 
     253      zqlw_ice(:,:,:) = 0.e0 
     254      zqla_ice(:,:,:) = 0.e0 
     255      zqsb_ice(:,:,:) = 0.e0 
     256 
     257      zpis2       = rpi / 2. 
     258      z2pi        = 2. * rpi 
     259 
     260 !CDIR NOVERRCHK 
     261      DO jj = 1, jpj 
     262 !CDIR NOVERRCHK 
     263         DO ji = 1, jpi 
     264 
     265            ztatm (ji,jj) = 273.15 + tatm  (ji,jj)  !  air temperature in Kelvins  
     266            zcatm1(ji,jj) = 1.0    - catm  (ji,jj)  !  fractional cloud cover 
     267            zfrld (ji,jj) = 1.0    - freeze(ji,jj)  !  fractional sea ice cover 
     268            zpatm(ji,jj)  = 101000.               !  pressure  
     269       
     270            !  Computation of air density, obtained from the equation of state for dry air.  
     271            zrhoa(ji,jj) = zpatm(ji,jj) / ( 287.04 * ztatm(ji,jj) ) 
     272       
     273            !  zes : Saturation water vapour 
     274            ztamr = ztatm(ji,jj) - rtt 
     275            zmt1  = SIGN( 17.269, ztamr ) 
     276            zmt2  = SIGN( 21.875, ztamr ) 
     277            zmt3  = SIGN( 28.200, -ztamr ) 
     278            zes(ji,jj) = 611.0 * EXP (  ABS( ztamr ) * MIN ( zmt1, zmt2 )   & 
     279               &                      / ( ztatm(ji,jj) - 35.86  + MAX( zzero, zmt3 ) ) ) 
     280 
     281            !  zev : vapour pressure  (hatm is relative humidity)   
     282            zev(ji,jj)   = hatm(ji,jj) * zes(ji,jj)  
     283            !  square-root of vapour pressure 
     284!CDIR NOVERRCHK 
     285            zevsqr(ji,jj) = SQRT( zev(ji,jj) * 0.01 ) 
     286            !  zqapb  : specific humidity  
     287            zqatm(ji,jj) = 0.622 * zev(ji,jj) / ( zpatm(ji,jj) - 0.378 * zev(ji,jj) ) 
     288 
     289 
     290            !---------------------------------------------------- 
     291            !   Computation of snow precipitation (Ledley, 1985) | 
     292            !---------------------------------------------------- 
     293 
     294            zmt1  =   253.0 - ztatm(ji,jj) 
     295            zmt2  = ( 272.0 - ztatm(ji,jj) ) / 38.0  
     296            zmt3  = ( 281.0 - ztatm(ji,jj) ) / 18.0 
     297            zind1 = MAX( zzero, SIGN( zone, zmt1 ) ) 
     298            zind2 = MAX( zzero, SIGN( zone, zmt2 ) ) 
     299            zind3 = MAX( zzero, SIGN( zone, zmt3 ) ) 
     300            ! total precipitation 
     301            tprecip(ji,jj) = watm(ji,jj) 
     302            ! solid  (snow) precipitation 
     303            sprecip(ji,jj) = tprecip(ji,jj) *       & 
     304               &             (           zind1      & 
     305               &               + ( 1.0 - zind1 ) * ( zind2 * ( 0.5 + zmt2 ) + ( 1.0 - zind2 ) *  zind3 * zmt3 ) )  
     306         END DO 
     307      END DO 
     308 
     309      !---------------------------------------------------------- 
     310      !   Computation of albedo (need to calculates heat fluxes)| 
     311      !----------------------------------------------------------- 
     312       
     313      CALL flx_blk_albedo( zalbios, zalboos, zalbics, zalbomu ) 
     314 
     315      !------------------------------------- 
     316      !   Computation of solar irradiance. | 
     317      !---------------------------------------- 
     318      indaet   = 1   
     319      !  compution of the day of the year at which the fluxes have to be calculate  
     320      !--The date corresponds to the middle of the time step. 
     321      zxday=nday_year + rdtbs2/rday 
     322 
     323      iday   = INT( zxday ) 
     324 
     325      IF(ln_ctl) CALL prt_ctl_info('declin : iday ', ivar1=iday, clinfo2=' nfbulk= ', ivar2=nfbulk) 
     326 
     327      !   computation of the solar declination, his sine and his cosine 
     328      CALL flx_blk_declin( indaet, iday, zdecl ) 
     329       
     330      zdecl    = zdecl * rad 
     331      zsdecl   = SIN( zdecl ) 
     332      zcdecl   = COS( zdecl ) 
     333       
     334      !  correction factor added for computation of shortwave flux to take into account the variation of 
     335      !  the distance between the sun and the earth during the year (Oberhuber 1988) 
     336      zdist    = zxday * z2pi / yearday 
     337      zdaycor  = 1.0 + 0.0013 * SIN( zdist ) + 0.0342 * COS( zdist ) 
     338 
     339!CDIR NOVERRCHK 
     340      DO jj = 1, jpj 
     341!CDIR NOVERRCHK 
     342         DO ji = 1, jpi 
     343            !  product of sine of latitude and sine of solar declination 
     344            zps     (ji,jj) = SIN( gphit(ji,jj) * rad ) * zsdecl 
     345            !  product of cosine of latitude and cosine of solar declination 
     346            zpc     (ji,jj) = COS( gphit(ji,jj) * rad ) * zcdecl 
     347            !  computation of the both local time of sunrise and sunset 
     348            zlsrise (ji,jj) = ACOS( - SIGN( zone, zps(ji,jj) ) * MIN( zone, SIGN( zone, zps(ji,jj) )  & 
     349               &                     * ( zps(ji,jj) / zpc(ji,jj) ) ) )  
     350            zlsset  (ji,jj) = - zlsrise(ji,jj) 
     351            !  dividing the solar day into jpintsr segments of length zdlha 
     352            zdlha   (ji,jj) = ( zlsrise(ji,jj) - zlsset(ji,jj) ) / REAL( jpintsr ) 
     353            !  computation of the local noon solar altitude 
     354            zlmunoon(ji,jj) = ASIN ( ( zps(ji,jj) + zpc(ji,jj) ) ) / rad 
     355             
     356            !  cloud correction taken from Reed (1977) (imposed lower than 1) 
     357            zcldcor (ji,jj) = MIN( zone, ( 1.e0 - 0.62 * catm(ji,jj) + 0.0019 * zlmunoon(ji,jj) ) ) 
     358         END DO 
     359      END DO 
     360 
     361         !  Computation of solar heat flux at each time of the day between sunrise and sunset.  
     362         !  We do this to a better optimisation of the code  
     363         !------------------------------------------------------        
     364      DO jl = 1, jpl 
     365 
     366!CDIR NOVERRCHK    
     367      DO jt = 1, jpintsr    
     368         zcoef = FLOAT( jt ) - 0.5 
     369!CDIR NOVERRCHK      
     370         DO jj = 1, jpj 
     371!CDIR NOVERRCHK 
     372            DO ji = 1, jpi 
     373               !  local hour angle 
     374               zlha (ji,jj,jt) = COS ( zlsrise(ji,jj) - zcoef * zdlha(ji,jj) ) 
     375 
     376               ! cosine of local solar altitude 
     377               zcmue              = MAX ( zzero ,   zps(ji,jj) + zpc(ji,jj) * zlha (ji,jj,jt)  ) 
     378               zcmue2             = 1368.0 * zcmue * zcmue 
     379               zscmue             = SQRT ( zcmue ) 
     380               zpcmue             = zcmue**1.4 
     381               ! computation of sea-water albedo (Payne, 1972) 
     382               zalbocs(ji,jj,jt)  = 0.05 / ( 1.1 * zpcmue + 0.15 ) 
     383               zalbo              = zcatm1(ji,jj) * zalbocs(ji,jj,jt) + catm(ji,jj) * zalboos(ji,jj) 
     384               ! solar heat flux absorbed at ocean surfaces (Zillman, 1972) 
     385               zevo               = zev(ji,jj) * 1.0e-05 
     386               zsqsro(ji,jj,jt)   =  ( 1.0 - zalbo ) * zdlha(ji,jj) * zcmue2                & 
     387                                   / ( ( zcmue + 2.7 ) * zevo + 1.085 * zcmue +  0.10 ) 
     388               !  solar heat flux absorbed at sea/ice surfaces  
     389               !  Formulation of Shine and Crane, 1984 adapted for high albedo surfaces  
     390 
     391               !  For clear sky         
     392               zevi               = zevo 
     393               zalbi              = zalbics(ji,jj,jl) 
     394               zsqsrics(ji,jj,jt) =  ( 1.0 - zalbi ) * zdlha(ji,jj) * zcmue2                & 
     395                  &                / ( ( 1.0 + zcmue ) * zevi + 1.2 * zcmue + 0.0455 ) 
     396 
     397               ! For overcast sky 
     398               zalbi              = zalbios(ji,jj,jl) 
     399               zsqsrios(ji,jj,jt) = zdlha(ji,jj) *                                                           & 
     400                  &                 ( ( 53.5 + 1274.5 * zcmue      ) *  zscmue * ( 1.0 - 0.996  * zalbi ) )  & 
     401                  &                 / (  1.0 + 0.139  * stauc(ji,jj) *           ( 1.0 - 0.9435 * zalbi ) ) 
     402            END DO 
     403         END DO 
     404      END DO 
     405 
     406 
     407      !  Computation of daily (between sunrise and sunset) solar heat flux absorbed  
     408      !  at the ocean and snow/ice surfaces. 
     409      !-------------------------------------------------------------------- 
     410 
     411      zalbocsd(:,:) = 0.e0 
     412      zqsro   (:,:) = 0.e0 
     413      zqsrics (:,:) = 0.e0 
     414      zqsrios (:,:) = 0.e0 
     415 
     416      DO jt = 1, jpintsr  
     417#   if defined key_vectopt_loop  
     418         DO ji = 1, jpij   
     419            zalbocsd(ji,1) = zalbocsd(ji,1) + zdlha   (ji,1) * zalbocs(ji,1,jt)   & 
     420               &                                             / MAX( 2.0 * zlsrise(ji,1) , zeps0 ) 
     421            zqsro   (ji,1) = zqsro   (ji,1) + zsqsro  (ji,1,jt) 
     422            zqsrics (ji,1) = zqsrics (ji,1) + zsqsrics(ji,1,jt) 
     423            zqsrios (ji,1) = zqsrios (ji,1) + zsqsrios(ji,1,jt) 
     424         END DO 
     425#  else 
     426         DO jj = 1, jpj 
     427            DO ji = 1, jpi   
     428               zalbocsd(ji,jj) = zalbocsd(ji,jj) + zdlha(ji,jj) * zalbocs(ji,jj,jt)   & 
     429                  &                                              / MAX( 2.0 * zlsrise(ji,jj) , zeps0 ) 
     430               zqsro  (ji,jj)  = zqsro   (ji,jj) + zsqsro  (ji,jj,jt) 
     431               zqsrics(ji,jj)  = zqsrics (ji,jj) + zsqsrics(ji,jj,jt) 
     432               zqsrios(ji,jj)  = zqsrios (ji,jj) + zsqsrios(ji,jj,jt) 
     433            END DO 
     434         END DO 
     435#  endif 
     436      END DO 
     437 
     438      DO jj = 1, jpj 
     439         DO ji = 1, jpi  
     440 
     441            !-------------------------------------------  
     442            !  Computation of shortwave radiation. 
     443            !------------------------------------------- 
     444 
     445            ! the solar heat flux absorbed at ocean and snow/ice surfaces 
     446            !------------------------------------------------------------ 
     447 
     448            ! For snow/ice  
     449            qsr_ice(ji,jj,jl) = ( zcatm1(ji,jj) * zqsrics(ji,jj) + catm(ji,jj) * zqsrios(ji,jj) ) / z2pi 
     450 
     451            ! Taking into account the ellipsity of the earth orbit 
     452            !----------------------------------------------------- 
     453 
     454            qsr_ice(ji,jj,jl) = qsr_ice(ji,jj,jl) * zdaycor 
     455            !--------------------------------------------------------------------------- 
     456            !   Computation of long-wave radiation  ( Berliand 1952 ; all latitudes ) 
     457            !--------------------------------------------------------------------------- 
     458 
     459            ! tempory variables 
     460            ztatm3         = ztatm(ji,jj) * ztatm(ji,jj) * ztatm(ji,jj) 
     461            ztatm4         = ztatm3 * ztatm(ji,jj) 
     462            z4tatm3        = 4. * ztatm3 
     463            zcldeff(ji,jj) = 1.0 - sbudyko(ji,jj) * catm(ji,jj) * catm(ji,jj)     
     464            ztaevbk        = ztatm4 * zcldeff(ji,jj) * ( 0.39 - 0.05 * zevsqr(ji,jj) )  
     465 
     466            !  Long-Wave for Ice 
     467            !---------------------- 
     468            zqlw_ice(ji,jj,jl) = - emic * stefan * ( ztaevbk + z4tatm3 * ( t_su(ji,jj,jl) - ztatm(ji,jj) ) )  
     469 
     470         END DO !ji 
     471      END DO !jj 
     472 
     473      END DO !jl 
     474 
     475      DO jj = 1, jpj 
     476         DO ji = 1, jpi  
     477 
     478            !  fraction of net shortwave radiation which is not absorbed in the  
     479            !  thin surface layer and penetrates inside the ice cover  
     480            !  ( Maykut and Untersteiner, 1971 ; Elbert anbd Curry, 1993 ) 
     481            !------------------------------------------------------------------ 
     482 
     483            fr1_i0(ji,jj) = 0.18  * zcatm1(ji,jj) + 0.35 * catm(ji,jj)  
     484            fr2_i0(ji,jj) = 0.82  * zcatm1(ji,jj) + 0.65 * catm(ji,jj) 
     485 
     486            ! the solar heat flux absorbed at ocean and snow/ice surfaces 
     487            !------------------------------------------------------------ 
     488            ! For ocean 
     489            qsr_oce(ji,jj) = srgamma * zcldcor(ji,jj) * zqsro(ji,jj) / z2pi 
     490            zinda          = SIGN( zone , -( -0.5 - zfrld(ji,jj) ) ) 
     491            zinda          = 1.0 - MAX( zzero , zinda ) 
     492            qsr_oce(ji,jj) = ( 1.- zinda ) * qsr_oce(ji,jj) 
     493 
     494            ! Taking into account the ellipsity of the earth orbit 
     495            !----------------------------------------------------- 
     496            qsr_oce(ji,jj) = qsr_oce(ji,jj) * zdaycor 
     497 
     498            !--------------------------------------------------------------------------- 
     499            !   Computation of long-wave radiation  ( Berliand 1952 ; all latitudes ) 
     500            !--------------------------------------------------------------------------- 
     501 
     502            ! tempory variables 
     503            ztatm3         = ztatm(ji,jj) * ztatm(ji,jj) * ztatm(ji,jj) 
     504            ztatm4         = ztatm3 * ztatm(ji,jj) 
     505            z4tatm3        = 4. * ztatm3 
     506            zcldeff(ji,jj) = 1.0 - sbudyko(ji,jj) * catm(ji,jj) * catm(ji,jj)     
     507            ztaevbk        = ztatm4 * zcldeff(ji,jj) * ( 0.39 - 0.05 * zevsqr(ji,jj) )  
     508 
     509            !  Long-Wave for Ocean 
     510            !----------------------- 
     511            zqlw_oce(ji,jj) = - emic * stefan * ( ztaevbk + z4tatm3 * ( psst  (ji,jj) - ztatm(ji,jj) ) )  
     512 
     513         END DO 
     514      END DO 
     515 
     516      !---------------------------------------- 
     517      !  Computation of turbulent heat fluxes  ( Latent and sensible )  
     518      !----------------------------------------         
     519      !CDIR NOVERRCHK 
     520      DO jj = 2 , jpjm1 
     521         !CDIR NOVERRCHK 
     522         DO  ji = 1, jpi 
     523 
     524            !  Turbulent heat fluxes over water 
     525            !---------------------------------- 
     526 
     527            ! zeso     : vapour pressure at saturation of ocean 
     528            ! zqsato   : humidity close to the ocean surface (at saturation) 
     529            zeso          =  611.0 * EXP ( 17.2693884 * ( psst(ji,jj) - rtt ) * tmask(ji,jj,1) / ( psst(ji,jj) - 35.86 ) ) 
     530            zqsato        = ( 0.622 * zeso ) / ( zpatm(ji,jj) - 0.378 * zeso ) 
     531 
     532            !  Drag coefficients from Large and Pond (1981,1982) 
     533            !--------------------------------------------------- 
     534     
     535            !  Stability parameters 
     536            zdteta         = psst(ji,jj) - ztatm(ji,jj) 
     537            zdeltaq        = zqatm(ji,jj) - zqsato 
     538            ztvmoy         = ztatm(ji,jj) * ( 1. + 2.2e-3 * ztatm(ji,jj) * zqatm(ji,jj) ) 
     539            zdenum         = MAX( vatm(ji,jj) * vatm(ji,jj) * ztvmoy, zeps ) 
     540            zdtetar        = zdteta / zdenum 
     541            ztvmoyr        = ztvmoy * ztvmoy * zdeltaq / zdenum 
     542             
     543            ! For stable atmospheric conditions 
     544            zobouks        = -70.0 * 10. * ( zdtetar + 3.2e-3 * ztvmoyr ) 
     545            zobouks        = MAX( zzero , zobouks ) 
     546            zpsims         = -7.0 * zobouks 
     547            zpsihs         =  zpsims 
     548            zpsils         =  zpsims 
     549 
     550            !  For unstable atmospheric conditions 
     551            zobouku        = -100.0 * 10.0 * ( zdtetar + 2.2e-3 * ztvmoyr ) 
     552            zobouku        = MIN( zzero , zobouku ) 
     553            zxins          = ( 1. - 16. * zobouku )**0.25 
     554            zlxins         = LOG( ( 1. + zxins * zxins ) / 2. ) 
     555            zpsimu         = 2. * LOG( ( 1 + zxins ) / 2. )  + zlxins - 2. * ATAN( zxins ) + zpis2 
     556            zpsihu         = 2. * zlxins 
     557            zpsilu         = zpsihu 
     558 
     559            ! computation of intermediate values 
     560            zstab          = MAX( zzero , SIGN( zone , zdteta ) ) 
     561            zpsim          = zstab * zpsimu + (1.0 - zstab ) * zpsims 
     562            zpsih          = zstab * zpsihu + (1.0 - zstab ) * zpsihs 
     563            zpsil          = zpsih 
     564             
     565            zvatmg         = MAX( 0.032 * 1.5e-3 * vatm(ji,jj) * vatm(ji,jj) / grav, zeps ) 
     566 
     567            zcmn           = vkarmn / LOG ( 10. / zvatmg ) 
     568            zcmn2          = zcmn * zcmn 
     569            zchn           = 0.0327 * zcmn 
     570            zcln           = 0.0346 * zcmn 
     571            zcmcmn         = 1 / ( 1 - zcmn * zpsim / vkarmn ) 
     572            zchcm          = zcmcmn / ( 1 - zchn * zpsih / ( vkarmn * zcmn ) ) 
     573            zclcm          = zchcm 
     574 
     575 
     576            !  Transfer cofficient zcsho and zcleo over ocean according to Large and Pond (1981,1982) 
     577            !--------------------------------------------------------------  
     578            zcsho          = zchn * zchcm 
     579            zcleo          = zcln * zclcm  
     580 
     581 
     582            !   Computation of sensible and latent fluxes over Ocean  
     583            !---------------------------------------------------------------- 
     584 
     585            !  computation of intermediate values 
     586            zrhova         = zrhoa(ji,jj) * vatm(ji,jj) 
     587            zrhovacsho     = zrhova * zcsho 
     588            zrhovacleo     = zrhova * zcleo 
     589 
     590            ! sensible heat flux 
     591            zqsb_oce(ji,jj) = zrhovacsho * 1004.0  * ( psst(ji,jj) - ztatm(ji,jj) )   
     592          
     593            !  latent heat flux  
     594            zqla_oce(ji,jj) = MAX(0.e0, zrhovacleo * 2.5e+06 * ( zqsato      - zqatm(ji,jj) ) ) 
     595                
     596            !  Calculate evaporation over water. (kg/m2/s) 
     597            !------------------------------------------------- 
     598            evap(ji,jj)    = zqla_oce(ji,jj) / cevap 
     599                
     600         END DO !ji 
     601      END DO !jj 
     602 
     603      DO jl = 1, jpl 
     604      !CDIR NOVERRCHK 
     605      DO jj = 2 , jpjm1 
     606         !CDIR NOVERRCHK 
     607         DO ji = 1, jpi 
     608                
     609            !  Turbulent heat fluxes over snow/ice. 
     610            !-------------------------------------------------- 
     611             
     612            !  zesi     : vapour pressure at saturation of ice 
     613            !  zqsati   : humidity close to the ice surface (at saturation) 
     614            zesi           =  611.0 * EXP ( 21.8745587 * tmask(ji,jj,1)   &   ! tmask needed to avoid overflow in the exponential 
     615               &                                       * ( t_su(ji,jj,jl) - rtt )/ ( t_su(ji,jj,jl)- 7.66 ) ) 
     616            zqsati         = ( 0.622 * zesi ) / ( zpatm(ji,jj) - 0.378 * zesi ) 
     617                
     618            !  computation of intermediate values 
     619            zticemb        = t_su(ji,jj,jl) - 7.66 
     620            zticemb2       = zticemb * zticemb   
     621            ztice3         = t_su(ji,jj,jl) * t_su(ji,jj,jl) * t_su(ji,jj,jl) 
     622            zqsati2        = zqsati * zqsati 
     623            zesi2          = zesi * zesi 
     624            zdesidt        = zesi * ( 9.5 * LOG( 10.0 ) * ( rtt - 7.66 )  / zticemb2 ) 
     625                
     626            !  Transfer cofficient zcshi and zclei over ice. Assumed to be constant Parkinson 1979 ; Maykut 1982 
     627            !-------------------------------------------------------------------- 
     628            zcshi          = 1.75e-03 
     629            zclei          = zcshi 
     630                
     631            !  Computation of sensible and latent fluxes over ice 
     632            !---------------------------------------------------------------- 
     633                
     634            !  computation of intermediate values 
     635            zrhova          = zrhoa(ji,jj) * vatm(ji,jj) 
     636            zrhovaclei      = zrhova * zcshi * 2.834e+06 
     637            zrhovacshi      = zrhova * zclei * 1004.0 
     638             
     639            !  sensible heat flux 
     640            zqsb_ice(ji,jj,jl) = zrhovacshi * ( t_su(ji,jj,jl) - ztatm(ji,jj) ) 
     641             
     642            !  latent heat flux  
     643            zqla_ice(ji,jj,jl) = zrhovaclei * ( zqsati        - zqatm(ji,jj) ) 
     644            qla_ice (ji,jj,jl) = MAX(0.e0, zqla_ice(ji,jj,jl) ) 
     645               
     646            !  Computation of sensitivity of non solar fluxes (dQ/dT) 
     647            !--------------------------------------------------------------- 
     648                
     649            !  computation of long-wave, sensible and latent flux sensitivity 
     650            zdqlw_ice       = 4.0 * emic * stefan * ztice3 
     651            zdqsb_ice       = zrhovacshi 
     652            zdqla_ice       = zrhovaclei * ( zdesidt * ( zqsati2 / zesi2 ) * ( zpatm(ji,jj) / 0.622 ) )    
     653             
     654            !  total non solar sensitivity 
     655            dqns_ice(ji,jj,jl) = -( zdqlw_ice + zdqsb_ice + zdqla_ice )  
     656             
     657            ! latent flux sensitivity 
     658            dqla_ice(ji,jj,jl) = zdqla_ice 
     659             
     660         END DO 
     661      END DO 
     662      END DO !jl 
     663 
     664      ! total non solar heat flux over ice 
     665      qnsr_ice(:,:,:) = zqlw_ice(:,:,:) - zqsb_ice(:,:,:) - zqla_ice(:,:,:) 
     666      ! total non solar heat flux over water  
     667      qnsr_oce(:,:) = zqlw_oce(:,:) - zqsb_oce(:,:) - zqla_oce(:,:) 
     668 
     669      ! solid precipitations ( kg/m2/day -> kg/m2/s) 
     670      tprecip(:,:) = tprecip  (:,:) / rday  
     671      ! snow  precipitations ( kg/m2/day -> kg/m2/s) 
     672      sprecip(:,:) = sprecip  (:,:) / rday   
     673 
     674      CALL lbc_lnk( qsr_oce (:,:) , 'T', 1. ) 
     675      CALL lbc_lnk( qnsr_oce(:,:) , 'T', 1. ) 
     676      CALL lbc_lnk( fr1_i0  (:,:) , 'T', 1. ) 
     677      CALL lbc_lnk( fr2_i0  (:,:) , 'T', 1. ) 
     678      CALL lbc_lnk( tprecip (:,:) , 'T', 1. ) 
     679      CALL lbc_lnk( sprecip (:,:) , 'T', 1. ) 
     680      CALL lbc_lnk( evap    (:,:) , 'T', 1. ) 
     681      DO jl = 1, jpl 
     682         CALL lbc_lnk( qsr_ice (:,:,jl) , 'T', 1. ) 
     683         CALL lbc_lnk( qnsr_ice(:,:,jl) , 'T', 1. ) 
     684         CALL lbc_lnk( dqns_ice(:,:,jl) , 'T', 1. ) 
     685         CALL lbc_lnk( qla_ice (:,:,jl) , 'T', 1. ) 
     686         CALL lbc_lnk( dqla_ice(:,:,jl) , 'T', 1. ) 
     687      END DO 
     688 
     689      qsr_oce (:,:) = qsr_oce (:,:)*tmask(:,:,1) 
     690      qnsr_oce(:,:) = qnsr_oce(:,:)*tmask(:,:,1) 
     691      DO jl = 1, jpl 
     692         qsr_ice (:,:,jl) = qsr_ice (:,:,jl)*tmask(:,:,1) 
     693         qnsr_ice(:,:,jl) = qnsr_ice(:,:,jl)*tmask(:,:,1) 
     694         qla_ice (:,:,jl) = qla_ice (:,:,jl)*tmask(:,:,1) 
     695         dqns_ice(:,:,jl) = dqns_ice(:,:,jl)*tmask(:,:,1) 
     696         dqla_ice(:,:,jl) = dqla_ice(:,:,jl)*tmask(:,:,1) 
     697      END DO 
     698      fr1_i0  (:,:) = fr1_i0  (:,:)*tmask(:,:,1) 
     699      fr2_i0  (:,:) = fr2_i0  (:,:)*tmask(:,:,1) 
     700      tprecip (:,:) = tprecip (:,:)*tmask(:,:,1) 
     701      sprecip (:,:) = sprecip (:,:)*tmask(:,:,1) 
     702      evap    (:,:) = evap    (:,:)*tmask(:,:,1) 
     703 
     704 
     705   END SUBROUTINE flx_blk 
     706 
     707 
     708#else 
    81709 
    82710   SUBROUTINE flx_blk( psst ) 
     
    215843      !   Initilization    ! 
    216844      !--------------------- 
    217 #if ! defined key_ice_lim 
     845#if ! defined key_lim2 
    218846      tn_ice(:,:) = psst(:,:) 
    219847#endif 
     
    6801308 
    6811309   END SUBROUTINE flx_blk 
     1310#endif 
    6821311 
    6831312 
  • trunk/NEMO/OPA_SRC/SBC/flxmod.F90

    r719 r833  
    108108   !!---------------------------------------------------------------------- 
    109109   !!   'key_oasis3'  or 'key_oasis4' and           Coupled Ocan/Atmosphere 
    110    !!   'key_ice_lim'                               with  LIM sea-ice model 
     110   !!   'key_lim3'                               with  LIM sea-ice model 
    111111   !!---------------------------------------------------------------------- 
    112112#  include "flx_oasis_ice.h90" 
  • trunk/NEMO/OPA_SRC/SBC/ocesbc.F90

    r719 r833  
    6464CONTAINS 
    6565 
    66 #if defined key_ice_lim 
    67    !!---------------------------------------------------------------------- 
    68    !!   'key_ice_lim' :                                   LIM sea-ice model 
     66#if defined key_lim3 || defined key_lim2 
     67   !!---------------------------------------------------------------------- 
     68   !!   'key_lim3'     :                                 LIM2 sea-ice model 
     69   !!   'key_lim2'     :                                 LIM3 sea-ice model 
    6970   !!---------------------------------------------------------------------- 
    7071# if defined key_coupled 
     
    154155            DO ji = 1, fs_jpim1   ! vertor opt. 
    155156               ztx   = 0.5 * ( freeze(ji+1,jj) + freeze(ji+1,jj+1) ) 
     157               zty   = 0.5 * ( freeze(ji,jj+1) + freeze(ji+1,jj+1) ) 
     158#if defined key_lim3 
     159               ztaux = ftaux(ji,jj) 
     160               ztauy = ftauy(ji,jj) 
     161#elif defined key_lim2 
    156162               ztaux = 0.5 * ( ftaux (ji+1,jj) + ftaux (ji+1,jj+1) ) 
     163               ztauy = 0.5 * ( ftauy (ji,jj+1) + ftauy (ji+1,jj+1) ) 
     164#endif 
    157165               taux(ji,jj) = (1.0-ztx) * taux(ji,jj) + ztx * ztaux 
    158  
    159                zty   = 0.5 * ( freeze(ji,jj+1) + freeze(ji+1,jj+1) ) 
    160                ztauy = 0.5 * ( ftauy (ji,jj+1) + ftauy (ji+1,jj+1) ) 
    161166               tauy(ji,jj) = (1.0-zty) * tauy(ji,jj) + zty * ztauy 
    162167            END DO 
     
    179184# elif defined key_flx_bulk_monthly || defined key_flx_bulk_daily || defined key_flx_core 
    180185      !!---------------------------------------------------------------------- 
    181       !!   'key_ice_lim'                              with  LIM sea-ice model 
     186      !!   'key_lim3'                              with  LIM sea-ice model 
    182187      !!---------------------------------------------------------------------- 
    183188 
     
    259264               ztx         = MAX( freezn(ji,jj), freezn(ji,jj+1) )   ! ice/ocean indicator at U- and V-points 
    260265               zty         = MAX( freezn(ji,jj), freezn(ji+1,jj) ) 
    261                ztaux       = 0.5 *( ftaux(ji+1,jj) + ftaux(ji+1,jj+1) ) ! ice-ocean stress at U- and V-points 
    262                ztauy       = 0.5 *( ftauy(ji,jj+1) + ftauy(ji+1,jj+1) ) 
     266#if defined key_lim3 
     267               ztaux = ftaux(ji,jj) 
     268               ztauy = ftauy(ji,jj) 
     269#elif defined key_lim2 
     270               ztaux = 0.5 * ( ftaux (ji+1,jj) + ftaux (ji+1,jj+1) ) 
     271               ztauy = 0.5 * ( ftauy (ji,jj+1) + ftauy (ji+1,jj+1) ) 
     272#endif 
    263273               taux(ji,jj) = (1.-ztx) * taux(ji,jj) + ztx * ztaux    ! stress at the ocean surface 
    264274               tauy(ji,jj) = (1.-zty) * tauy(ji,jj) + zty * ztauy 
     
    816826      !!---------------------------------------------------------------------- 
    817827 
    818 #if defined key_ice_lim 
     828#if defined key_lim3 || defined key_lim2 
    819829      ! sea ice indicator (1 or 0) 
    820830      DO jj = 1, jpj 
  • trunk/NEMO/OPA_SRC/SBC/taumod.F90

    r719 r833  
    5959   !!---------------------------------------------------------------------- 
    6060   !!   'key_oasis3' or 'key_oasis4' and           Coupled Ocean/Atmosphere 
    61    !!   'key_ice_lim'                                   LIM sea-ice 
     61   !!   'key_lim3'or 'key_lim2'                              LIM sea-ice 
    6262   !!---------------------------------------------------------------------- 
    6363   ! New way: 3D referential link to the earth (avoid north pole pb) 
  • trunk/NEMO/OPA_SRC/TRA/traadv_cen2.F90

    r789 r833  
    147147               zind(ji,jj,jk) =  MAX ( upsrnfh(ji,jj) * upsrnfz(jk),     &  ! changing advection scheme near runoff 
    148148                  &                    upsadv(ji,jj)                     &  ! in the vicinity of some straits 
    149 #if defined key_ice_lim 
     149#if defined key_lim3 || defined key_lim2 
    150150                  &                  , tmask(ji,jj,jk)                   &  ! half upstream tracer fluxes 
    151151                  &                  * MAX( 0., SIGN( 1., fzptn(ji,jj)   &  ! if tn < ("freezing"+0.1 ) 
  • trunk/NEMO/OPA_SRC/cpl.F90

    r719 r833  
    569569      sieoc(:,:) = sieoc(:,:) + freeze(:,:) 
    570570 
    571 #if defined key_ice_lim 
     571#if defined key_lim3 || defined key_lim2 
    572572      alboc(:,:) = alboc(:,:) + freeze(:,:) * alb_ice(:,:) 
    573573      ticoc(:,:) = ticoc(:,:) + freeze(:,:) * tn_ice(:,:)  
  • trunk/NEMO/OPA_SRC/cpl_oce.F90

    r719 r833  
    218218      qsrc           !: solar radiation (w m-2) 
    219219 
    220 #  if defined key_ice_lim 
     220#  if defined key_lim3 || defined key_lim3 
    221221   REAL(wp), DIMENSION(jpi,jpj) ::   &  !: 
    222222      watm        ,    &  !: 
  • trunk/NEMO/OPA_SRC/ice_oce.F90

    r719 r833  
    1111   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
    1212   !!---------------------------------------------------------------------- 
    13 #if defined key_ice_lim 
     13#if defined key_lim2 || defined key_lim3 
    1414   !!---------------------------------------------------------------------- 
    15    !!   'key_ice_lim'   :                                     LIM ice model 
     15   !!   'key_lim2 or key_lim3 '   :             LIM 2.0 or 3.0 ice model 
    1616   !!---------------------------------------------------------------------- 
    1717   !! * Modules used 
     
    2323  
    2424   !! Shared module variables 
    25    LOGICAL, PUBLIC, PARAMETER ::   lk_ice_lim = .TRUE.    !: LIM ice model 
     25# if defined  key_lim2 
     26   LOGICAL, PUBLIC, PARAMETER ::   lk_lim2        = .TRUE.    !: LIM2 ice model 
     27   LOGICAL, PUBLIC, PARAMETER ::   lk_lim3        = .FALSE.   !: LIM3 ice model 
     28# else 
     29   LOGICAL, PUBLIC, PARAMETER ::   lk_lim2        = .FALSE.   !: LIM2 ice model 
     30   LOGICAL, PUBLIC, PARAMETER ::   lk_lim3        = .TRUE.    !: LIM3 ice model 
     31# endif 
    2632 
    2733   !!---------------------------------------------------------------------- 
     
    3137   REAL(wp), PUBLIC, DIMENSION(jpiglo,jpjglo) ::   &  !: cumulated fields 
    3238      fqsr_oce ,      &   !: Net short wave heat flux on free ocean  
    33       fqsr_ice ,      &   !: Net short wave het flux on sea ice  
     39      fqsr_ice ,      &   !: Net short wave heat flux on sea ice  
    3440      fqnsr_oce,      &   !: Net longwave heat flux on free ocean 
    3541      fqnsr_ice,      &   !: Net longwave heat flux on sea ice 
     
    4854      ftaux , ftauy  , &  !: wind stresses 
    4955      gtaux , gtauy       !: wind stresses 
     56 
     57# if defined key_lim3 
     58   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &  !: field exchanges with ice model to ocean 
     59      catm_ice       , &  !: cloud cover 
     60      tatm_ice       , &  !: air temperature 
     61      icethi              !: icethickness 
     62# endif 
    5063    
    5164   REAL(wp), PUBLIC ::   &  !: 
     
    5770   !!   Default option                                 NO LIM sea-ice model 
    5871   !!---------------------------------------------------------------------- 
    59    LOGICAL, PUBLIC, PARAMETER ::   lk_ice_lim = .FALSE.  !: No LIM ice model 
     72   LOGICAL, PUBLIC, PARAMETER ::   lk_lim2        = .FALSE.  !: No LIM 2.0 ice model 
     73   LOGICAL, PUBLIC, PARAMETER ::   lk_lim3        = .FALSE.  !: No LIM 3.0 ice model 
    6074#endif 
    6175 
  • trunk/NEMO/OPA_SRC/opa.F90

    r719 r833  
    5959 
    6060   USE phycst          ! physical constant                  (par_cst routine) 
     61#if defined key_lim3 
    6162   USE iceini          ! initialization of sea-ice         (ice_init routine) 
     63#endif 
     64#if defined key_lim2 
     65   USE iceini_2        ! initialization of sea-ice         (ice_init_2 routine) 
     66#endif 
    6267   USE cpl             ! coupled ocean/atmos.              (cpl_init routine) 
    6368   USE ocfzpt          ! ocean freezing point              (oc_fz_pt routine) 
     
    282287      CALL oc_fz_pt                         ! Surface freezing point 
    283288 
    284 #if defined key_ice_lim 
    285       CALL ice_init                         ! Sea ice model 
     289#if defined key_lim3 
     290      CALL ice_init                         ! Sea ice model LIM3 
     291#endif 
     292 
     293#if defined key_lim2 
     294      CALL ice_init_2                       ! Sea ice model LIM2 
    286295#endif 
    287296 
  • trunk/NEMO/OPA_SRC/phycst.F90

    r719 r833  
    4646      rtt      = 273.16_wp  ,  &  !: triple point of temperature (Kelvin) 
    4747      rt0      = 273.15_wp  ,  &  !: freezing point of water (Kelvin) 
     48#if defined key_lim3 
     49      rt0_snow = 273.16_wp  ,  &  !: melting point of snow  (Kelvin) 
     50      rt0_ice  = 273.16_wp  ,  &  !: melting point of ice   (Kelvin) 
     51#else 
    4852      rt0_snow = 273.15_wp  ,  &  !: melting point of snow  (Kelvin) 
    4953      rt0_ice  = 273.05_wp  ,  &  !: melting point of ice   (Kelvin) 
     54#endif 
    5055      rau0     = 1020._wp   ,  &  !: volumic mass of reference (kg/m3) 
    5156      rauw     = 1000._wp   ,  &  !: density of pure water (kg/m3) 
     
    5459 
    5560   REAL(wp), PUBLIC ::            &  !: 
     61#if defined key_lim3 
     62      rcdsn   =   0.31_wp     ,   &  !: thermal conductivity of snow 
     63      rcdic   =   2.034396_wp ,   &  !: thermal conductivity of fresh ice 
     64      cpic    = 2067.0        ,   & 
     65      ! add the following lines 
     66      lsub    = 2.834e+6      ,   &  !: pure ice latent heat of sublimation (J.kg-1) 
     67      lfus    = 0.334e+6      ,   &  !: latent heat of fusion of fresh ice   (J.kg-1) 
     68      rhoic   = 917._wp       ,   &  !: density of sea ice (kg/m3) 
     69      tmut    =   0.054       ,   &  !: decrease of seawater meltpoint with salinity 
     70#else 
    5671      rcdsn   =   0.22_wp     ,   &  !: conductivity of the snow 
    5772      rcdic   =   2.034396_wp ,   &  !: conductivity of the ice 
     
    6277      xsn     =   2.8e+6      ,   &  !: latent heat of sublimation of snow 
    6378      rhoic   = 900._wp       ,   &  !: density of sea ice (kg/m3) 
     79#endif 
    6480      rhosn   = 330._wp       ,   &  !: density of snow (kg/m3) 
    6581      emic    =   0.97_wp     ,   &  !: emissivity of snow or ice 
     
    169185         WRITE(numout,*) '          thermal conductivity of the snow          = ', rcdsn   , ' J/s/m/K' 
    170186         WRITE(numout,*) '          thermal conductivity of the ice           = ', rcdic   , ' J/s/m/K' 
     187#if defined key_lim3 
     188         WRITE(numout,*) '          fresh ice specific heat                   = ', cpic    , ' J/kg/K' 
     189         WRITE(numout,*) '          latent heat of fusion of fresh ice / snow = ', lfus    , ' J/kg' 
     190         WRITE(numout,*) '          latent heat of subl.  of fresh ice / snow = ', lsub    , ' J/kg' 
     191#else 
    171192         WRITE(numout,*) '          density times specific heat for snow      = ', rcpsn   , ' J/m^3/K'  
    172193         WRITE(numout,*) '          density times specific heat for ice       = ', rcpic   , ' J/m^3/K' 
     
    174195         WRITE(numout,*) '          volumetric latent heat fusion of snow     = ', xlsn    , ' J/m'  
    175196         WRITE(numout,*) '          latent heat of sublimation of snow        = ', xsn     , ' J/kg'  
     197#endif 
    176198         WRITE(numout,*) '          density of sea ice                        = ', rhoic   , ' kg/m^3' 
    177199         WRITE(numout,*) '          density of snow                           = ', rhosn   , ' kg/m^3' 
  • trunk/NEMO/OPA_SRC/restart.F90

    r783 r833  
    144144      CALL iom_rstput( kt, nitrst, numrow, 'hdivn'  , hdivn   ) 
    145145 
    146 #if defined key_ice_lim         
     146#if defined key_lim3 || defined key_lim2 
    147147      CALL iom_rstput( kt, nitrst, numrow, 'nfice'  , REAL( nfice, wp) )   !  ice computation frequency 
    148148      CALL iom_rstput( kt, nitrst, numrow, 'sst_io' , sst_io  ) 
     
    210210      !!---------------------------------------------------------------------- 
    211211      REAL(wp) ::   zcoef, zkt, zrdt, zrdttra1, zndastp, znfice, znfbulk 
    212 #if defined key_ice_lim 
     212#if defined key_lim3 || defined key_lim2 
    213213      INTEGER  ::   ji, jj 
    214214#endif 
     
    306306      !!sm: TO BE MOVED IN NEW SURFACE MODULE... 
    307307 
    308 #if defined key_ice_lim 
     308#if defined key_lim3 || defined key_lim2 
    309309      ! Louvain La Neuve Sea Ice Model 
    310310      IF( iom_varid( numror, 'nfice', ldstop = .FALSE. ) > 0 ) then  
  • trunk/NEMO/OPA_SRC/step.F90

    r789 r833  
    9696   USE zpshde          ! partial step: hor. derivative     (zps_hde routine) 
    9797   USE ice_oce         ! sea-ice variable 
     98#if defined key_lim3 
    9899   USE icestp          ! sea-ice time-stepping             (ice_stp routine) 
    99  
     100#endif 
     101#if defined key_lim2 
     102   USE icestp_2        ! sea-ice time-stepping             (ice_stp_2 routine) 
     103#endif 
    100104   USE diawri          ! Standard run outputs             (dia_wri routine) 
    101105   USE trdicp          ! Ocean momentum/tracers trends    (trd_wri routine) 
     
    206210                         CALL flx( kstp )             ! heat and freshwater fluxes 
    207211 
    208       IF( lk_ice_lim )   CALL ice_stp( kstp )         ! sea-ice model (Update stress & fluxes) 
     212#if defined key_lim3 
     213      CALL ice_stp( kstp )           ! sea-ice model (Update stress & fluxes) 
     214#endif 
     215#if defined key_lim2 
     216      CALL ice_stp_2( kstp )         ! sea-ice model (Update stress & fluxes) 
     217#endif 
    209218 
    210219                         CALL oce_sbc( kstp )         ! ocean surface boudaries 
  • trunk/NEMO/TOP_SRC/TRP/trcadv_cen2.F90

    r719 r833  
    164164               zind(ji,jj,jk) =  MAX ( upsrnfh(ji,jj) * upsrnfz(jk),     &  ! changing advection scheme near runoff 
    165165                  &                    upsadv(ji,jj)                     &  ! in the vicinity of some straits 
    166 #if defined key_ice_lim 
     166#if defined key_lim3 
    167167                  &                  , tmask(ji,jj,jk)                   &  ! half upstream tracer fluxes 
    168168                  &                  * MAX( 0., SIGN( 1., fzptn(ji,jj)   &  ! if tn < ("freezing"+0.1 ) 
  • trunk/UTIL/fait_AA_make

    r687 r833  
    339339do 
    340340  bn=`basename $i .f` 
    341   if [ "${bn}" != "${MAIN}" ]  
    342   then  
    343   if [ "${bn}" != "agrif2model" ]  
    344   then  
    345341    echo "\\" 
    346342    echo "     \$(MODEL_LIB)($bn.o)\c" 
    347   fi 
    348   fi 
    349343done 
    350344 
     
    390384do 
    391385  bn=`basename $i .F` 
    392   if [ "${bn}" != "${MAIN}" ]  
    393   then  
    394   if [ "${bn}" != "agrif2model" ]  
    395   then  
    396386    echo "\\" 
    397387    echo "     \$(MODEL_LIB)($bn.o)\c" 
    398   fi 
    399   fi 
    400388 done 
    401389 
     
    457445      for fuse0 in `sed -n 's/^[    ]*[uU][sS][eE] [  ]*\([^!,;]*\).*/\1/p' $inc | sort -u` 
    458446      do 
    459            if [ $fuse0 != "ioipsl" ]  
    460                 then 
    461                 if [ $fuse0 != "Agrif_Util" ]  
    462                 then 
    463                 if [ $fuse0 != "Agrif_Types" ]  
    464                 then 
    465                 if [ $fuse0 != "netcdf" ]  
    466                 then 
     447                    [ -f $fuse0.[hfF]90 ] || continue 
    467448          lfuse0=$fuse0.f90 
    468449          [ -f $fuse0.F90 ] && lfuse0=$fuse0.F90 
    469450          luse0="$luse0\n$lfuse0\n\$(MODEL_LIB)($fuse0.o)" 
    470                 fi 
    471                 fi 
    472                 fi 
    473                 fi 
    474451      done 
    475452 
     
    480457          for fuse0 in `sed -n 's/^[   ]*[uU][sS][eE] [  ]*\([^!,;]*\).*/\1/p' $inc2 | sort -u` 
    481458          do 
    482                if [ $fuse0 != "ioipsl" ]  
    483                     then 
    484                     if [ $fuse0 != "Agrif_Util" ]  
    485                     then 
    486                     if [ $fuse0 != "Agrif_Types" ]  
    487                     then 
    488                     if [ $fuse0 != "netcdf" ]  
    489                     then 
     459                        [ -f $fuse0.[hfF]90 ] || continue 
    490460              lfuse0=$fuse0.f90 
    491461              [ -f $fuse0.F90 ] && lfuse0=$fuse0.F90 
    492462              luse0="$luse0\n$lfuse0\n\$(MODEL_LIB)($fuse0.o)" 
    493                     fi 
    494                     fi 
    495                     fi 
    496                     fi 
    497463          done 
    498464           done 
     
    502468   for fuse1 in `sed -n 's/^[    ]*[uU][sS][eE] [  ]*\([^!,;]*\).*/\1/p' $fic | sort -u` 
    503469   do 
    504    if [ $fuse1 != "ioipsl" ]  
    505         then 
    506         if [ $fuse1 != "Agrif_Util" ]  
    507         then 
    508         if [ $fuse1 != "Agrif_Types" ]  
    509         then 
    510         if [ $fuse1 != "netcdf" ]  
    511         then 
     470            [ -f $fuse1.[hfF]90 ] || continue 
    512471       lfuse1=$fuse1.f90 
    513472       [ -f $fuse1.F90 ] && lfuse1=$fuse1.F90 
     
    515474      for fuse2 in `sed -n 's/^[    ]*[uU][sS][eE] [  ]*\([^!,;]*\).*/\1/p' $lfuse1 | sort -u` 
    516475      do 
    517            if [ $fuse2 != "ioipsl" ]  
    518                 then 
    519                 if [ $fuse2 != "Agrif_Util" ]  
    520                 then 
    521                 if [ $fuse2 != "Agrif_Types" ]  
    522                 then 
    523                 if [ $fuse2 != "netcdf" ]  
    524                 then 
     476                    [ -f $fuse2.[hfF]90 ] || continue 
    525477          lfuse2=$fuse2.f90 
    526478          [ -f $fuse2.F90 ] && lfuse2=$fuse2.F90 
     
    529481          for fuse3 in `sed -n 's/^#[     ]*[uU][sS][eE] [  ]*\([^!,;]*\).*/\1/p' $lfuse2 | sort -u` 
    530482          do 
    531           if [ $fuse3 != "ioipsl" ]  
    532                     then 
    533                     if [ $fuse3 != "Agrif_Util" ]  
    534                     then 
    535                     if [ $fuse3 != "Agrif_Types" ]  
    536                     then 
    537                     if [ $fuse3 != "netcdf" ]  
    538                     then 
     483                        [ -f $fuse3.[hfF]90 ] || continue 
    539484         luse3="$luse3\n$lfuse3\n\$(MODEL_LIB)($fuse3.o)" 
    540                     fi          
    541                     fi          
    542                     fi          
    543                     fi          
    544485                    done 
    545                 fi 
    546                 fi 
    547                 fi 
    548                 fi 
    549486      done 
    550         fi 
    551         fi 
    552         fi 
    553         fi 
    554487   done 
    555488#- 
     
    652585echo '       ln -sf ../OPA_SRC/IOM/*.[Ffh]90      . ; \' 
    653586echo '  fi ' 
    654 echo '   @check=`grep LIM_SRC .config`              ; \' 
     587echo '   @check=`grep LIM_SRC_3 .config`              ; \' 
    655588echo '   if [ -n "$$check" ] ; then                   \' 
    656 echo '   echo "   use LIM_SRC files"                ; \' 
    657 echo '      ln -sf ../LIM_SRC/*.[Ffh]90          . ; \' 
     589echo '   echo "   use LIM_SRC_3 files"                ; \' 
     590echo '      ln -sf ../LIM_SRC_3/*.[Ffh]90          . ; \' 
     591echo '  fi ' 
     592echo '   @check=`grep LIM_SRC_2 .config`              ; \' 
     593echo '   if [ -n "$$check" ] ; then                   \' 
     594echo '   echo "   use LIM_SRC_2 files"                ; \' 
     595echo '      ln -sf ../LIM_SRC_2/*.[Ffh]90          . ; \' 
    658596echo '  fi ' 
    659597echo '   @check=`grep C1D_SRC .config`              ; \' 
  • trunk/UTIL/fait_config

    r798 r833  
    2626# Example 1 : in order to create a GYRE_TRC configuration : 
    2727# 1. In this script, change LIST to LIST="ORCA2_LIM \nGYRE \nGYRE_TRC" 
    28 # 2. In this script, add set -A DIR_GYRE_TRC OPA_SRC LIM_SRC TOP_SRC C1D_SRC, take care of the syntax 
     28# 2. In this script, add set -A DIR_GYRE_TRC OPA_SRC LIM_SRC_3 TOP_SRC C1D_SRC, take care of the syntax 
    2929# 3. Run fait_config GYRE_TRC 
    3030# Example 2 : in order to create an OFFLINE_TRC configuration : 
     
    3333# 3. Run fait_config OFFLINE_TRC 
    3434 
    35 LIST="ORCA2_LIM \nGYRE" 
    36 set -A DIR_ORCA2_LIM OPA_SRC LIM_SRC C1D_SRC NST_SRC 
    37 set -A DIR_GYRE OPA_SRC LIM_SRC C1D_SRC  
    38 set -A DIR_GYRE_LOBSTER OPA_SRC LIM_SRC C1D_SRC TOP_SRC 
     35LIST="ORCA2_LIM \nGYRE \nGYRE_LOBSTER" 
     36set -A DIR_ORCA2_LIM OPA_SRC LIM_SRC_3 C1D_SRC NST_SRC 
     37set -A DIR_GYRE OPA_SRC LIM_SRC_3 C1D_SRC  
     38set -A DIR_GYRE_LOBSTER OPA_SRC LIM_SRC_3 C1D_SRC TOP_SRC 
    3939 
    4040################################### 
     
    9696    while [ i -lt $NDIR ] 
    9797    do 
    98       if [ "${TAB[i]}" = "LIM_SRC" ]; then 
    99      ln -sf ../LIM_SRC/*.[Ffh]90 .   
     98      if [ "${TAB[i]}" = "LIM_SRC_3" ]; then 
     99     ln -sf ../LIM_SRC_3/*.[Ffh]90 .   
     100       
     101      elif [ "${TAB[i]}" = "LIM_SRC_2" ]; then 
     102     ln -sf ../LIM_SRC_2/*.[Ffh]90 .   
    100103       
    101104      elif [ "${TAB[i]}" = "C1D_SRC" ]; then 
Note: See TracChangeset for help on using the changeset viewer.