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 888 for trunk/NEMO/LIM_SRC_2/limistate_2.F90 – NEMO

Ignore:
Timestamp:
2008-04-11T19:05:03+02:00 (16 years ago)
Author:
ctlod
Message:

merge dev_001_SBC branche with the trunk to include the New Surface Module package, see ticket: #113

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/LIM_SRC_2/limistate_2.F90

    r823 r888  
    44   !!              Initialisation of diagnostics ice variables 
    55   !!====================================================================== 
    6    !! History :   2.0  !  01-04  (C. Ethe, G. Madec)  Original code 
     6   !! History :   1.0  !  01-04  (C. Ethe, G. Madec)  Original code 
     7   !!             2.0  !  03-08  (G. Madec)  add lim_istate_init 
    78   !!                  !  04-04  (S. Theetten) initialization from a file 
    89   !!                  !  06-07  (S. Masson)  IOM to read the restart 
     10   !!                  !  07-10  (G. Madec)  surface module 
    911   !!-------------------------------------------------------------------- 
    1012#if defined key_lim2 
     
    1820   USE phycst 
    1921   USE ocfzpt 
    20    USE oce             ! dynamics and tracers variables      !!gm used??? 
    21    USE dom_oce                                                     !!gm used??? 
    2222   USE par_ice_2       ! ice parameters 
    2323   USE ice_oce         ! ice variables 
    2424   USE dom_ice_2 
    2525   USE lbclnk 
     26   USE oce 
    2627   USE ice_2 
    2728   USE iom 
     
    4748   !!---------------------------------------------------------------------- 
    4849   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2006)  
    49    !! $Header$  
     50   !! $ Id: $ 
    5051   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    5152   !!---------------------------------------------------------------------- 
     
    6667      REAL(wp), DIMENSION(jpi,jpj) ::   ztn   ! workspace 
    6768      !-------------------------------------------------------------------- 
    68  
    69        CALL lim_istate_init_2   !  reading the initials parameters of the ice 
    70  
    71       !-- Initialisation of sst,sss,u,v do i=1,jpi 
    72       u_io(:,:)  = 0.e0       ! ice velocity in x direction 
    73       v_io(:,:)  = 0.e0       ! ice velocity in y direction 
    74  
    75       IF( ln_limini ) THEN    !  
    76          
    77          ! Initialisation at tn if no ice or sst_ini if ice 
    78          ! Idem for salinity 
    79  
    80       !--- Criterion for presence (zidto=1.) or absence (zidto=0.) of ice 
    81          DO jj = 1 , jpj 
    82             DO ji = 1 , jpi 
    83                 
    84                zidto = MAX(zzero, - SIGN(1.,frld(ji,jj) - 1.)) 
    85                 
    86                sst_io(ji,jj) = ( nfice - 1 ) * (zidto * sst_ini(ji,jj)  + &   ! use the ocean initial values 
    87                     &          (1.0 - zidto ) * ( tn(ji,jj,1) + rt0 ))        ! tricky trick *(nfice-1) ! 
    88                sss_io(ji,jj) = ( nfice - 1 ) * (zidto * sss_ini(ji,jj) + & 
    89                     &          (1.0 - zidto ) *  sn(ji,jj,1) ) 
    90  
    91                ! to avoid the the melting of ice, several layers (mixed layer) should be 
    92                ! set to sst_ini (sss_ini) if there is ice 
    93                ! example for one layer  
    94                ! tn(ji,jj,1) = zidto * ( sst_ini(ji,jj) - rt0 )  + (1.0 - zidto ) *  tn(ji,jj,1) 
    95                ! sn(ji,jj,1) = zidto * sss_ini(ji,jj)  + (1.0 - zidto ) *  sn(ji,jj,1) 
    96                ! tb(ji,jj,1) = tn(ji,jj,1) 
    97                ! sb(ji,jj,1) = sn(ji,jj,1) 
    98             END DO 
    99          END DO 
    100           
    101           
    102          !  tfu: Melting point of sea water 
    103          tfu(:,:)  = ztf    
    104           
    105          tfu(:,:)  = ABS ( rt0 - 0.0575       * sss_ini(:,:)                               & 
    106               &                    + 1.710523e-03 * sss_ini(:,:) * SQRT( sss_ini(:,:) )    & 
    107               &                    - 2.154996e-04 * sss_ini(:,:) * sss_ini(:,:) ) 
    108       ELSE                     ! 
    109  
     69  
     70      CALL lim_istate_init_2     !  reading the initials parameters of the ice 
     71 
     72      IF( .NOT. ln_limini ) THEN   
    11073          
    11174         ! Initialisation at tn or -2 if ice 
     
    11679            END DO 
    11780         END DO 
    118           
    119          u_io  (:,:) = 0.e0 
    120          v_io  (:,:) = 0.e0 
    121          sst_io(:,:) = ( nfice - 1 ) * ( tn(:,:,1) + rt0 )   ! use the ocean initial values 
    122          sss_io(:,:) = ( nfice - 1 ) *   sn(:,:,1)           ! tricky trick *(nfice-1) ! 
    123           
    124          ! reference salinity 34psu 
     81                   
     82         !  tfu: Melting point of sea water [Kelvin] 
    12583         zs0 = 34.e0 
    126          ztf = ABS ( rt0 - 0.0575       * zs0                           & 
    127               &                    + 1.710523e-03 * zs0 * SQRT( zs0 )   & 
    128               &                    - 2.154996e-04 * zs0 *zs0          ) 
    129           
    130          !  tfu: Melting point of sea water 
    131          tfu(:,:)  = ztf    
     84         ztf = rt0 + ( - 0.0575 + 1.710523e-3 * SQRT( zs0 ) - 2.154996e-4 * zs0 ) * zs0 
     85         tfu(:,:) = ztf 
    13286          
    13387         DO jj = 1, jpj 
     
    152106         tbif  (:,:,2) = tfu(:,:) 
    153107         tbif  (:,:,3) = tfu(:,:) 
    154        
     108 
    155109      ENDIF 
     110      
    156111      fsbbq (:,:)   = 0.e0 
    157112      qstoif(:,:)   = 0.e0 
    158       u_ice (:,:)   = 0.e0 
    159       v_ice (:,:)   = 0.e0 
     113      ui_ice(:,:)   = 0.e0 
     114      vi_ice(:,:)   = 0.e0 
    160115# if defined key_coupled 
    161116      albege(:,:)   = 0.8 * tms(:,:) 
     
    191146 
    192147      CALL lbc_lnk( hsnif, 'T', 1. ) 
    193       CALL lbc_lnk( sist , 'T', 1. ) 
     148      CALL lbc_lnk( sist , 'T', 1. , pval = rt0 )      ! set rt0 on closed boundary (required by bulk formulation) 
    194149      DO jk = 1, jplayersp1 
    195150         CALL lbc_lnk(tbif(:,:,jk), 'T', 1. ) 
     
    197152      CALL lbc_lnk( fsbbq  , 'T', 1. ) 
    198153      CALL lbc_lnk( qstoif , 'T', 1. ) 
    199       CALL lbc_lnk( sss_io , 'T', 1. ) 
    200       ! 
     154 
    201155   END SUBROUTINE lim_istate_2 
    202156 
     
    209163      !! 
    210164      !! ** Method  :   Read the namiceini namelist and check the parameter  
    211       !!                values called at the first timestep (nit000) 
    212       !!                or 
    213       !!                Read 7 variables from a previous restart file 
    214       !!                sst, sst, hicif, hsnif, frld, ts & tbif 
     165      !!       values called at the first timestep (nit000) 
    215166      !! 
    216167      !! ** input   :   Namelist namiceini 
     
    222173         &                hnins, hgins, alins 
    223174      !!------------------------------------------------------------------- 
    224        
    225       ! Read Namelist namiceini  
    226       REWIND ( numnam_ice ) 
     175      ! 
     176      REWIND ( numnam_ice )               ! Read Namelist namiceini  
    227177      READ   ( numnam_ice , namiceini ) 
    228        
    229       IF(.NOT. ln_limini) THEN  
    230          IF(lwp) THEN 
    231             WRITE(numout,*) 
    232             WRITE(numout,*) 'lim_istate_init : ice parameters inititialisation ' 
    233             WRITE(numout,*) '~~~~~~~~~~~~~~~' 
    234             WRITE(numout,*) '         threshold water temp. for initial sea-ice    ttest      = ', ttest 
    235             WRITE(numout,*) '         initial snow thickness in the north          hninn      = ', hninn 
    236             WRITE(numout,*) '         initial ice thickness in the north           hginn      = ', hginn  
    237             WRITE(numout,*) '         initial leads area in the north              alinn      = ', alinn             
    238             WRITE(numout,*) '         initial snow thickness in the south          hnins      = ', hnins  
    239             WRITE(numout,*) '         initial ice thickness in the south           hgins      = ', hgins 
    240             WRITE(numout,*) '         initial leads area in the south              alins      = ', alins 
    241          ENDIF 
     178      ! 
     179      IF(lwp) THEN 
     180         WRITE(numout,*) 
     181         WRITE(numout,*) 'lim_istate_init_2 : ice parameters inititialisation ' 
     182         WRITE(numout,*) '~~~~~~~~~~~~~~~~~' 
     183         WRITE(numout,*) '         threshold water temp. for initial sea-ice    ttest      = ', ttest 
     184         WRITE(numout,*) '         initial snow thickness in the north          hninn      = ', hninn 
     185         WRITE(numout,*) '         initial ice thickness in the north           hginn      = ', hginn  
     186         WRITE(numout,*) '         initial leads area in the north              alinn      = ', alinn             
     187         WRITE(numout,*) '         initial snow thickness in the south          hnins      = ', hnins  
     188         WRITE(numout,*) '         initial ice thickness in the south           hgins      = ', hgins 
     189         WRITE(numout,*) '         initial leads area in the south              alins      = ', alins 
     190         WRITE(numout,*) '         Ice state initialization using input file    ln_limini  = ', ln_limini 
    242191      ENDIF 
    243192 
    244193      IF( ln_limini ) THEN                      ! Ice initialization using input file 
    245  
     194         ! 
    246195         CALL iom_open( 'Ice_initialization.nc', inum_ice ) 
    247  
     196         ! 
    248197         IF( inum_ice > 0 ) THEN 
    249             IF(lwp) THEN 
    250                WRITE(numout,*) ' ' 
    251                WRITE(numout,*) 'lim_istate_init : ice state initialization with : Ice_initialization.nc' 
    252                WRITE(numout,*) '~~~~~~~~~~~~~~~' 
    253                WRITE(numout,*) '         Ice state initialization using input file    ln_limini  = ', ln_limini 
    254                WRITE(numout,*) ' ' 
    255             ENDIF 
     198            IF(lwp) WRITE(numout,*) 
     199            IF(lwp) WRITE(numout,*) '                  ice state initialization with : Ice_initialization.nc' 
    256200             
    257             CALL iom_get( inum_ice, jpdom_data, 'sst'  , sst_ini(:,:) )         
    258             CALL iom_get( inum_ice, jpdom_data, 'sss'  , sss_ini(:,:) )        
    259             CALL iom_get( inum_ice, jpdom_data, 'hicif', hicif  (:,:) )       
    260             CALL iom_get( inum_ice, jpdom_data, 'hsnif', hsnif  (:,:) )       
    261             CALL iom_get( inum_ice, jpdom_data, 'frld' , frld   (:,:) )      
    262             CALL iom_get( inum_ice, jpdom_data, 'ts'   , sist   (:,:) ) 
     201            CALL iom_get( inum_ice, jpdom_data, 'hicif', hicif )       
     202            CALL iom_get( inum_ice, jpdom_data, 'hsnif', hsnif )       
     203            CALL iom_get( inum_ice, jpdom_data, 'frld' , frld  )      
     204            CALL iom_get( inum_ice, jpdom_data, 'ts'   , sist  ) 
    263205            CALL iom_get( inum_ice, jpdom_unknown, 'tbif', tbif(1:nlci,1:nlcj,:),   & 
    264206                 &        kstart = (/ mig(1),mjg(1),1 /), kcount = (/ nlci,nlcj,jplayersp1 /) ) 
     
    268210 
    269211            CALL iom_close( inum_ice) 
    270              
     212            ! 
    271213         ENDIF 
    272214      ENDIF 
    273       ! 
     215      !      
    274216   END SUBROUTINE lim_istate_init_2 
    275217 
Note: See TracChangeset for help on using the changeset viewer.