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 2528 for trunk/NEMOGCM/NEMO/LIM_SRC_3/limistate.F90 – NEMO

Ignore:
Timestamp:
2010-12-27T18:33:53+01:00 (13 years ago)
Author:
rblod
Message:

Update NEMOGCM from branch nemo_v3_3_beta

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/limistate.F90

    r1471 r2528  
    44   !!              Initialisation of diagnostics ice variables 
    55   !!====================================================================== 
     6   !! History :  2.0  ! 2004-01 (C. Ethe, G. Madec)  Original code 
     7   !!---------------------------------------------------------------------- 
    68#if defined key_lim3 
    79   !!---------------------------------------------------------------------- 
     
    1113   !!   lim_istate_init :  initialization of ice state and namelist read 
    1214   !!---------------------------------------------------------------------- 
    13    !! * Modules used 
    14    USE phycst 
    15    USE oce             ! dynamics and tracers variables 
    16    USE dom_oce 
    17    USE sbc_oce         ! Surface boundary condition: ocean fields 
    18    USE par_ice         ! ice parameters 
    19    USE eosbn2          ! equation of state 
    20    USE in_out_manager 
    21    USE dom_ice 
    22    USE ice 
    23    USE lbclnk 
     15   USE phycst           ! physical constant 
     16   USE oce              ! dynamics and tracers variables 
     17   USE dom_oce          ! ocean domain 
     18   USE sbc_oce          ! Surface boundary condition: ocean fields 
     19   USE eosbn2           ! equation of state 
     20   USE ice              ! sea-ice variables 
     21   USE par_ice          ! ice parameters 
     22   USE dom_ice          ! sea-ice domain 
     23   USE in_out_manager   ! I/O manager 
     24   USE lbclnk           ! lateral boundary condition - MPP exchanges 
    2425 
    2526   IMPLICIT NONE 
    2627   PRIVATE 
    2728 
    28    !! * Accessibility 
    29    PUBLIC lim_istate      ! routine called by lim_init.F90 
    30  
    31    !! * Module variables 
    32    REAL(wp) ::             & !!! ** init namelist (namiceini) ** 
    33       ttest    = 2.0  ,    &  ! threshold water temperature for initial sea ice 
    34       hninn    = 0.5  ,    &  ! initial snow thickness in the north 
    35       hginn_u  = 2.5  ,    &  ! initial ice thickness in the north 
    36       aginn_u  = 0.7  ,    &  ! initial leads area in the north 
    37       hginn_d  = 5.0  ,    &  ! initial ice thickness in the north 
    38       aginn_d  = 0.25 ,    &  ! initial leads area in the north 
    39       hnins    = 0.1  ,    &  ! initial snow thickness in the south 
    40       hgins_u  = 1.0  ,    &  ! initial ice thickness in the south 
    41       agins_u  = 0.7  ,    &  ! initial leads area in the south 
    42       hgins_d  = 2.0  ,    &  ! initial ice thickness in the south 
    43       agins_d  = 0.2  ,    &  ! initial leads area in the south 
    44       sinn     = 6.301 ,   &  ! initial salinity  
    45       sins     = 6.301 
    46  
    47    REAL(wp)  ::            &  ! constant values 
    48       zzero   = 0.0     ,  & 
    49       zone    = 1.0 
    50  
    51    !!---------------------------------------------------------------------- 
    52    !!   LIM 3.0,  UCL-LOCEAN-IPSL (2008) 
     29   PUBLIC   lim_istate      ! routine called by lim_init.F90 
     30 
     31   !                                  !!** init namelist (namiceini) ** 
     32   REAL(wp) ::   ttest    = 2.0_wp     ! threshold water temperature for initial sea ice 
     33   REAL(wp) ::   hninn    = 0.5_wp     ! initial snow thickness in the north 
     34   REAL(wp) ::   hginn_u  = 2.5_wp     ! initial ice thickness in the north 
     35   REAL(wp) ::   aginn_u  = 0.7_wp     ! initial leads area in the north 
     36   REAL(wp) ::   hginn_d  = 5.0_wp     ! initial ice thickness in the north 
     37   REAL(wp) ::   aginn_d  = 0.25_wp    ! initial leads area in the north 
     38   REAL(wp) ::   hnins    = 0.1_wp     ! initial snow thickness in the south 
     39   REAL(wp) ::   hgins_u  = 1.0_wp     ! initial ice thickness in the south 
     40   REAL(wp) ::   agins_u  = 0.7_wp     ! initial leads area in the south 
     41   REAL(wp) ::   hgins_d  = 2.0_wp     ! initial ice thickness in the south 
     42   REAL(wp) ::   agins_d  = 0.2_wp     ! initial leads area in the south 
     43   REAL(wp) ::   sinn     = 6.301_wp   ! initial salinity  
     44   REAL(wp) ::   sins     = 6.301_wp   ! 
     45 
     46   !!---------------------------------------------------------------------- 
     47   !! NEMO/LIM3 3.3 , UCL - NEMO Consortium (2010) 
    5348   !! $Id$ 
    54    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    55    !!---------------------------------------------------------------------- 
    56  
     49   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     50   !!---------------------------------------------------------------------- 
    5751CONTAINS 
    5852 
     
    6559      !! ** Method  :   restart from a state defined in a binary file 
    6660      !!                or from arbitrary sea-ice conditions 
    67       !! 
    68       !! History : 
    69       !!   2.0  !  01-04  (C. Ethe, G. Madec)  Original code 
    70       !!-------------------------------------------------------------------- 
    71  
    72       !! * Local variables 
     61      !!------------------------------------------------------------------- 
    7362      INTEGER  ::   ji, jj, jk, jl             ! dummy loop indices 
    74  
    75       REAL(wp) ::       &  ! temporary scalar 
    76          zeps6, zeps, ztmelts, & 
    77          epsi06 
    78       REAL(wp), DIMENSION(jpm) ::   & 
    79          zgfactorn, zhin, & 
    80          zgfactors, zhis 
    81       REAL(wp) ::  & 
    82          zvol, zare, zh, zh1, zh2, zh3, zan, zbn, zas, zbs  
    83       REAL(wp), DIMENSION(jpi,jpj) ::   zidto    ! ice indicator 
     63      REAL(wp) ::   zeps6, zeps, ztmelts, epsi06   ! local scalars 
     64      REAL(wp) ::  zvol, zare, zh, zh1, zh2, zh3, zan, zbn, zas, zbs  
     65      REAL(wp), DIMENSION(jpm)     ::   zgfactorn, zhin  
     66      REAL(wp), DIMENSION(jpm)     ::   zgfactors, zhis 
     67      REAL(wp), DIMENSION(jpi,jpj) ::   zidto      ! ice indicator 
    8468      !-------------------------------------------------------------------- 
    8569 
     
    8771      ! 1) Preliminary things  
    8872      !-------------------------------------------------------------------- 
    89       epsi06 = 1.0e-6 
     73      epsi06 = 1.e-6_wp 
    9074 
    9175      CALL lim_istate_init     !  reading the initials parameters of the ice 
     
    116100 
    117101      ! constants for heat contents 
    118       zeps   = 1.0d-20 
    119       zeps6  = 1.0d-06 
     102      zeps   = 1.e-20_wp 
     103      zeps6  = 1.e-06_wp 
    120104 
    121105      ! zgfactor for initial ice distribution 
    122       zgfactorn(:) = 0.0 
    123       zgfactors(:) = 0.0 
     106      zgfactorn(:) = 0._wp 
     107      zgfactors(:) = 0._wp 
    124108 
    125109      ! first ice type 
    126110      DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2) 
    127          zhin (1)     = ( hi_max(jl-1) + hi_max(jl) ) / 2.0 
    128          zgfactorn(1) = zgfactorn(1) + exp(-(zhin(1)-hginn_u)*(zhin(1)-hginn_u)/2.0) 
    129          zhis (1)     = ( hi_max(jl-1) + hi_max(jl) ) / 2.0 
    130          zgfactors(1) = zgfactors(1) + exp(-(zhis(1)-hgins_u)*(zhis(1)-hgins_u)/2.0) 
     111         zhin (1)     = ( hi_max(jl-1) + hi_max(jl) ) * 0.5_wp 
     112         zgfactorn(1) = zgfactorn(1) + exp(-(zhin(1)-hginn_u)*(zhin(1)-hginn_u) * 0.5_wp ) 
     113         zhis (1)     = ( hi_max(jl-1) + hi_max(jl) ) * 0.5_wp 
     114         zgfactors(1) = zgfactors(1) + exp(-(zhis(1)-hgins_u)*(zhis(1)-hgins_u) * 0.5_wp ) 
    131115      END DO ! jl 
    132116      zgfactorn(1) = aginn_u / zgfactorn(1) 
     
    135119      ! ------------- 
    136120      ! new distribution, polynom of second order, conserving area and volume 
    137       zh1 = 0.0 
    138       zh2 = 0.0 
    139       zh3 = 0.0 
     121      zh1 = 0._wp 
     122      zh2 = 0._wp 
     123      zh3 = 0._wp 
    140124      DO jl = 1, jpl 
    141          zh = ( hi_max(jl-1) + hi_max(jl) ) / 2.0 
     125         zh = ( hi_max(jl-1) + hi_max(jl) ) * 0.5_wp 
    142126         zh1 = zh1 + zh 
    143          zh2 = zh2 + zh*zh 
    144          zh3 = zh3 + zh*zh*zh 
     127         zh2 = zh2 + zh * zh 
     128         zh3 = zh3 + zh * zh * zh 
    145129      END DO 
    146130      IF(lwp) WRITE(numout,*) ' zh1 : ', zh1 
     
    148132      IF(lwp) WRITE(numout,*) ' zh3 : ', zh3 
    149133 
    150       zvol = aginn_u*hginn_u 
     134      zvol = aginn_u * hginn_u 
    151135      zare = aginn_u 
    152       IF ( jpl .GE. 2 ) THEN 
     136      IF( jpl >= 2 ) THEN 
    153137         zbn = ( zvol*zh2 - zare*zh3 ) / ( zh2*zh2 - zh1*zh3) 
    154138         zan = ( zare - zbn*zh1 ) / zh2 
     
    160144      IF(lwp) WRITE(numout,*) ' zan : ', zan  
    161145 
    162       zvol = agins_u*hgins_u 
     146      zvol = agins_u * hgins_u 
    163147      zare = agins_u 
    164       IF ( jpl .GE. 2 ) THEN 
     148      IF( jpl >= 2 ) THEN 
    165149         zbs = ( zvol*zh2 - zare*zh3 ) / ( zh2*zh2 - zh1*zh3) 
    166150         zas = ( zare - zbs*zh1 ) / zh2 
     
    205189            !--- Northern hemisphere 
    206190            !---------------------------------------------------------------- 
    207             IF( fcor(ji,jj) >= 0.e0 ) THEN     
     191            IF( fcor(ji,jj) >= 0._wp ) THEN     
    208192 
    209193               !----------------------- 
     
    453437            ENDIF ! on fcor 
    454438 
    455          ENDDO 
    456       ENDDO 
     439         END DO 
     440      END DO 
    457441 
    458442      !-------------------------------------------------------------------- 
     
    494478 
    495479      DO jl = 1, jpl 
    496  
    497480         CALL lbc_lnk( a_i(:,:,jl)  , 'T', 1. ) 
    498481         CALL lbc_lnk( v_i(:,:,jl)  , 'T', 1. ) 
     
    500483         CALL lbc_lnk( smv_i(:,:,jl), 'T', 1. ) 
    501484         CALL lbc_lnk( oa_i(:,:,jl) , 'T', 1. ) 
    502  
     485         ! 
    503486         CALL lbc_lnk( ht_i(:,:,jl) , 'T', 1. ) 
    504487         CALL lbc_lnk( ht_s(:,:,jl) , 'T', 1. ) 
     
    514497            CALL lbc_lnk(e_i(:,:,jk,jl), 'T', 1. ) 
    515498         END DO 
    516  
    517          a_i (:,:,jl) = tms(:,:) * a_i(:,:,jl) 
    518  
     499         ! 
     500         a_i(:,:,jl) = tms(:,:) * a_i(:,:,jl) 
    519501      END DO 
    520502 
    521503      CALL lbc_lnk( at_i , 'T', 1. ) 
    522504      at_i(:,:) = tms(:,:) * at_i(:,:)                       ! put 0 over land 
    523  
     505      ! 
    524506      CALL lbc_lnk( fsbbq  , 'T', 1. ) 
    525  
     507      ! 
    526508   END SUBROUTINE lim_istate 
     509 
    527510 
    528511   SUBROUTINE lim_istate_init 
     
    532515      !! ** Purpose : Definition of initial state of the ice  
    533516      !! 
    534       !! ** Method : Read the namiceini namelist and check the parameter  
    535       !!       values called at the first timestep (nit000) 
     517      !! ** Method :   Read the namiceini namelist and check the parameter  
     518      !!             values called at the first timestep (nit000) 
    536519      !! 
    537       !! ** input :  
    538       !!        Namelist namiceini 
    539       !! 
    540       !! history : 
    541       !!  8.5  ! 03-08 (C. Ethe) original code 
     520      !! ** input  :   namelist namiceini 
    542521      !!----------------------------------------------------------------------------- 
    543       NAMELIST/namiceini/ ttest, hninn, hginn_u, aginn_u, hginn_d, aginn_d, hnins, & 
    544          hgins_u, agins_u, hgins_d, agins_d, sinn, sins 
     522      NAMELIST/namiceini/ ttest, hninn, hginn_u, aginn_u, hginn_d, aginn_d, hnins,   & 
     523         &                hgins_u, agins_u, hgins_d, agins_d, sinn, sins 
    545524      !!----------------------------------------------------------------------------- 
    546  
    547       ! Define the initial parameters 
    548       ! ------------------------- 
    549  
    550       ! Read Namelist namiceini  
    551       REWIND ( numnam_ice ) 
     525      ! 
     526      REWIND ( numnam_ice )               ! Read Namelist namiceini  
    552527      READ   ( numnam_ice , namiceini ) 
    553       IF(lwp) THEN 
     528      ! 
     529      IF(lwp) THEN                        ! control print 
    554530         WRITE(numout,*) 
    555531         WRITE(numout,*) 'lim_istate_init : ice parameters inititialisation ' 
     
    569545         WRITE(numout,*) '   initial  ice salinity       in the south     sins       = ', sins 
    570546      ENDIF 
    571  
     547      ! 
    572548   END SUBROUTINE lim_istate_init 
    573549 
Note: See TracChangeset for help on using the changeset viewer.