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 5208 for branches/2014/dev_r4650_UKMO11_restart_functionality/NEMOGCM/NEMO/LIM_SRC_3/limistate.F90 – NEMO

Ignore:
Timestamp:
2015-04-13T15:08:59+02:00 (9 years ago)
Author:
davestorkey
Message:

Merge in changes from trunk up to 5021.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4650_UKMO11_restart_functionality/NEMOGCM/NEMO/LIM_SRC_3/limistate.F90

    r4688 r5208  
    66   !! History :  2.0  ! 2004-01 (C. Ethe, G. Madec)  Original code 
    77   !!            4.0  ! 2011-02 (G. Madec) dynamical allocation 
    8    !!             -   ! 2012    (C. Rousset) add par_oce (for jp_sal)...bug? 
     8   !!             -   ! 2014    (C. Rousset) add N/S initializations 
    99   !!---------------------------------------------------------------------- 
    1010#if defined key_lim3 
     
    2929   USE lib_fortran      ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
    3030   USE wrk_nemo         ! work arrays 
    31    USE cpl_oasis3, ONLY : lk_cpl 
    3231 
    3332   IMPLICIT NONE 
     
    3635   PUBLIC   lim_istate      ! routine called by lim_init.F90 
    3736 
    38    !! * Module variables 
    3937   !                          !!** init namelist (namiceini) ** 
    4038   REAL(wp) ::   thres_sst   ! threshold water temperature for initial sea ice 
     
    5654   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    5755   !!---------------------------------------------------------------------- 
    58  
    5956CONTAINS 
    6057 
     
    8077      !! 
    8178      !! ** Notes   : o_i, t_su, t_s, t_i, s_i must be filled everywhere, even 
    82       !!              where there is no ice (clem: I do not know why but it is mandatory)  
     79      !!              where there is no ice (clem: I do not know why, is it mandatory?)  
    8380      !! 
    8481      !! History : 
     
    116113      CALL lim_istate_init     !  reading the initials parameters of the ice 
    117114 
    118 # if defined key_coupled 
    119       albege(:,:)   = 0.8 * tms(:,:) 
    120 # endif 
    121  
    122115      ! surface temperature 
    123116      DO jl = 1, jpl ! loop over categories 
     
    125118         tn_ice(:,:,jl) = rtt * tms(:,:) 
    126119      END DO 
    127       ! Basal temperature is set to the freezing point of seawater in Kelvin 
    128       t_bo(:,:) = ( tfreez( tsn(:,:,1,jp_sal) ) + rt0 ) * tms(:,:)  
     120 
     121      ! basal temperature (considered at freezing point) 
     122      t_bo(:,:) = ( eos_fzp( tsn(:,:,1,jp_sal) ) + rt0 ) * tms(:,:)  
    129123 
    130124      IF( ln_limini ) THEN 
     
    133127      ! 2) Basal temperature, ice mask and hemispheric index 
    134128      !-------------------------------------------------------------------- 
    135       ! ice if sst <= t-freez + thres_sst 
    136       DO jj = 1, jpj                                        
     129 
     130      DO jj = 1, jpj                                       ! ice if sst <= t-freez + ttest 
    137131         DO ji = 1, jpi 
    138             IF( ( tsn(ji,jj,1,jp_tem)  - ( t_bo(ji,jj) - rt0 ) ) * tms(ji,jj) >= thres_sst ) THEN  ; zswitch(ji,jj) = 0._wp * tms(ji,jj)    ! no ice 
    139             ELSE                                                                                   ; zswitch(ji,jj) = 1._wp * tms(ji,jj)    !    ice 
     132            IF( ( tsn(ji,jj,1,jp_tem)  - ( t_bo(ji,jj) - rt0 ) ) * tms(ji,jj) >= thres_sst ) THEN  
     133               zswitch(ji,jj) = 0._wp * tms(ji,jj)    ! no ice 
     134            ELSE                                                                                    
     135               zswitch(ji,jj) = 1._wp * tms(ji,jj)    !    ice 
    140136            ENDIF 
    141137         END DO 
     
    144140 
    145141      ! Hemispheric index 
    146       ! MV 2011 new initialization 
    147142      DO jj = 1, jpj 
    148143         DO ji = 1, jpi 
     
    154149         END DO 
    155150      END DO 
    156       ! END MV 2011 new initialization 
    157151 
    158152      !-------------------------------------------------------------------- 
     
    299293 
    300294      IF(lwp) THEN  
    301          WRITE(numout,*), ' ztests : ', ztests 
     295         WRITE(numout,*) ' ztests : ', ztests 
    302296         IF ( ztests .NE. 4 ) THEN 
    303297            WRITE(numout,*) 
    304             WRITE(numout,*), ' !!!! ALERT                  !!! ' 
    305             WRITE(numout,*), ' !!!! Something is wrong in the LIM3 initialization procedure ' 
     298            WRITE(numout,*) ' !!!! ALERT                  !!! ' 
     299            WRITE(numout,*) ' !!!! Something is wrong in the LIM3 initialization procedure ' 
    306300            WRITE(numout,*) 
    307             WRITE(numout,*), ' *** ztests is not equal to 4 ' 
    308             WRITE(numout,*), ' *** ztest_i (i=1,4) = ', ztest_1, ztest_2, ztest_3, ztest_4 
    309             WRITE(numout,*), ' zat_i_ini : ', zat_i_ini(i_hemis) 
    310             WRITE(numout,*), ' zht_i_ini : ', zht_i_ini(i_hemis) 
     301            WRITE(numout,*) ' *** ztests is not equal to 4 ' 
     302            WRITE(numout,*) ' *** ztest_i (i=1,4) = ', ztest_1, ztest_2, ztest_3, ztest_4 
     303            WRITE(numout,*) ' zat_i_ini : ', zat_i_ini(i_hemis) 
     304            WRITE(numout,*) ' zht_i_ini : ', zht_i_ini(i_hemis) 
    311305         ENDIF ! ztests .NE. 4 
    312306      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.