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 1037 for trunk/NEMO – NEMO

Changeset 1037 for trunk/NEMO


Ignore:
Timestamp:
2008-05-30T18:21:28+02:00 (16 years ago)
Author:
ctlod
Message:

trunk: replace freeze(:,:) variable with fr_i(:,:), use the tfreez function defined in eosbn2.F90 and remove the useless ocfzpt.F90 module, see ticket: #177

Location:
trunk/NEMO
Files:
22 edited

Legend:

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

    r900 r1037  
    2525   USE ice_oce         ! ice variables 
    2626   USE phycst          ! physical constants 
    27    USE ocfzpt          ! ??? 
    2827   USE zdfmxl          ! mixed layer 
    2928   USE daymod          ! calendar 
     
    185184         CALL histdef( nid_T, "somixhgt", "Turbocline Depth"                   , "m"      ,   &  ! hmld 
    186185            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    187          CALL histdef( nid_T, "soicecov", "Ice Cover"                          , "[0,1]"  ,   &  ! freeze 
     186         CALL histdef( nid_T, "soicecov", "Ice Fraction"                          , "[0,1]"  ,   &  ! fr_i 
    188187            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    189188         IF( ln_ssr ) THEN 
     
    304303      CALL histwrite( nid_T, "somxlavt", it, zw2d          , ndim_hT, ndex_hT )   ! Kz at bottom of mixed layer  
    305304      CALL histwrite( nid_T, "somixhgt", it, hmld          , ndim_hT, ndex_hT )   ! turbocline depth 
    306       CALL histwrite( nid_T, "soicecov", it, freeze        , ndim_hT, ndex_hT )   ! ice cover  
     305      CALL histwrite( nid_T, "soicecov", it, fr_i          , ndim_hT, ndex_hT )   ! ice fraction  
    307306      IF( ln_ssr ) THEN 
    308307         CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
  • trunk/NEMO/C1D_SRC/step_c1d.F90

    r922 r1037  
    2626   USE sbcmod          ! surface boundary condition       (sbc     routine) 
    2727   USE sbcrnf          ! surface boundary condition: runoff variables 
    28    USE ocfzpt          ! surface ocean freezing point    (oc_fz_pt routine) 
    2928 
    3029   USE trcstp          ! passive tracer time-stepping      (trc_stp routine) 
     
    185184 
    186185      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    187       ! Computation of diagnostic variables 
    188       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    189       ! N.B. ua, va, ta, sa arrays are used as workspace in this section 
    190       !----------------------------------------------------------------------- 
    191                        CALL oc_fz_pt                        ! ocean surface freezing temperature 
    192  
    193       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    194186      ! Control and restarts 
    195187      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
  • trunk/NEMO/LIM_SRC_2/iceini_2.F90

    r900 r1037  
    2121   USE sbc_ice         ! surface boundary condition: ice 
    2222   USE phycst          ! Define parameters for the routines 
    23    USE ocfzpt 
    2423   USE ice_2 
    2524   USE limmsh_2 
     
    7574       
    7675      tn_ice(:,:) = sist(:,:)         ! initialisation of ice temperature    
    77       freeze(:,:) = 1.0 - frld(:,:)   ! initialisation of sea/ice cover     
     76      fr_i  (:,:) = 1.0 - frld(:,:)   ! initialisation of sea-ice fraction     
    7877# if defined key_coupled 
    7978      alb_ice(:,:) = albege(:,:)      ! sea-ice albedo 
  • trunk/NEMO/LIM_SRC_2/limistate_2.F90

    r888 r1037  
    1919   !!---------------------------------------------------------------------- 
    2020   USE phycst 
    21    USE ocfzpt 
    2221   USE par_ice_2       ! ice parameters 
    2322   USE ice_oce         ! ice variables 
    2423   USE dom_ice_2 
     24   USE eosbn2          ! equation of state 
    2525   USE lbclnk 
    2626   USE oce 
     
    7272      IF( .NOT. ln_limini ) THEN   
    7373          
    74          ! Initialisation at tn or -2 if ice 
     74         tfu(:,:) = tfreez( sn(:,:,1) ) * tmask(:,:,1)       ! freezing/melting point of sea water [Celcius] 
     75 
    7576         DO jj = 1, jpj 
    7677            DO ji = 1, jpi 
    77                zbin = MAX( 0., SIGN( 1., fzptn(ji,jj) - tn(ji,jj,1) ) ) 
    78                ztn(ji,jj) = ( (1.-zbin) * tn(ji,jj,1) - 2. * zbin + rt0 ) * tmask(ji,jj,1) 
    79             END DO 
    80          END DO 
    81                    
    82          !  tfu: Melting point of sea water [Kelvin] 
    83          zs0 = 34.e0 
    84          ztf = rt0 + ( - 0.0575 + 1.710523e-3 * SQRT( zs0 ) - 2.154996e-4 * zs0 ) * zs0 
    85          tfu(:,:) = ztf 
    86           
    87          DO jj = 1, jpj 
    88             DO ji = 1, jpi 
    89                !--- Criterion for presence (zidto=1) or absence (zidto=0) of ice 
    90                zidto  = tms(ji,jj) * ( 1.0 - MAX(zzero, SIGN( zone, ztn(ji,jj) - tfu(ji,jj) - ttest) ) ) 
    91                 
     78               !                     ! ice if sst <= t-freez + ttest 
     79               IF( tn(ji,jj,1)  - tfu(ji,jj) >= ttest ) THEN   ;   zidto = 0.e0      ! no ice 
     80               ELSE                                            ;   zidto = 1.e0      !    ice 
     81               ENDIF 
     82               ! 
    9283               IF( fcor(ji,jj) >= 0.e0 ) THEN     !--  Northern hemisphere. 
    9384                  hicif(ji,jj)   = zidto * hginn 
     
    10192            END DO 
    10293         END DO 
     94 
     95         tfu(:,:) = tfu(:,:) + rt0       ! ftu converted from Celsius to Kelvin (rt0 over land) 
    10396          
    10497         sist  (:,:)   = tfu(:,:) 
  • trunk/NEMO/LIM_SRC_2/limsbc_2.F90

    r888 r1037  
    2020   USE sbc_oce          ! surface boundary condition 
    2121   USE phycst           ! physical constants 
    22    USE ocfzpt           ! surface ocean freezing point 
    2322   USE ice_oce          ! sea-ice variable 
    2423   USE ice_2            ! LIM sea-ice variables 
     
    6160      !!              - Update  
    6261      !!      
    63       !! ** Outputs : - qsr    : sea heat flux:     solar  
    64       !!              - qns    : sea heat flux: non solar 
    65       !!              - emp    : freshwater budget: volume flux  
    66       !!              - emps   : freshwater budget: concentration/dillution  
    67       !!              - utau   : sea surface i-stress (ocean referential) 
    68       !!              - vtau   : sea surface j-stress (ocean referential) 
     62      !! ** Outputs : - qsr     : sea heat flux:     solar  
     63      !!              - qns     : sea heat flux: non solar 
     64      !!              - emp     : freshwater budget: volume flux  
     65      !!              - emps    : freshwater budget: concentration/dillution  
     66      !!              - utau    : sea surface i-stress (ocean referential) 
     67      !!              - vtau    : sea surface j-stress (ocean referential) 
     68      !!              - fr_i    : ice fraction 
     69      !!              - tn_ice  : sea-ice surface temperature 
     70      !!              - alb_ice : sea-ice alberdo (lk_cpl=T) 
    6971      !! 
    7072      !! References : Goosse, H. et al. 1996, Bul. Soc. Roy. Sc. Liege, 65, 87-90. 
     
    214216      !-----------------------------------------------! 
    215217 
    216       freeze(:,:) = 1.0 - frld(:,:)       ! Sea ice cover             
    217       tn_ice(:,:) = sist(:,:)             ! Ice surface temperature                       
     218      fr_i  (:,:) = 1.0 - frld(:,:)       ! sea-ice fraction 
     219      tn_ice(:,:) = sist(:,:)             ! sea-ice surface temperature                       
    218220 
    219221#if defined key_coupled             
     
    234236         CALL prt_ctl(tab2d_1=utau  , clinfo1=' lim_sbc: utau   : ', mask1=umask,   & 
    235237            &         tab2d_2=vtau  , clinfo2=' vtau    : '        , mask2=vmask ) 
    236          CALL prt_ctl(tab2d_1=freeze, clinfo1=' lim_sbc: freeze : ', tab2d_2=tn_ice, clinfo2=' tn_ice  : ') 
     238         CALL prt_ctl(tab2d_1=fr_i  , clinfo1=' lim_sbc: fr_i  : ', tab2d_2=tn_ice, clinfo2=' tn_ice  : ') 
    237239      ENDIF  
    238240    
  • trunk/NEMO/LIM_SRC_3/iceini.F90

    r921 r1037  
    1616   USE sbc_ice         ! Surface boundary condition: ice fields 
    1717   USE phycst          ! Define parameters for the routines 
    18    USE ocfzpt 
    1918   USE ice 
    2019   USE limmsh 
     
    9392      ENDIF 
    9493 
    95       freeze(:,:) = at_i(:,:)   ! initialisation of sea/ice cover     
     94      fr_i(:,:) = at_i(:,:)           ! initialisation of sea-ice fraction 
    9695# if defined key_coupled 
    9796      Must be adpated to LIM3  
  • trunk/NEMO/LIM_SRC_3/limistate.F90

    r921 r1037  
    1313   !! * Modules used 
    1414   USE phycst 
    15    USE ocfzpt 
    1615   USE oce             ! dynamics and tracers variables 
    1716   USE dom_oce 
     
    1918   USE par_ice         ! ice parameters 
    2019   USE ice_oce         ! ice variables 
     20   USE eosbn2          ! equation of state 
    2121   USE in_out_manager 
    2222   USE dom_ice 
     
    7474      INTEGER  ::   ji, jj, jk, jl             ! dummy loop indices 
    7575 
    76       REAL(wp) ::   zidto,    &  ! temporary scalar 
    77          zs0, ztf, zbin, & 
     76      REAL(wp) ::       &  ! temporary scalar 
     77         zs0, ztf, & 
    7878         zeps6, zeps, ztmelts, & 
    7979         epsi06 
     
    8181         zgfactorn, zhin, & 
    8282         zgfactors, zhis 
    83       REAL(wp), DIMENSION(jpi,jpj) ::   & 
    84          ztn   
    8583      REAL(wp) ::  & 
    8684         zvol, zare, zh, zh1, zh2, zh3, zan, zbn, zas, zbs  
     85      REAL(wp), DIMENSION(jpi,jpj) ::   zidto    ! ice indicator 
    8786      !-------------------------------------------------------------------- 
    8887 
     
    9493      CALL lim_istate_init     !  reading the initials parameters of the ice 
    9594 
    96       ! Initialisation at tn or -2 if ice 
    97       DO jj = 1, jpj 
     95!!gm  in lim2  the initialisation if only done if required in the namelist : 
     96!!gm      IF( .NOT. ln_limini ) THEN 
     97!!gm  this should be added in lim3 namelist... 
     98 
     99      !-------------------------------------------------------------------- 
     100      ! 2) Ice initialization (hi,hs,frld,t_su,sm_i,t_i,t_s)              |  
     101      !-------------------------------------------------------------------- 
     102 
     103      IF(lwp) WRITE(numout,*) 
     104      IF(lwp) WRITE(numout,*) 'lim_istate : Ice initialization ' 
     105      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' 
     106 
     107      t_bo(:,:) = tfreez( sn(:,:,1) ) * tmask(:,:,1)       ! freezing/melting point of sea water [Celcius] 
     108 
     109      DO jj = 1, jpj                                       ! ice if sst <= t-freez + ttest 
    98110         DO ji = 1, jpi 
    99             zbin = MAX( 0., SIGN( 1., fzptn(ji,jj) - tn(ji,jj,1) ) ) 
    100             ztn(ji,jj) = ( (1.-zbin) * tn(ji,jj,1) - 2. * zbin + rt0 ) * tmask(ji,jj,1) 
     111            IF( tn(ji,jj,1)  - t_bo(ji,jj) >= ttest ) THEN   ;   zidto(ji,jj) = 0.e0      ! no ice 
     112            ELSE                                             ;   zidto(ji,jj) = 1.e0      !    ice 
     113            ENDIF 
    101114         END DO 
    102115      END DO 
    103116 
    104       !-------------------------------------------------------------------- 
    105       ! 2) Ice initialization (hi,hs,frld,t_su,sm_i,t_i,t_s)              |  
    106       !-------------------------------------------------------------------- 
    107  
    108       WRITE(numout,*) 
    109       WRITE(numout,*) 'lim_istate : Ice initialization ' 
    110       WRITE(numout,*) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' 
    111  
    112       ! reference salinity 34psu 
    113       zs0 = 34.e0 
    114       ztf = ABS ( rt0 - 0.0575       * zs0                               & 
    115          &                    + 1.710523e-03 * zs0 * SQRT( zs0 )   & 
    116          &                    - 2.154996e-04 * zs0 *zs0          ) 
     117      t_bo(:,:) = t_bo(:,:) + rt0                          ! t_bo converted from Celsius to Kelvin (rt0 over land) 
    117118 
    118119      ! constants for heat contents 
    119120      zeps   = 1.0d-20 
    120121      zeps6  = 1.0d-06 
    121  
    122       !  t_bo: Seawater freezing point 
    123       t_bo(:,:)  = ztf    
    124122 
    125123      ! zgfactor for initial ice distribution 
     
    148146         zh3 = zh3 + zh*zh*zh 
    149147      END DO 
    150       WRITE(numout,*) ' zh1 : ', zh1 
    151       WRITE(numout,*) ' zh2 : ', zh2 
    152       WRITE(numout,*) ' zh3 : ', zh3 
     148      IF(lwp) WRITE(numout,*) ' zh1 : ', zh1 
     149      IF(lwp) WRITE(numout,*) ' zh2 : ', zh2 
     150      IF(lwp) WRITE(numout,*) ' zh3 : ', zh3 
    153151 
    154152      zvol = aginn_u*hginn_u 
     
    159157      ENDIF 
    160158 
    161       WRITE(numout,*) ' zvol: ', zvol 
    162       WRITE(numout,*) ' zare: ', zare 
    163       WRITE(numout,*) ' zbn : ', zbn  
    164       WRITE(numout,*) ' zan : ', zan  
     159      IF(lwp) WRITE(numout,*) ' zvol: ', zvol 
     160      IF(lwp) WRITE(numout,*) ' zare: ', zare 
     161      IF(lwp) WRITE(numout,*) ' zbn : ', zbn  
     162      IF(lwp) WRITE(numout,*) ' zan : ', zan  
    165163 
    166164      zvol = agins_u*hgins_u 
     
    171169      ENDIF 
    172170 
    173       WRITE(numout,*) ' zvol: ', zvol 
    174       WRITE(numout,*) ' zare: ', zare 
    175       WRITE(numout,*) ' zbn : ', zbn  
    176       WRITE(numout,*) ' zan : ', zan  
     171      IF(lwp) WRITE(numout,*) ' zvol: ', zvol 
     172      IF(lwp) WRITE(numout,*) ' zare: ', zare 
     173      IF(lwp) WRITE(numout,*) ' zbn : ', zbn  
     174      IF(lwp) WRITE(numout,*) ' zan : ', zan  
    177175 
    178176      !end of new lines 
     
    201199      ! END retour a LIMA_MEC 
    202200!!! 
     201 
     202!!gm  optimisation :  loop over the ice categories inside the ji, jj loop !!! 
     203 
    203204      DO jj = 1, jpj 
    204205         DO ji = 1, jpi 
    205  
    206             !--- Criterion for presence (zidto=1) or absence (zidto=0) of ice 
    207             zidto  = tms(ji,jj) * ( 1.0 - MAX(zzero, SIGN( zone, ztn(ji,jj) - t_bo(ji,jj) - ttest) ) ) 
    208206 
    209207            !--- Northern hemisphere 
     
    218216 
    219217                  DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2) ! loop over ice thickness categories 
    220                      a_i(ji,jj,jl)    = zidto * aginn_u 
    221                      ht_i(ji,jj,jl)   = zidto * hginn_u 
     218                     a_i(ji,jj,jl)    = zidto(ji,jj) * aginn_u 
     219                     ht_i(ji,jj,jl)   = zidto(ji,jj) * hginn_u 
    222220                     v_i(ji,jj,jl)    = ht_i(ji,jj,jl)*a_i(ji,jj,jl) 
    223221                  END DO 
     
    227225                  DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2) ! loop over ice thickness categories 
    228226                     zhin(1)          = ( hi_max(jl-1) + hi_max(jl) ) / 2.0 
    229                      a_i(ji,jj,jl)    = zidto * MAX( zgfactorn(1) * exp(-(zhin(1)-hginn_u)* &  
     227                     a_i(ji,jj,jl)    = zidto(ji,jj) * MAX( zgfactorn(1) * exp(-(zhin(1)-hginn_u)* &  
    230228                        (zhin(1)-hginn_u)/2.0) , epsi06) 
    231229                     ! new line 
    232                      a_i(ji,jj,jl)    = zidto * ( zan * zhin(1) * zhin(1) + zbn * zhin(1) ) 
    233                      ht_i(ji,jj,jl)   = zidto * zhin(1)  
     230                     a_i(ji,jj,jl)    = zidto(ji,jj) * ( zan * zhin(1) * zhin(1) + zbn * zhin(1) ) 
     231                     ht_i(ji,jj,jl)   = zidto(ji,jj) * zhin(1)  
    234232                     v_i(ji,jj,jl)    = ht_i(ji,jj,jl)*a_i(ji,jj,jl) 
    235233                  END DO 
     
    245243               !              DO jl = ice_cat_bounds(2,1), ice_cat_bounds(2,2) ! loop over ice thickness categories 
    246244               !                 zhin(2)          = ( hi_max(jl-1) + hi_max(jl) ) / 2.0 
    247                !                 a_i(ji,jj,jl)    = zidto * MAX( zgfactorn(2) * exp(-(zhin(2)-hginn_d)* & 
     245               !                 a_i(ji,jj,jl)    = zidto(ji,jj) * MAX( zgfactorn(2) * exp(-(zhin(2)-hginn_d)* & 
    248246               !                                    (zhin(2)-hginn_d)/2.0) , epsi06) 
    249                !                 ht_i(ji,jj,jl)   = zidto * zhin(2)  
     247               !                 ht_i(ji,jj,jl)   = zidto(ji,jj) * zhin(2)  
    250248               !                 v_i(ji,jj,jl)    = ht_i(ji,jj,jl)*a_i(ji,jj,jl) 
    251249               !              END DO 
     
    265263                  ! Snow depth 
    266264                  !------------- 
    267                   ht_s(ji,jj,jl)   = zidto * hninn 
     265                  ht_s(ji,jj,jl)   = zidto(ji,jj) * hninn 
    268266                  v_s(ji,jj,jl)    = ht_s(ji,jj,jl)*a_i(ji,jj,jl) 
    269267 
     
    271269                  ! Ice salinity 
    272270                  !--------------- 
    273                   sm_i(ji,jj,jl)   = zidto * sinn  + ( 1.0 - zidto ) * 0.1 
     271                  sm_i(ji,jj,jl)   = zidto(ji,jj) * sinn  + ( 1.0 - zidto(ji,jj) ) * 0.1 
    274272                  smv_i(ji,jj,jl)  = MIN( sm_i(ji,jj,jl) , sss_m(ji,jj) ) * v_i(ji,jj,jl) 
    275273 
     
    277275                  ! Ice age 
    278276                  !---------- 
    279                   o_i(ji,jj,jl)    = zidto * 1.0   + ( 1.0 - zidto ) 
     277                  o_i(ji,jj,jl)    = zidto(ji,jj) * 1.0   + ( 1.0 - zidto(ji,jj) ) 
    280278                  oa_i(ji,jj,jl)   = o_i(ji,jj,jl) * a_i(ji,jj,jl) 
    281279 
     
    284282                  !------------------------------ 
    285283 
    286                   t_su(ji,jj,jl)   = zidto * 270.0 + ( 1.0 - zidto ) * t_bo(ji,jj) 
     284                  t_su(ji,jj,jl)   = zidto(ji,jj) * 270.0 + ( 1.0 - zidto(ji,jj) ) * t_bo(ji,jj) 
    287285 
    288286                  !------------------------------------ 
     
    291289 
    292290                  DO jk = 1, nlay_s 
    293                      t_s(ji,jj,jk,jl) = zidto * 270.00 + ( 1.0 - zidto ) * rtt 
     291                     t_s(ji,jj,jk,jl) = zidto(ji,jj) * 270.00 + ( 1.0 - zidto(ji,jj) ) * rtt 
    294292                     ! Snow energy of melting 
    295                      e_s(ji,jk,jk,jl) = zidto * rhosn * ( cpic * ( rtt - t_s(ji,jj,jk,jl) ) + lfus ) 
     293                     e_s(ji,jk,jk,jl) = zidto(ji,jj) * rhosn * ( cpic * ( rtt - t_s(ji,jj,jk,jl) ) + lfus ) 
    296294                     ! Change dimensions 
    297295                     e_s(ji,jj,jk,jl) = e_s(ji,jj,jk,jl) / unit_fac 
     
    306304 
    307305                  DO jk = 1, nlay_i 
    308                      t_i(ji,jj,jk,jl) = zidto*270.00 + ( 1.0 - zidto ) * rtt  
    309                      s_i(ji,jj,jk,jl) = zidto * sinn + ( 1.0 - zidto ) * 0.1 
     306                     t_i(ji,jj,jk,jl) = zidto(ji,jj)*270.00 + ( 1.0 - zidto(ji,jj) ) * rtt  
     307                     s_i(ji,jj,jk,jl) = zidto(ji,jj) * sinn + ( 1.0 - zidto(ji,jj) ) * 0.1 
    310308                     ztmelts          = - tmut * s_i(ji,jj,jk,jl) + rtt !Melting temperature in K 
    311309 
    312310                     ! heat content per unit volume 
    313                      e_i(ji,jj,jk,jl) = zidto * rhoic * & 
     311                     e_i(ji,jj,jk,jl) = zidto(ji,jj) * rhoic * & 
    314312                        (   cpic    * ( ztmelts - t_i(ji,jj,jk,jl) ) & 
    315313                        +   lfus    * ( 1.0 - (ztmelts-rtt) / MIN((t_i(ji,jj,jk,jl)-rtt),-zeps) ) & 
     
    340338 
    341339                  DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2) ! loop over ice thickness categories 
    342                      a_i(ji,jj,jl)    = zidto * agins_u 
    343                      ht_i(ji,jj,jl)   = zidto * hgins_u 
     340                     a_i(ji,jj,jl)    = zidto(ji,jj) * agins_u 
     341                     ht_i(ji,jj,jl)   = zidto(ji,jj) * hgins_u 
    344342                     v_i(ji,jj,jl)    = ht_i(ji,jj,jl)*a_i(ji,jj,jl) 
    345343                  END DO 
     
    351349 
    352350                     zhis(1)       = ( hi_max(jl-1) + hi_max(jl) ) / 2.0 
    353                      a_i(ji,jj,jl) = zidto * MAX( zgfactors(1) * exp(-(zhis(1)-hgins_u) * &  
     351                     a_i(ji,jj,jl) = zidto(ji,jj) * MAX( zgfactors(1) * exp(-(zhis(1)-hgins_u) * &  
    354352                        (zhis(1)-hgins_u)/2.0) , epsi06 ) 
    355353                     ! new line square distribution volume conserving 
    356                      a_i(ji,jj,jl)    = zidto * ( zas * zhis(1) * zhis(1) + zbs * zhis(1) ) 
    357                      ht_i(ji,jj,jl)   = zidto * zhis(1)  
     354                     a_i(ji,jj,jl)    = zidto(ji,jj) * ( zas * zhis(1) * zhis(1) + zbs * zhis(1) ) 
     355                     ht_i(ji,jj,jl)   = zidto(ji,jj) * zhis(1)  
    358356                     v_i(ji,jj,jl)    = ht_i(ji,jj,jl)*a_i(ji,jj,jl) 
    359357 
     
    369367               !              DO jl = ice_cat_bounds(2,1), ice_cat_bounds(2,2) !over thickness categories 
    370368               !                 zhis(2)       = ( hi_max(jl-1) + hi_max(jl) ) / 2.0 
    371                !                 a_i(ji,jj,jl) = zidto*MAX( zgfactors(2) * exp(-(zhis(2)-hgins_d)*(zhis(2)-hgins_d)/2.0), epsi06 ) 
    372                !                 ht_i(ji,jj,jl)   = zidto * zhis(2)  
     369               !                 a_i(ji,jj,jl) = zidto(ji,jj)*MAX( zgfactors(2)   & 
     370               !                    &          * exp(-(zhis(2)-hgins_d)*(zhis(2)-hgins_d)/2.0), epsi06 ) 
     371               !                 ht_i(ji,jj,jl)   = zidto(ji,jj) * zhis(2)  
    373372               !                 v_i(ji,jj,jl)    = ht_i(ji,jj,jl)*a_i(ji,jj,jl) 
    374373               !              END DO 
     
    389388                  !--------------- 
    390389 
    391                   ht_s(ji,jj,jl)   = zidto * hnins 
     390                  ht_s(ji,jj,jl)   = zidto(ji,jj) * hnins 
    392391                  v_s(ji,jj,jl)    = ht_s(ji,jj,jl)*a_i(ji,jj,jl) 
    393392 
     
    396395                  !--------------- 
    397396 
    398                   sm_i(ji,jj,jl)   = zidto * sins  + ( 1.0 - zidto ) * 0.1 
     397                  sm_i(ji,jj,jl)   = zidto(ji,jj) * sins  + ( 1.0 - zidto(ji,jj) ) * 0.1 
    399398                  smv_i(ji,jj,jl)  = MIN( sm_i(ji,jj,jl) , sss_m(ji,jj) ) * v_i(ji,jj,jl) 
    400399 
     
    403402                  !---------- 
    404403 
    405                   o_i(ji,jj,jl)    = zidto * 1.0   + ( 1.0 - zidto ) 
     404                  o_i(ji,jj,jl)    = zidto(ji,jj) * 1.0   + ( 1.0 - zidto(ji,jj) ) 
    406405                  oa_i(ji,jj,jl)   = o_i(ji,jj,jl) * a_i(ji,jj,jl) 
    407406 
     
    410409                  !------------------------------ 
    411410 
    412                   t_su(ji,jj,jl)   = zidto * 270.0 + ( 1.0 - zidto ) * t_bo(ji,jj) 
     411                  t_su(ji,jj,jl)   = zidto(ji,jj) * 270.0 + ( 1.0 - zidto(ji,jj) ) * t_bo(ji,jj) 
    413412 
    414413                  !---------------------------------- 
     
    417416 
    418417                  DO jk = 1, nlay_s 
    419                      t_s(ji,jj,jk,jl) = zidto * 270.00 + ( 1.0 - zidto ) * rtt 
     418                     t_s(ji,jj,jk,jl) = zidto(ji,jj) * 270.00 + ( 1.0 - zidto(ji,jj) ) * rtt 
    420419                     ! Snow energy of melting 
    421                      e_s(ji,jj,jk,jl) = zidto * rhosn * ( cpic * ( rtt - t_s(ji,jj,jk,jl) ) + lfus ) 
     420                     e_s(ji,jj,jk,jl) = zidto(ji,jj) * rhosn * ( cpic * ( rtt - t_s(ji,jj,jk,jl) ) + lfus ) 
    422421                     ! Change dimensions 
    423422                     e_s(ji,jj,jk,jl) = e_s(ji,jj,jk,jl) / unit_fac 
     
    432431 
    433432                  DO jk = 1, nlay_i 
    434                      t_i(ji,jj,jk,jl) = zidto*270.00 + ( 1.0 - zidto ) * rtt  
    435                      s_i(ji,jj,jk,jl) = zidto * sins + ( 1.0 - zidto ) * 0.1 
     433                     t_i(ji,jj,jk,jl) = zidto(ji,jj)*270.00 + ( 1.0 - zidto(ji,jj) ) * rtt  
     434                     s_i(ji,jj,jk,jl) = zidto(ji,jj) * sins + ( 1.0 - zidto(ji,jj) ) * 0.1 
    436435                     ztmelts          = - tmut * s_i(ji,jj,jk,jl) + rtt !Melting temperature in K 
    437436 
    438437                     ! heat content per unit volume 
    439                      e_i(ji,jj,jk,jl) = zidto * rhoic * & 
     438                     e_i(ji,jj,jk,jl) = zidto(ji,jj) * rhoic * & 
    440439                        (   cpic    * ( ztmelts - t_i(ji,jj,jk,jl) ) & 
    441440                        +   lfus  * ( 1.0 - (ztmelts-rtt) / MIN((t_i(ji,jj,jk,jl)-rtt),-zeps) ) & 
  • trunk/NEMO/LIM_SRC_3/limsbc.F90

    r921 r1037  
    2121   USE sbc_oce          ! Surface boundary condition: ocean fields 
    2222   USE phycst           ! physical constants 
    23    USE ocfzpt           ! surface ocean freezing point 
    2423   USE ice_oce          ! sea-ice variable 
    2524   USE ice              ! LIM sea-ice variables 
     
    225224      !!              - Update the ocean sbc 
    226225      !!      
    227       !! ** Outputs : - qsr    : sea heat flux:     solar  
    228       !!              - qns    : sea heat flux: non solar 
    229       !!              - emp    : freshwater budget: volume flux  
    230       !!              - emps   : freshwater budget: concentration/dillution  
     226      !! ** Outputs : - qsr     : sea heat flux:     solar  
     227      !!              - qns     : sea heat flux: non solar 
     228      !!              - emp     : freshwater budget: volume flux  
     229      !!              - emps    : freshwater budget: concentration/dillution  
     230      !!              - fr_i    : ice fraction 
     231      !!              - tn_ice  : sea-ice surface temperature 
     232      !!              - alb_ice : sea-ice alberdo (lk_cpl=T) 
    231233      !! 
    232234      !! References : Goosse, H. et al. 1996, Bul. Soc. Roy. Sc. Liege, 65, 87-90. 
     
    422424      !-----------------------------------------------! 
    423425 
    424       freeze(:,:)   = at_i(:,:)             ! Sea ice cover             
     426      fr_i  (:,:)   = at_i(:,:)             ! Sea-ice fraction             
    425427      tn_ice(:,:,:) = t_su(:,:,:)           ! Ice surface temperature                       
    426428 
     
    440442         CALL prt_ctl( tab2d_1=qsr   , clinfo1=' lim_sbc: qsr    : ', tab2d_2=qns , clinfo2=' qns     : ' ) 
    441443         CALL prt_ctl( tab2d_1=emp   , clinfo1=' lim_sbc: emp    : ', tab2d_2=emps, clinfo2=' emps    : ' ) 
    442          CALL prt_ctl( tab2d_1=freeze, clinfo1=' lim_sbc: freeze : ' ) 
     444         CALL prt_ctl( tab2d_1=fr_i  , clinfo1=' lim_sbc: fr_i  : ' ) 
    443445         CALL prt_ctl( tab3d_1=tn_ice, clinfo1=' lim_sbc: tn_ice : ', kdim=jpl ) 
    444446      ENDIF 
  • trunk/NEMO/OPA_SRC/DIA/diawri.F90

    r895 r1037  
    1818   USE sbcssr          ! restoring term toward SST/SSS climatology 
    1919   USE phycst          ! physical constants 
    20    USE ocfzpt          ! ocean freezing point 
    2120   USE zdfmxl          ! mixed layer 
    2221   USE daymod          ! calendar 
     
    271270         CALL histdef( nid_T, "somixhgt", "Turbocline Depth"                   , "m"      ,   &  ! hmld 
    272271            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    273          CALL histdef( nid_T, "soicecov", "Ice Cover"                          , "[0,1]"  ,   &  ! freeze 
     272         CALL histdef( nid_T, "soicecov", "Ice fraction"                       , "[0,1]"  ,   &  ! fr_i 
    274273            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    275274#if ! defined key_coupled  
     
    433432      CALL histwrite( nid_T, "somxl010", it, hmlp          , ndim_hT, ndex_hT )   ! mixed layer depth 
    434433      CALL histwrite( nid_T, "somixhgt", it, hmld          , ndim_hT, ndex_hT )   ! turbocline depth 
    435       CALL histwrite( nid_T, "soicecov", it, freeze        , ndim_hT, ndex_hT )   ! ice cover  
     434      CALL histwrite( nid_T, "soicecov", it, fr_i          , ndim_hT, ndex_hT )   ! ice fraction   
    436435#if ! defined key_coupled 
    437436      CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
     
    622621      CALL histdef( id_i, "soshfldo", "Shortwave Radiation"   , "W/m2"   ,   &   ! solar flux 
    623622         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    624       CALL histdef( id_i, "soicecov", "Ice fraction"          , "[0,1]"  ,   &   ! freeze 
     623      CALL histdef( id_i, "soicecov", "Ice fraction"          , "[0,1]"  ,   &   ! fr_i 
    625624         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    626625      CALL histdef( id_i, "sozotaux", "Zonal Wind Stress"     , "N/m2"   ,   &   ! i-wind stress 
     
    652651      CALL histwrite( id_i, "sohefldo", 1, qsr + qns, jpi*jpj    , idex )    ! total heat flux 
    653652      CALL histwrite( id_i, "soshfldo", 1, qsr      , jpi*jpj    , idex )    ! solar heat flux 
    654       CALL histwrite( id_i, "soicecov", 1, freeze   , jpi*jpj    , idex )    ! ice cover 
     653      CALL histwrite( id_i, "soicecov", 1, fr_i     , jpi*jpj    , idex )    ! ice fraction 
    655654      CALL histwrite( id_i, "sozotaux", 1, utau     , jpi*jpj    , idex )    ! i-wind stress 
    656655      CALL histwrite( id_i, "sometauy", 1, vtau     , jpi*jpj    , idex )    ! j-wind stress 
  • trunk/NEMO/OPA_SRC/DIA/diawri_dimg.h90

    r888 r1037  
    5252    !!  level 10: hmld(:,:)                turbocline depth 
    5353    !!  level 11: hmlp(:,:)                mixed layer depth 
    54     !!  level 12: freeze (:,:)             Ice cover (1. or 0.) 
     54    !!  level 12: fr_i(:,:)                ice fraction (between 0 and 1) 
    5555    !!  level 13: sst(:,:)                 the observed SST we relax to. 
    5656    !!  level 14: qct(:,:)                 equivalent flux due to treshold SST 
     
    181181       fsel(:,:,10) = fsel(:,:,10) + hmld(:,:) 
    182182       fsel(:,:,11) = fsel(:,:,11) + hmlp(:,:) 
    183        fsel(:,:,12) = fsel(:,:,12) + freeze(:,:) 
     183       fsel(:,:,12) = fsel(:,:,12) + fr_i(:,:) 
    184184       fsel(:,:,13) = fsel(:,:,13) + sst(:,:) 
    185185       !        fsel(:,:,14) = fsel(:,:,14) + qct(:,:) 
     
    263263          fsel(:,:,10) = hmld(:,:) * tmask(:,:,1) 
    264264          fsel(:,:,11) = hmlp(:,:) * tmask(:,:,1) 
    265           fsel(:,:,12) = freeze(:,:) * tmask(:,:,1) 
     265          fsel(:,:,12) = fr_i(:,:) * tmask(:,:,1) 
    266266          fsel(:,:,13) =  sst(:,:)   
    267267          !         fsel(:,:,14) =  qct(:,:) 
  • trunk/NEMO/OPA_SRC/SBC/sbc_oce.F90

    r1033 r1037  
    1616   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   utau      !: sea surface i-stress (ocean referential)     [N/m2] 
    1717   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   vtau      !: sea surface j-stress (ocean referential)     [N/m2] 
    18    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   wndm      !: wind speed module at T-point (= |U10m -Uoce| [m/s] 
     18   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   wndm      !: wind speed module at T-point (=|U10m-Uoce|) [m/s] 
    1919   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qns       !: sea heat flux: non solar                     [W/m2] 
    2020   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qsr       !: sea heat flux:     solar                     [W/m2] 
    2121   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emp       !: freshwater budget: volume flux               [Kg/m2/s] 
    2222   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emps      !: freshwater budget: concentration/dillution   [Kg/m2/s] 
    23    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fr_i      !: ice fraction (between 0 to 1) 
     23   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fr_i      !: ice fraction  (between 0 to 1)               - 
    2424 
    2525   !!---------------------------------------------------------------------- 
  • trunk/NEMO/OPA_SRC/SBC/sbcana.F90

    r1028 r1037  
    1616   USE phycst          ! physical constants 
    1717   USE daymod          ! calendar 
    18    USE ocfzpt          ! ocean freezing point 
    1918   USE in_out_manager  ! I/O manager 
    2019   USE lib_mpp         ! distribued memory computing library 
     
    3635   REAL(wp) ::   rn_emp0   = 0.e0   ! net freshwater flux 
    3736  
    38    REAL(wp) ::   rhoa  = 1.22         ! Air density kg/m3 
    39    REAL(wp) ::   cdrag    = 1.5e-3      ! drag coefficient 
     37   REAL(wp) ::   rhoa      = 1.22   ! Air density kg/m3 
     38   REAL(wp) ::   cdrag     = 1.5e-3 ! drag coefficient 
    4039   
    4140   !! * Substitutions 
  • trunk/NEMO/OPA_SRC/SBC/sbcblk_clio.F90

    r1000 r1037  
    2020   USE phycst          ! physical constants 
    2121   USE daymod          ! calendar 
    22    USE ocfzpt          ! ocean freezing point 
    2322   USE fldread         ! read input fields 
    2423   USE sbc_oce         ! Surface boundary condition: ocean fields 
  • trunk/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r1025 r1037  
    2424   USE phycst          ! physical constants 
    2525   USE daymod          ! calendar 
    26    USE ocfzpt          ! ocean freezing point 
    2726   USE fldread         ! read input fields 
    2827   USE sbc_oce         ! Surface boundary condition: ocean fields 
  • trunk/NEMO/OPA_SRC/SBC/sbcflx.F90

    r1029 r1037  
    3030   USE phycst          ! physical constants 
    3131   USE daymod          ! calendar 
    32    USE ocfzpt          ! ocean freezing point 
    3332   USE fldread         ! read input fields 
    3433   USE iom             ! IOM library 
  • trunk/NEMO/OPA_SRC/SBC/sbcice_if.F90

    r888 r1037  
    55   !!                   covered area using ice-if model 
    66   !!====================================================================== 
    7    !! History :  9.0   !  06-06  (G. Madec)  Original code 
     7   !! History :  3.0   !  2006-06  (G. Madec)  Original code 
    88   !!---------------------------------------------------------------------- 
    99 
     
    1414   USE dom_oce         ! ocean space and time domain 
    1515   USE phycst          ! physical constants 
    16    USE ocfzpt          ! ocean freezing point 
    17    USE sbc_oce         ! Surface boundary condition: ocean fields 
     16   USE eosbn2          ! equation of state 
     17   USE sbc_oce         ! surface boundary condition: ocean fields 
    1818   USE fldread         ! read input field 
    1919   USE iom             ! I/O manager library 
     
    3030#  include "domzgr_substitute.h90" 
    3131   !!---------------------------------------------------------------------- 
    32    !!   OPA 9.0 , LOCEAN-IPSL (2006)  
    33    !! $ Id: $ 
     32   !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)  
     33   !! $Id:$ 
    3434   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    3535   !!---------------------------------------------------------------------- 
     
    4747      !!              - blah blah blah, ... 
    4848      !! 
    49       !! ** Action  :   qns, qsr:  update heat flux below sea-ice 
    50       !!                emp, emps: update freshwater flux below sea-ice 
     49      !! ** Action  :   utau, vtau : remain unchanged 
     50      !!                qns, qsr   : update heat flux below sea-ice 
     51      !!                emp, emps  : update freshwater flux below sea-ice 
     52      !!                fr_i       : update the ice fraction 
    5153      !!--------------------------------------------------------------------- 
    5254      INTEGER, INTENT(in)          ::   kt         ! ocean time step 
    5355      ! 
     56      INTEGER  ::   ji, jj     ! dummy loop indices 
     57      INTEGER  ::   ierror     ! return error code 
     58      REAL(wp) ::   ztrp, zsice, zt_fzp, zfr_obs 
     59      REAL(wp) ::   zqri, zqrj, zqrp, zqi 
     60      !! 
    5461      CHARACTER(len=100) ::   cn_dir              ! Root directory for location of ice-if files 
    5562      TYPE(FLD_N)        ::   sn_ice              ! informations about the fields to be read 
    5663      NAMELIST/namsbc_iif/ cn_dir, sn_ice 
    57       ! 
    58       INTEGER  ::   ji, jj     ! dummy loop indices 
    59       INTEGER  ::   ierror     ! return error code 
    60       REAL(wp) ::   ztrp, zsice, zt_fzp, zicover_obs, zicover_opa 
    61       REAL(wp) ::   zqri, zqrj, zqrp, zqi 
    6264      !!--------------------------------------------------------------------- 
    6365      !                                         ! ====================== ! 
     
    8082 
    8183         ! store namelist information in sf_ice structure 
    82          WRITE(sf_ice(1)%clrootname,'(a,a)' )   TRIM( cn_dir ), TRIM( sn_ice%clname ) 
     84         WRITE(sf_ice(1)%clrootname,'(a,a)')   TRIM( cn_dir ), TRIM( sn_ice%clname ) 
    8385         sf_ice(1)%freqh   = sn_ice%freqh 
    8486         sf_ice(1)%clvar   = sn_ice%clvar 
     
    111113         zsice = - 0.04 / 0.8    ! ratio of isohaline compressibility over isotherme compressibility 
    112114                                 ! ( d rho / dt ) / ( d rho / ds )      ( s = 34, t = -1.8 ) 
    113          ! Flux computation 
     115          
     116         fr_i(:,:) = tfreez( sss_m ) * tmask(:,:,1)      ! sea surface freezing temperature [Celcius] 
     117 
     118         ! Flux and ice fraction computation 
    114119!CDIR COLLAPSE 
    115120         DO jj = 1, jpj 
    116121            DO ji = 1, jpi 
    117                ! ... sea surface freezing point temperature [Celcius] 
    118                zt_fzp = (  ( - 0.0575 + 1.710523e-3 * SQRT( sss_m(ji,jj) )   & 
    119             &                         - 2.154996e-4 *       sss_m(ji,jj)   ) * sss_m(ji,jj)  ) * tmask(ji,jj,1) 
    120              
    121                ! ... indicators : ice cover (obs, ocean model) & hemisphere (=1 north, =-1 south) 
    122                zicover_obs = sf_ice(1)%fnow(ji,jj)                                                ! observed  
    123                zicover_opa = MAX( 0., SIGN( 1., zt_fzp - sst_m(ji,jj) )  ) * tmask(ji,jj,1)   ! model    
     122               ! 
     123               zt_fzp  = fr_i(ji,jj)                        ! freezing point temperature 
     124               zfr_obs = sf_ice(1)%fnow(ji,jj)              ! observed ice cover 
     125               !                                            ! ocean ice fraction (0/1) from the freezing point temperature 
     126               IF( sst_m(ji,jj) <= zt_fzp ) THEN   ;   fr_i(ji,jj) = 1.e0 
     127               ELSE                                ;   fr_i(ji,jj) = 0.e0 
     128               ENDIF 
    124129 
    125                ! ... avoid over-freezing point temperature 
    126                tn(ji,jj,1) = MAX( tn(ji,jj,1), zt_fzp ) 
     130               tn(ji,jj,1) = MAX( tn(ji,jj,1), zt_fzp )     ! avoid over-freezing point temperature 
    127131 
    128                ! ... solar heat flux : zero below observed ice cover 
    129                qsr(ji,jj) = ( 1. - zicover_obs ) * qsr(ji,jj) 
     132               qsr(ji,jj) = ( 1. - zfr_obs ) * qsr(ji,jj)   ! solar heat flux : zero below observed ice cover 
    130133 
    131                ! ... non solar heat flux : add a damping term  
    132                !      - gamma*(t-(tgel-1.))  if observed ice and no opa ice   (zicover_obs=1 zicover_opa=0) 
    133                !      - gamma*min(0,t-tgel)  if observed ice and opa ice      (zicover_obs=1 zicover_opa=1) 
    134  
     134               !                                            ! non solar heat flux : add a damping term  
     135               !      # ztrp*(t-(tgel-1.))  if observed ice and no opa ice   (zfr_obs=1 fr_i=0) 
     136               !      # ztrp*min(0,t-tgel)  if observed ice and opa ice      (zfr_obs=1 fr_i=1) 
    135137               zqri = ztrp * ( tb(ji,jj,1) - ( zt_fzp - 1.) ) 
    136138               zqrj = ztrp * MIN( 0., tb(ji,jj,1) - zt_fzp ) 
     139               zqrp = ( zfr_obs * ( (1. - fr_i(ji,jj) ) * zqri    & 
     140                 &                 +      fr_i(ji,jj)   * zqrj ) ) * tmask(ji,jj,1) 
    137141 
    138                zqrp =  ( zicover_obs * ( (1. - zicover_opa ) * zqri    & 
    139                  &                      +      zicover_opa   * zqrj ) ) * tmask(ji,jj,1) 
    140  
    141                ! c) net downward heat flux q() = q0 + qrp() 
    142                ! for q0 
    143                ! # qns unchanged              if no climatological ice              (zicover_obs=0) 
    144                ! # qns = zqrp                 if climatological ice and no opa ice  (zicover_obs=1, zicover_opa=0) 
    145                ! # qns = zqrp -2(-4) watt/m2  if climatological ice and opa ice     (zicover_obs=1, zicover_opa=1) 
    146                ! (-2=arctic, -4=antarctic)    
     142               !                                            ! non-solar heat flux  
     143               !      # qns unchanged              if no climatological ice              (zfr_obs=0) 
     144               !      # qns = zqrp                 if climatological ice and no opa ice  (zfr_obs=1, fr_i=0) 
     145               !      # qns = zqrp -2(-4) watt/m2  if climatological ice and opa ice     (zfr_obs=1, fr_i=1) 
     146               !                                   (-2=arctic, -4=antarctic)    
    147147               zqi = -3. + SIGN( 1.e0, ff(ji,jj) ) 
    148                qns(ji,jj) = ( ( 1.- zicover_obs ) * qns(ji,jj)   & 
    149                   &          +      zicover_obs   * zicover_opa * zqi ) * tmask(ji,jj,1)   & 
     148               qns(ji,jj) = ( ( 1.- zfr_obs ) * qns(ji,jj)                             & 
     149                  &          +      zfr_obs   * fr_i(ji,jj) * zqi ) * tmask(ji,jj,1)   & 
    150150                  &       + zqrp 
    151151            END DO 
  • trunk/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r914 r1037  
    4646   USE in_out_manager  ! I/O manager 
    4747   USE prtctl          ! Print control 
    48    USE ocfzpt          ! ocean freezing point 
    4948 
    5049   IMPLICIT NONE 
     
    158157            DO jj = 1, jpj 
    159158               DO ji = 1, jpi 
    160                   zinda    = MAX(  0.e0, SIGN(  1.e0, -( -1.5 - freeze(ji,jj) )  )  ) 
     159!!                zinda    = MAX(  0.e0, SIGN(  1.e0, -( -1.5 - freeze(ji,jj) )  )  ) 
     160!!gm  BBBBBBBBUUUUUUGGGGGGGGGGGGGGGGG    zinda alway negatif   !!!   ???????? 
     161                  zinda    = MAX(  0.e0, SIGN(  1.e0, -( -1.5 - 1.e0 + frld(ji,jj) )  )  ) 
    161162                  qsr(ji,jj) = zinda * qsr(ji,jj) 
    162163               END DO 
  • trunk/NEMO/OPA_SRC/SBC/sbcmod.F90

    r920 r1037  
    44   !! Surface module :  provide to the ocean its surface boundary condition 
    55   !!====================================================================== 
    6    !! History :  9.0   !  06-07  (G. Madec)  Original code 
     6   !! History :  3.0   !  2006-07  (G. Madec)  Original code 
    77   !!---------------------------------------------------------------------- 
    88 
    99   !!---------------------------------------------------------------------- 
    1010   !!   sbc_init       : read namsbc namelist 
    11    !!   sbc            : surface ocean momentum, heat and freshwater  
    12    !!                    boundary conditions 
     11   !!   sbc            : surface ocean momentum, heat and freshwater boundary conditions 
    1312   !!---------------------------------------------------------------------- 
    1413   USE oce             ! ocean dynamics and tracers 
     
    1615   USE daymod          ! calendar 
    1716   USE phycst          ! physical constants 
    18    USE ocfzpt          ! ocean freezing point 
    1917 
    2018   USE ice_oce         ! sea-ice model : LIM 
     
    6664#  include "domzgr_substitute.h90" 
    6765   !!---------------------------------------------------------------------- 
    68    !!   OPA 9.0 , LOCEAN-IPSL (2006)  
     66   !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)  
    6967   !! $Id: $ 
    7068   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    8583      !!---------------------------------------------------------------------- 
    8684      INTEGER ::   icpt      ! temporary integer 
    87       !!---------------------------------------------------------------------- 
     85      !! 
    8886      NAMELIST/namsbc/ nn_fsbc, ln_ana, ln_flx, ln_blk_clio, ln_blk_core, ln_cpl,   & 
    8987         &             nn_ice , ln_dm2dc, ln_rnf, ln_ssr, nn_fwb, nn_ico_cpl 
     88      !!---------------------------------------------------------------------- 
    9089 
    9190      IF(lwp) THEN 
     
    119118         WRITE(numout,*) '              coupled    formulation (T if key_sbc_cpl)  ln_cpl      = ', ln_cpl 
    120119         WRITE(numout,*) '           Misc. options of sbc : ' 
    121          WRITE(numout,*) '              ice management in the sbc (=0/1/2       nn_ice      = ', nn_ice  
     120         WRITE(numout,*) '              ice management in the sbc (=0/1/2/3)       nn_ice      = ', nn_ice  
    122121         WRITE(numout,*) '              ice-ocean stress computation (=0/1/2)      nn_ico_cpl  = ', nn_ico_cpl 
    123122         WRITE(numout,*) '              daily mean to diurnal cycle qsr            ln_dm2dc    = ', ln_dm2dc  
     
    128127      ENDIF 
    129128 
     129      IF( .NOT. ln_rnf )   nn_runoff = 0      ! no runoff, or runoff mouths 
     130      IF( nn_ice == 0  )   fr_i(:,:) = 0.e0   ! no ice in the domain, ice fraction is always zero 
     131 
    130132      ! Check consistancy   !!gm mixture of real and integer : coding to be changed.... 
    131  
    132       IF( .NOT. ln_rnf )   nn_runoff = 0      ! no runoff, or runoff mouths 
    133133 
    134134      IF( nn_ice == 2 )   THEN 
     
    191191      !! ** Action  : - set the ocean surface boundary condition, i.e.   
    192192      !!                utau, vtau, qns, qsr, emp, emps, qrp, erp 
     193      !!              - updte the ice fraction : fr_i 
    193194      !!---------------------------------------------------------------------- 
    194195      INTEGER, INTENT(in) ::   kt       ! ocean time step 
     
    202203      !                                          ! temperature and salinity (at T-point) over nf_sbc time-step 
    203204      !                                          ! (i.e. sst_m, sss_m, ssu_m, ssv_m) 
    204  
    205 !!gm  add a flag on nn_fsbc frequency ?????  except the diurnal cycle! 
    206 !!    IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN 
    207  
    208205 
    209206      ! sbc formulation 
     
    219216      CASE(  5 )   ;   CALL sbc_cpl     ( kt )      ! coupled formulation 
    220217      CASE( -1 )                                 
    221          ;             CALL sbc_ana     ( kt )      ! ESOPA, test ALL the formulations 
    222          ;             CALL sbc_gyre    ( kt ) 
    223          ;             CALL sbc_flx     ( kt ) 
    224          ;             CALL sbc_blk_clio( kt ) 
    225          ;             CALL sbc_blk_core( kt ) 
    226          ;             CALL sbc_cpl     ( kt ) 
     218                       CALL sbc_ana     ( kt )      ! ESOPA, test ALL the formulations 
     219                       CALL sbc_gyre    ( kt ) 
     220                       CALL sbc_flx     ( kt ) 
     221                       CALL sbc_blk_clio( kt ) 
     222                       CALL sbc_blk_core( kt ) 
     223                       CALL sbc_cpl     ( kt ) 
    227224      END SELECT 
    228225 
     
    232229!!gm  IF( ln_dm2dc       )   CALL sbc_dcy( kt )                 ! Daily mean qsr distributed over the Diurnal Cycle 
    233230       
    234       SELECT CASE( nn_ice )                                     ! Update sbc over ice-covered areas 
    235       CASE(  1 )   ;         CALL sbc_ice_if ( kt )                     ! Ice-cover climatology ("Ice-if" model) 
    236          !                                                              ! (update heat and freshwater fluxes) 
    237       CASE(  2 )   ;         CALL sbc_ice_lim_2( kt, nsbc )             ! LIM 2.0 ice model 
    238          !                                                              ! (update heat and freshwater fluxes) 
    239       CASE(  3 )   ;         CALL sbc_ice_lim  ( kt, nsbc, nn_ico_cpl)          ! LIM 3.0 ice model 
    240       END SELECT                                                        ! (update all fluxes using bulk + LIM) 
    241  
    242       IF( ln_ssr         )   CALL sbc_ssr( kt )                 ! add SST/SSS damping term 
    243  
    244       IF( ln_rnf         )   CALL sbc_rnf( kt )                 ! add runoffs to fresh water fluxes 
     231      SELECT CASE( nn_ice )                                     ! Update heat and freshwater fluxes over ice-covered areas 
     232      CASE(  1 )   ;       CALL sbc_ice_if ( kt )                     ! Ice-cover climatology ("Ice-if" model) 
     233         !                                                       
     234      CASE(  2 )   ;       CALL sbc_ice_lim_2( kt, nsbc )             ! LIM 2.0 ice model 
     235         !                                                      
     236      CASE(  3 )   ;       CALL sbc_ice_lim  ( kt, nsbc, nn_ico_cpl)  ! LIM 3.0 ice model 
     237      END SELECT                                               
     238 
     239      IF( ln_ssr       )   CALL sbc_ssr( kt )                   ! add SST/SSS damping term 
     240 
     241      IF( ln_rnf       )   CALL sbc_rnf( kt )                   ! add runoffs to fresh water fluxes 
    245242  
    246       IF( nn_fwb    /= 0 )   CALL sbc_fwb( kt, nn_fwb, nn_fsbc )         ! control the freshwater budget 
     243      IF( nn_fwb  /= 0 )   CALL sbc_fwb( kt, nn_fwb, nn_fsbc )  ! control the freshwater budget 
    247244 
    248245      IF( nclosea == 1 )   CALL sbc_clo( kt )                   ! treatment of closed sea in the model domain  
     
    250247      ! 
    251248      IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    252          CALL prt_ctl(tab2d_1=emp    , clinfo1=' emp  - : ', mask1=tmask, ovlap=1) 
    253          CALL prt_ctl(tab2d_1=emps   , clinfo1=' emps - : ', mask1=tmask, ovlap=1) 
    254          CALL prt_ctl(tab2d_1=qns    , clinfo1=' qns  - : ', mask1=tmask, ovlap=1) 
    255          CALL prt_ctl(tab2d_1=qsr    , clinfo1=' qsr  - : ', mask1=tmask, ovlap=1) 
    256          CALL prt_ctl(tab3d_1=tmask  , clinfo1=' tmask  : ', mask1=tmask, ovlap=1, kdim=jpk) 
    257          CALL prt_ctl(tab3d_1=tn     , clinfo1=' sst  - : ', mask1=tmask, ovlap=1, kdim=1) 
    258          CALL prt_ctl(tab3d_1=sn     , clinfo1=' sss  - : ', mask1=tmask, ovlap=1, kdim=1) 
    259          CALL prt_ctl(tab2d_1=utau   , clinfo1=' utau - : ', mask1=umask, & 
    260                       tab2d_2=vtau   , clinfo2=' vtau - : ', mask2=vmask, ovlap=1) 
    261       ENDIF 
    262  
    263 !!gm 
    264 !!    ENDIF 
    265 !!gm 
     249         CALL prt_ctl(tab2d_1=fr_i   , clinfo1=' fr_i - : ', mask1=tmask, ovlap=1 ) 
     250         CALL prt_ctl(tab2d_1=emp    , clinfo1=' emp  - : ', mask1=tmask, ovlap=1 ) 
     251         CALL prt_ctl(tab2d_1=emps   , clinfo1=' emps - : ', mask1=tmask, ovlap=1 ) 
     252         CALL prt_ctl(tab2d_1=qns    , clinfo1=' qns  - : ', mask1=tmask, ovlap=1 ) 
     253         CALL prt_ctl(tab2d_1=qsr    , clinfo1=' qsr  - : ', mask1=tmask, ovlap=1 ) 
     254         CALL prt_ctl(tab3d_1=tmask  , clinfo1=' tmask  : ', mask1=tmask, ovlap=1, kdim=jpk ) 
     255         CALL prt_ctl(tab3d_1=tn     , clinfo1=' sst  - : ', mask1=tmask, ovlap=1, kdim=1   ) 
     256         CALL prt_ctl(tab3d_1=sn     , clinfo1=' sss  - : ', mask1=tmask, ovlap=1, kdim=1   ) 
     257         CALL prt_ctl(tab2d_1=utau   , clinfo1=' utau - : ', mask1=umask,                      & 
     258            &         tab2d_2=vtau   , clinfo2=' vtau - : ', mask2=vmask, ovlap=1 ) 
     259      ENDIF 
    266260      ! 
    267261   END SUBROUTINE sbc 
  • trunk/NEMO/OPA_SRC/SBC/sbcssr.F90

    r888 r1037  
    1616   USE phycst          ! physical constants 
    1717   USE daymod          ! calendar 
    18    USE ocfzpt          ! ocean freezing point 
    1918   USE sbcrnf          ! surface boundary condition : runoffs 
    2019   USE fldread         ! read input fields 
  • trunk/NEMO/OPA_SRC/TRA/traadv_cen2.F90

    r916 r1037  
    2323   USE dynspg_oce      ! choice/control of key cpp for surface pressure gradient 
    2424   USE trdmod_oce      ! ocean variables trends 
     25   USE eosbn2          ! equation of state 
    2526   USE trdmod          ! ocean active tracers trends  
    2627   USE closea          ! closed sea 
    2728   USE trabbl          ! advective term in the BBL 
    28    USE ocfzpt          ! 
    2929   USE sbcmod          ! surface Boundary Condition 
    3030   USE sbcrnf          ! river runoffs 
     
    137137         &          zupst , zupss , zcent , zcens ,   &  !    "         " 
    138138         &          z_hdivn_x, z_hdivn_y, z_hdivn  
     139      REAL(wp) ::   zice                                 !    -         - 
     140      REAL(wp), DIMENSION(jpi,jpj)     ::   ztfreez            ! 2D workspace 
    139141      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zwz, ztrdt, zind   ! 3D workspace 
    140142      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zww, ztrds         !  "      " 
     
    160162      ! Upstream / centered scheme indicator 
    161163      ! ------------------------------------ 
     164!!gm  not strickly exact : the freezing point should be computed at each ocean levels... 
     165!!gm  not a big deal since cen2 is no more used in global ice-ocean simulations 
     166      ztfreez(:,:) = tfreez( sn(:,:,1) ) 
    162167      DO jk = 1, jpk 
    163168         DO jj = 1, jpj 
    164169            DO ji = 1, jpi 
     170               !                                        ! below ice covered area (if tn < "freezing"+0.1 ) 
     171               IF( tn(ji,jj,jk) <= ztfreez(ji,jj) + 0.1 ) THEN   ;   zice = 1.e0 
     172               ELSE                                              ;   zice = 0.e0 
     173               ENDIF 
    165174               zind(ji,jj,jk) = MAX (   & 
    166175                  rnfmsk(ji,jj) * rnfmsk_z(jk),      &  ! near runoff mouths (& closed sea outflows) 
    167                   upsmsk(ji,jj)                      &  ! some of some straits 
    168 #if defined key_lim3 || defined key_lim2 
    169                   !                                     ! below ice covered area (if tn < "freezing"+0.1 ) 
    170                   , MAX(  0., SIGN( 1., fzptn(ji,jj) + 0.1 - tn(ji,jj,jk) )  ) * tmask(ji,jj,jk)   & 
    171 #endif 
    172                   &                  ) 
     176                  upsmsk(ji,jj)               ,      &  ! some of some straits 
     177                  zice                               &  ! below ice covered area (if tn < "freezing"+0.1 ) 
     178                  &                  ) * tmask(ji,jj,jk) 
    173179            END DO 
    174180         END DO 
  • trunk/NEMO/OPA_SRC/opa.F90

    r1002 r1037  
    6464 
    6565   USE phycst          ! physical constant                  (par_cst routine) 
    66    USE ocfzpt          ! ocean freezing point              (oc_fz_pt routine) 
    6766   USE trdmod          ! momentum/tracers trends       (trd_mod_init routine) 
    6867 
     
    278277      CALL istate_init                      ! ocean initial state (Dynamics and tracers) 
    279278 
    280       CALL oc_fz_pt                         ! Surface freezing point 
    281  
    282279      !                                     ! Ocean physics 
    283280 
  • trunk/NEMO/OPA_SRC/step.F90

    r988 r1037  
    4242   USE sbcmod          ! surface boundary condition       (sbc     routine) 
    4343   USE sbcrnf          ! surface boundary condition: runoff variables 
    44    USE ocfzpt          ! surface ocean freezing point    (oc_fz_pt routine) 
    4544 
    4645   USE trcstp          ! passive tracer time-stepping      (trc_stp routine) 
     
    324323      ! N.B. ua, va, ta, sa arrays are used as workspace in this section 
    325324      !----------------------------------------------------------------------- 
    326                        CALL oc_fz_pt                        ! ocean surface freezing temperature 
    327325                       CALL div_cur( kstp )                 ! Horizontal divergence & Relative vorticity 
    328326      IF( n_cla == 1 ) CALL div_cla( kstp )                 ! Cross Land Advection (Update Hor. divergence) 
Note: See TracChangeset for help on using the changeset viewer.