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 991 for branches/dev_003_CPL/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90 – NEMO

Ignore:
Timestamp:
2008-05-23T17:55:55+02:00 (16 years ago)
Author:
smasson
Message:

dev_003_CPL: preliminary draft (not working), see ticket #155

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/dev_003_CPL/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r990 r991  
    1212   !!   'key_lim2' :                                  LIM 2.0 sea-ice model 
    1313   !!---------------------------------------------------------------------- 
     14   !!---------------------------------------------------------------------- 
    1415   !!   sbc_ice_lim_2  : sea-ice model time-stepping and 
    1516   !!                    update ocean sbc over ice-covered area 
    1617   !!---------------------------------------------------------------------- 
    1718   USE oce             ! ocean dynamics and tracers 
    18    USE c1d             ! 1d configuration 
    1919   USE dom_oce         ! ocean space and time domain 
    2020   USE ice_2 
     
    4646   USE in_out_manager  ! I/O manager 
    4747   USE prtctl          ! Print control 
    48    USE ocfzpt          ! ocean freezing point 
    4948 
    5049   IMPLICIT NONE 
     
    5958#  include "vectopt_loop_substitute.h90" 
    6059   !!---------------------------------------------------------------------- 
    61    !! NEMO/SBC  3.0 , LOCEAN-IPSL (2008)  
    62    !! $Id: $ 
     60   !!   OPA 9.0 , LOCEAN-IPSL (2006)  
     61   !! $ Id: $ 
    6362   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    6463   !!---------------------------------------------------------------------- 
     
    9089      !! 
    9190      INTEGER  ::   ji, jj   ! dummy loop indices 
    92       REAL(wp) ::   zinda     
    9391      REAL(wp), DIMENSION(jpi,jpj,1) ::   alb_ice_os   ! albedo of the ice under overcast sky 
    9492      REAL(wp), DIMENSION(jpi,jpj,1) ::   alb_ice_cs   ! albedo of ice under clear sky 
     
    126124 
    127125         ! ... masked sea surface freezing temperature [Kelvin] (set to rt0 over land) 
    128          tfu(:,:) = tfreez( sss_m ) +  rt0  
    129  
    130          zsist (:,:,1) = sist (:,:) 
    131          zhicif(:,:,1) = hicif(:,:)   ;   zhsnif(:,:,1) = hsnif(:,:) 
     126         tfu(:,:) = tfreez( sss_m ) + rt0  
     127 
    132128 
    133129         ! ... ice albedo 
    134          CALL albedo_ice( zsist, zhicif, zhsnif, alb_ice_cs, alb_ice_os ) 
    135  
     130          
     131         IF ( nsbc /= 5 ) THEN 
     132+++ INTERFACE 2D/3D suprimer les tableaux intermediaires 
     133+++ les mettre sous cle cpp 
     134+++ il faudrait utiliser les variables de transfert pour tn_ice, ice/snow thickness, albedo... 
     135 
     136            zsist (:,:,1) = sist (:,:) 
     137            zhicif(:,:,1) = hicif(:,:)   ;   zhsnif(:,:,1) = hsnif(:,:) 
     138            CALL albedo_ice( zsist, zhicif, zhsnif, alb_ice_cs, alb_ice_os ) 
    136139         ! ... Sea-ice surface boundary conditions output from bulk formulae : 
    137140         !     - utaui_ice  ! surface ice stress i-component (I-point)   [N/m2] 
     
    154157               &                               tprecip   , sprecip    ,                          & 
    155158               &                               fr1_i0    , fr2_i0     , cl_grid  ) 
    156  
    157             ! CAUTION: ocean shortwave radiation sets to zero if more than 50% of sea-ice !!gm to be removed 
    158             DO jj = 1, jpj 
    159                DO ji = 1, jpi 
    160                   zinda    = MAX(  0.e0, SIGN(  1.e0, -( -1.5 - freeze(ji,jj) )  )  ) 
    161                   qsr(ji,jj) = zinda * qsr(ji,jj) 
    162                END DO 
    163             END DO 
    164  
    165159         CASE( 4 )           ! CORE bulk formulation 
    166160            CALL blk_ice_core( zsist , ui_ice , vi_ice   , alb_ice_cs ,                         & 
     
    175169         qla_ice(:,:) = zqla_ice(:,:,1)   ;   dqla_ice(:,:) = zdqla_ice(:,:,1) 
    176170 
     171         ENDIF 
    177172         IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    178173            CALL prt_ctl_info( 'Ice Forcings ' ) 
     
    188183         !  Ice model step  ! 
    189184         ! ---------------- ! 
    190                                         CALL lim_rst_opn_2  ( kt )      ! Open Ice restart file 
    191          IF( .NOT. lk_c1d ) THEN                                        ! Ice dynamics & transport (not in 1D case) 
    192                                         CALL lim_dyn_2      ( kt )           ! Ice dynamics    ( rheology/dynamics ) 
    193                                         CALL lim_trp_2      ( kt )           ! Ice transport   ( Advection/diffusion ) 
    194             IF( ln_limdmp )             CALL lim_dmp_2      ( kt )           ! Ice damping  
    195          ENDIF 
    196                                         CALL lim_thd_2      ( kt )      ! Ice thermodynamics  
    197                                         CALL lim_sbc_2      ( kt )      ! Ice/Ocean Mass & Heat fluxes  
     185         ;                              CALL lim_rst_opn_2  ( kt )      ! Open Ice restart file 
     186         ;                              CALL lim_dyn_2      ( kt )      ! Ice dynamics    ( rheology/dynamics ) 
     187         ;                              CALL lim_trp_2      ( kt )      ! Ice transport   ( Advection/diffusion ) 
     188         IF( ln_limdmp )                CALL lim_dmp_2      ( kt )      ! Ice damping  
     189         ;                              CALL lim_thd_2      ( kt )      ! Ice thermodynamics  
     190         ;                              CALL lim_sbc_2      ( kt )      ! Ice/Ocean Mass & Heat fluxes  
    198191         IF( MOD( kt+nn_fsbc-1, ninfo ) == 0 .OR.   & 
    199192            &  ntmoy == 1 )             CALL lim_dia_2      ( kt )      ! Ice Diagnostics  
    200                                         CALL lim_wri_2      ( kt )      ! Ice outputs  
     193         ;                              CALL lim_wri_2      ( kt )      ! Ice outputs  
    201194         IF( lrst_ice )                 CALL lim_rst_write_2( kt )      ! Ice restart file  
    202195         ! 
Note: See TracChangeset for help on using the changeset viewer.