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

Changeset 88 for trunk/NEMO/LIM_SRC


Ignore:
Timestamp:
2004-04-22T15:50:27+02:00 (20 years ago)
Author:
opalod
Message:

CT : UPDATE057 : # General syntax, alignement, comments corrections

# l_ctl alone replace the set (l_ctl .AND. lwp)
# Add of diagnostics which are activated when using l_ctl logical

Location:
trunk/NEMO/LIM_SRC
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/LIM_SRC/ice.F90

    r12 r88  
    3131      resl   = 5.0e-05,  &  !: maximum value for the residual of relaxation 
    3232      cw     = 5.0e-03,  &  !: drag coefficient for oceanic stress 
    33       angvg  = 0.0    ,  &  !: turning angle for oceanic stress 
     33      angvg  = 0.e0   ,  &  !: turning angle for oceanic stress 
    3434      pstar  = 1.0e+04,  &  !: first bulk-rheology parameter 
    35       c_rhg  = 20.0   ,  &  !: second bulk-rhelogy parameter 
    36       etamn  = 0.0e+07,  &  !: minimun value for viscosity 
    37       creepl = 2.0e-08,  &  !: creep limit 
    38       ecc    = 2.0    ,  &  !: eccentricity of the elliptical yield curve 
     35      c_rhg  = 20.e0  ,  &  !: second bulk-rhelogy parameter 
     36      etamn  = 0.e+07,   &  !: minimun value for viscosity 
     37      creepl = 2.e-08,   &  !: creep limit 
     38      ecc    = 2.e0   ,  &  !: eccentricity of the elliptical yield curve 
    3939      ahi0   = 350.e0       !: sea-ice hor. eddy diffusivity coeff. (m2/s) 
    4040 
     
    9898      tio_u, tio_v       !: two components of the ice-ocean stress (N/m2) 
    9999 
    100    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,nsmax) ::   &  !: 
     100   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpsmax) ::   &  !: 
    101101      scal0              !: ??? 
    102102 
    103    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,nlayersp1) ::   &  !: 
     103   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jplayersp1) ::   &  !: 
    104104      tbif          !: Temperature inside the ice/snow layer 
    105105 
    106    REAL(wp), DIMENSION(jpi,jpj,0:kmax+1) ::    &  !: 
     106   REAL(wp), DIMENSION(jpi,jpj,0:jpkmax+1) ::    &  !: 
    107107      reslum        !: Relative absorption of solar radiation in each ocean level 
    108108 
  • trunk/NEMO/LIM_SRC/icestp.F90

    r3 r88  
    1616   USE flx_oce         ! forcings variables 
    1717   USE dom_ice 
     18   USE cpl_oce 
    1819   USE daymod 
    1920   USE phycst          ! Define parameters for the routines 
     
    7677 
    7778      IF( kt == nit000 ) THEN 
    78 # if defined key_coupled 
    79          IF(lwp) WRITE(numout,*) 
    80          IF(lwp) WRITE(numout,*) 'ice_stp : Louvain la Neuve Ice Model (LIM)' 
    81          IF(lwp) WRITE(numout,*) '~~~~~~~   coupled case' 
    82 #else 
    83          IF(lwp) WRITE(numout,*) 
    84          IF(lwp) WRITE(numout,*) 'ice_stp : Louvain la Neuve Ice Model (LIM)'  
    85          IF(lwp) WRITE(numout,*) '~~~~~~~   forced case using bulk formulea' 
    86 #endif 
     79         IF( lk_cpl ) THEN 
     80            IF(lwp) WRITE(numout,*) 
     81            IF(lwp) WRITE(numout,*) 'ice_stp : Louvain la Neuve Ice Model (LIM)' 
     82            IF(lwp) WRITE(numout,*) '~~~~~~~   coupled case' 
     83         ELSE 
     84            IF(lwp) WRITE(numout,*) 
     85            IF(lwp) WRITE(numout,*) 'ice_stp : Louvain la Neuve Ice Model (LIM)'  
     86            IF(lwp) WRITE(numout,*) '~~~~~~~   forced case using bulk formulea' 
     87         ENDIF 
    8788         !  Initialize fluxes fields 
    8889         gtaux(:,:) = 0.e0 
     
    183184          
    184185 
    185          IF( l_ctl .AND. lwp ) THEN         ! print mean trends (used for debugging) 
     186         IF( l_ctl ) THEN         ! print mean trends (used for debugging) 
    186187            WRITE(numout,*) 'Ice Forcings ' 
    187188            WRITE(numout,*) ' qsr_oce  : ', SUM( qsr_oce (:,:) ), ' qsr_ice  : ', SUM( qsr_ice (:,:) ) 
     
    202203         CALL lim_dyn                                                ! Ice dynamics !   ( rheology/dynamics ) 
    203204         !                                                           !--------------! 
    204          IF( l_ctl .AND. lwp ) THEN 
     205         IF( l_ctl ) THEN 
    205206            WRITE(numout,*) ' hsnif  2 : ', SUM( hsnif  (:,:) ), ' hicnif   : ', SUM( hicif  (:,:) ) 
    206207            WRITE(numout,*) ' frld   2 : ', SUM( frld   (:,:) ), ' sist     : ', SUM( sist   (:,:) ) 
     
    211212         CALL lim_trp                                                ! Ice transport !  ( Advection/diffusion ) 
    212213         !                                                           !---------------! 
    213          IF( l_ctl .AND. lwp ) THEN 
     214         IF( l_ctl ) THEN 
    214215            WRITE(numout,*) ' hsnif  3 : ', SUM( hsnif  (:,:) ), ' hicnif   : ', SUM( hicif  (:,:) ) 
    215216            WRITE(numout,*) ' frld   3 : ', SUM( frld   (:,:) ), ' sist     : ', SUM( sist   (:,:) ) 
     
    220221         CALL lim_thd                                                ! Ice thermodynamics ! 
    221222         !                                                           !--------------------! 
    222          IF( l_ctl .AND. lwp ) THEN 
     223         IF( l_ctl ) THEN 
    223224            WRITE(numout,*) ' hsnif  4 : ', SUM( hsnif  (:,:) ), ' hicnif   : ', SUM( hicif  (:,:) ) 
    224225            WRITE(numout,*) ' frld   4 : ', SUM( frld   (:,:) ), ' sist     : ', SUM( sist   (:,:) ) 
     
    270271#else 
    271272   !!---------------------------------------------------------------------- 
    272    !!   Default option                                 NO LIM sea-ice model 
    273    !!---------------------------------------------------------------------- 
    274    USE in_out_manager 
    275  
     273   !!   Default option           Dummy module          NO LIM sea-ice model 
     274   !!---------------------------------------------------------------------- 
    276275CONTAINS 
    277  
    278    SUBROUTINE ice_stp ( kt )            ! Empty routine 
    279       INTEGER, INTENT( in ) ::   kt     ! ocean time-step index 
    280  
    281       IF( kt == nit000 ) THEN 
    282          IF(lwp) WRITE(numout,*) 
    283          IF(lwp) WRITE(numout,*) 'No Sea Ice Model' 
    284          IF(lwp) WRITE(numout,*) '~~~~~~~' 
    285       ENDIF 
    286  
     276   SUBROUTINE ice_stp ( kt )     ! Dummy routine 
     277      WRITE(*,*) 'ice_stp: You should not have seen this print! error?', kt 
    287278   END SUBROUTINE ice_stp 
    288  
    289279#endif 
    290280 
  • trunk/NEMO/LIM_SRC/limadv.F90

    r3 r88  
    11MODULE limadv  
    2 #if defined key_ice_lim 
    32   !!====================================================================== 
    43   !!                       ***  MODULE limadv   *** 
    54   !! LIM sea-ice model : sea-ice advection 
    65   !!====================================================================== 
    7  
     6#if defined key_ice_lim 
     7   !!---------------------------------------------------------------------- 
     8   !!   'key_ice_lim'                                     LIM sea-ice model 
    89   !!---------------------------------------------------------------------- 
    910   !!   lim_adv_x  : advection of sea ice on x axis 
     
    221222      CALL lbc_lnk( psxy, 'T', 1. ) 
    222223 
    223       IF( l_ctl .AND. lwp ) THEN 
     224      IF(l_ctl) THEN 
    224225         WRITE(numout,*) ' lim_adv_x: psm  ', SUM( psm  ), ' ps0  ', SUM( ps0  ) 
    225226         WRITE(numout,*) ' lim_adv_x: psx  ', SUM( psx  ), ' psxx ', SUM( psxx ) 
     
    421422      CALL lbc_lnk( psxy, 'T', 1. ) 
    422423 
    423       IF( l_ctl .AND. lwp ) THEN 
     424      IF(l_ctl) THEN 
    424425         WRITE(numout,*) ' lim_adv_y: psm  ', SUM( psm  ), ' ps0  ', SUM( ps0  ) 
    425426         WRITE(numout,*) ' lim_adv_y: psx  ', SUM( psx  ), ' psxx ', SUM( psxx ) 
     
    430431   END SUBROUTINE lim_adv_y 
    431432 
    432    !!====================================================================== 
    433433#else 
    434    !!============================================================================== 
    435    !!                       ***  MODULE limadv   *** 
    436    !!                              No sea ice 
    437    !!============================================================================== 
     434   !!---------------------------------------------------------------------- 
     435   !!   Default option            Dummy module         NO LIM sea-ice model 
     436   !!---------------------------------------------------------------------- 
    438437CONTAINS 
    439438   SUBROUTINE lim_adv_x         ! Empty routine 
  • trunk/NEMO/LIM_SRC/limflx.F90

    r33 r88  
    99   !!---------------------------------------------------------------------- 
    1010   !!   lim_flx  : flux at the ice / ocean interface 
     11   !!---------------------------------------------------------------------- 
    1112   !! * Modules used 
    1213   USE par_oce 
     
    2627   PUBLIC lim_flx       ! called by lim_step 
    2728 
    28   !! * Module variables 
    29      REAL(wp)  ::            &  ! constant values 
    30          epsi16 = 1e-16   ,  & 
    31          rzero  = 0.0    ,  & 
    32          rone   = 1.0 
     29   !! * Module variables 
     30   REAL(wp)  ::            &  ! constant values 
     31      epsi16 = 1.e-16  ,  & 
     32      rzero  = 0.e0    ,  & 
     33      rone   = 1.e0 
     34 
    3335   !! * Substitutions 
    3436#  include "vectopt_loop_substitute.h90" 
     
    4143      !!------------------------------------------------------------------- 
    4244      !!                ***  ROUTINE lim_flx *** 
    43       !!                 
    4445      !!   
    4546      !! ** Purpose : Computes the mass and heat fluxes to the ocean 
     
    5354      !!              - fmass   : freshwater flux at sea ice/ocean interface 
    5455      !! 
    55       !! 
    5656      !! ** References : 
    5757      !!       H. Goosse et al. 1996, Bul. Soc. Roy. Sc. Liege, 65, 87-90 
     
    5959      !!         addition    : 02-07 (C. Ethe, G. Madec) 
    6060      !!--------------------------------------------------------------------- 
    61       !! * Modules used 
    6261      !! * Local variables 
    6362      INTEGER ::   ji, jj         ! dummy loop indices 
     
    174173      !-----------------------------------------------! 
    175174 
    176       DO jj = 1, jpj 
    177          DO ji = 1, jpi 
    178             ftaux (ji,jj) = - tio_u(ji,jj) * rau0   ! taux ( ice: N/m2/rau0, ocean: N/m2 ) 
    179             ftauy (ji,jj) = - tio_v(ji,jj) * rau0   ! tauy ( ice: N/m2/rau0, ocean: N/m2 )                 
    180             freeze(ji,jj) = 1.0 - frld(ji,jj)       ! Sea ice cover             
    181             tn_ice(ji,jj) = sist(ji,jj)             ! Ice surface temperature                       
    182          END DO 
    183       END DO 
     175      ftaux (:,:) = - tio_u(:,:) * rau0   ! taux ( ice: N/m2/rau0, ocean: N/m2 ) 
     176      ftauy (:,:) = - tio_v(:,:) * rau0   ! tauy ( ice: N/m2/rau0, ocean: N/m2 )                 
     177      freeze(:,:) = 1.0 - frld(:,:)       ! Sea ice cover             
     178      tn_ice(:,:) = sist(:,:)             ! Ice surface temperature                       
    184179 
    185180#if defined key_coupled             
     
    194189      CALL flx_blk_albedo( zalb, zalcn, zalbp, zaldum ) 
    195190 
    196       DO jj = 1, jpj 
    197          DO ji = 1, jpi 
    198             alb_ice(ji,jj) =  0.5 * zalbp(ji,jj) + 0.5 * zalb (ji,jj)  ! Ice albedo                        
    199          END DO 
    200       END DO 
    201 #endif 
    202  
    203       IF( l_ctl .AND. lwp ) THEN 
     191      alb_ice(:,:) =  0.5 * zalbp(:,:) + 0.5 * zalb (:,:)   ! Ice albedo                        
     192#endif 
     193 
     194      IF(l_ctl) THEN 
    204195         WRITE(numout,*) ' lim_flx  ' 
    205196         WRITE(numout,*) ' fsolar ', SUM(fsolar), ' fnsolar', SUM( fnsolar ) 
     
    208199         WRITE(numout,*) ' freeze ', SUM(freeze), ' tn_ice ', SUM(tn_ice) 
    209200      ENDIF  
    210   
    211201    
    212202    END SUBROUTINE lim_flx 
     
    214204#else 
    215205   !!---------------------------------------------------------------------- 
    216    !!   Default option :        Empty module           NO LIM sea-ice model 
     206   !!   Default option :        Dummy module           NO LIM sea-ice model 
    217207   !!---------------------------------------------------------------------- 
    218208CONTAINS 
    219    SUBROUTINE lim_flx         ! Empty routine 
     209   SUBROUTINE lim_flx         ! Dummy routine 
    220210   END SUBROUTINE lim_flx 
    221211#endif  
    222212 
     213   !!====================================================================== 
    223214END MODULE limflx 
  • trunk/NEMO/LIM_SRC/limhdf.F90

    r12 r88  
    11MODULE limhdf 
    2 #if defined key_ice_lim 
    32   !!====================================================================== 
    43   !!                    ***  MODULE limhdf   *** 
    5    !! LIM diffusion ice model : sea-ice variables horizontal diffusion 
     4   !! LIM ice model : horizontal diffusion of sea-ice quantities 
    65   !!====================================================================== 
    7  
     6#if defined key_ice_lim 
     7   !!---------------------------------------------------------------------- 
     8   !!   'key_ice_lim'                                     LIM sea-ice model 
    89   !!---------------------------------------------------------------------- 
    910   !!   lim_hdf  : diffusion trend on sea-ice variable 
     
    9697            DO ji = fs_2 , fs_jpim1   ! vector opt. 
    9798               zfact(ji,jj) = ( e2u(ji,jj) + e2u(ji-1,jj  ) + e1v(ji,jj) + e1v(ji,jj-1) ) & 
    98                              / ( e1t(ji,jj) * e2t(ji,jj) ) 
     99                  &          / ( e1t(ji,jj) * e2t(ji,jj) ) 
    99100            END DO 
    100101         END DO 
     
    144145 
    145146         ! convergence test 
    146          zconv = 0.0 
     147         zconv = 0.e0 
    147148         DO jj = 2, jpjm1 
    148149            DO ji = 2, jpim1 
     
    165166 
    166167      ptab(:,:) = ptab(:,:) 
    167       IF( l_ctl .AND. lwp ) THEN 
    168          WRITE(numout,*) ' lim_hdf  : ', SUM( ptab-ptab0 ), ' zconv= ', zconv, ' iter= ', iter 
    169       ENDIF 
     168 
     169      IF(l_ctl)   WRITE(numout,*) ' lim_hdf  : ', SUM( ptab-ptab0 ), ' zconv= ', zconv, ' iter= ', iter 
    170170 
    171171   END SUBROUTINE lim_hdf 
     172 
    172173#else 
    173    !!====================================================================== 
    174    !!                       ***  MODULE limhdf   *** 
    175    !!                          no sea ice model 
    176    !!====================================================================== 
     174   !!---------------------------------------------------------------------- 
     175   !!   Default option          Dummy module           NO LIM sea-ice model 
     176   !!---------------------------------------------------------------------- 
    177177CONTAINS 
    178178   SUBROUTINE lim_hdf         ! Empty routine 
  • trunk/NEMO/LIM_SRC/limrst.F90

    r3 r88  
    8484      zinfo(2) = FLOAT( it0   )   ! iteration number 
    8585 
    86       zsec     = 0. 
     86      zsec     = 0.e0 
    8787      itime    = 0 
    88       zdept(1) = 0. 
     88      zdept(1) = 0.e0 
    8989      zdt      = rdt_ice * nstock 
    9090 
  • trunk/NEMO/LIM_SRC/limthd_lac.F90

    r12 r88  
    2222   PUBLIC lim_thd_lac     ! called by lim_thd 
    2323 
    24   !! * Module variables 
    25      REAL(wp)  ::            &  ! constant values 
    26          epsi20 = 1e-20   ,  & 
    27          epsi13 = 1e-13   ,  & 
    28          zzero  = 0.0     ,  & 
    29          zone   = 1.0 
     24   !! * Module variables 
     25   REAL(wp)  ::            &  ! constant values 
     26      epsi20 = 1.e-20  ,  & 
     27      epsi13 = 1.e-13  ,  & 
     28      zzero  = 0.e0    ,  & 
     29      zone   = 1.e0 
    3030   !!---------------------------------------------------------------------- 
    3131   !!   LIM 2.0 , UCL-LODYC-IPSL  (2003) 
     
    3333CONTAINS 
    3434     
    35     SUBROUTINE lim_thd_lac( kideb, kiut ) 
     35   SUBROUTINE lim_thd_lac( kideb, kiut ) 
    3636      !!------------------------------------------------------------------- 
    3737      !!               ***   ROUTINE lim_thd_lac  *** 
     
    6363      !!      Fichefet T. and M. Maqueda 1997, J. Geo. Res., 102(C6),  
    6464      !!                                                12609 -12646    
    65       !! 
    6665      !! History : 
    6766      !!   1.0  !  01-04 (LIM)  original code 
  • trunk/NEMO/LIM_SRC/limthd_zdf.F90

    r12 r88  
    11MODULE limthd_zdf 
    2 #if defined key_ice_lim 
    32   !!====================================================================== 
    43   !!                       ***  MODULE limthd_zdf *** 
    54   !!                thermodynamic growth and decay of the ice  
    65   !!====================================================================== 
    7  
     6#if defined key_ice_lim 
     7   !!---------------------------------------------------------------------- 
     8   !!   'key_ice_lim'                                     LIM sea-ice model 
    89   !!---------------------------------------------------------------------- 
    910   !!   lim_thd_zdf  : vertical accr./abl. and lateral ablation of sea ice 
     11   !!---------------------------------------------------------------------- 
    1012   !! * Modules used 
    1113   USE par_oce          ! ocean parameters 
     
    2527   !! * Module variables 
    2628   REAL(wp)  ::           &  ! constant values 
    27       epsi20 = 1e-20   ,  & 
    28       epsi13 = 1e-13   ,  & 
    29       zzero  = 0.0     ,  & 
    30       zone   = 1.0 
     29      epsi20 = 1.e-20  ,  & 
     30      epsi13 = 1.e-13  ,  & 
     31      zzero  = 0.e0    ,  & 
     32      zone   = 1.e0 
    3133   !!---------------------------------------------------------------------- 
    3234   !!   LIM 2.0 , UCL-LODYC-IPSL  (2003) 
     
    3537 
    3638   SUBROUTINE lim_thd_zdf( kideb , kiut ) 
    37        !!------------------------------------------------------------------ 
    38        !!                ***  ROUTINE lim_thd_zdf  *** 
    39        !!               
    40        !! ** Purpose : This routine determines the time evolution of snow  
    41        !!      and sea-ice thicknesses, concentration and heat content  
    42        !!      due to the vertical and lateral thermodynamic accretion- 
    43        !!      ablation processes. One only treats the case of lat. abl. 
    44        !!      For lateral accretion, see routine lim_lat_accr  
    45        !!  
    46        !! ** Method  : The representation of vertical growth and decay of  
    47        !!      the sea-ice model is based upon the diffusion of heat  
    48        !!      through the external and internal boundaries of a  
    49        !!      three-layer system (two layers of ice and one layer and  
    50        !!      one layer of snow, if present, on top of the ice). 
    51        !!  
    52        !! ** Action  : - Calculation of some intermediates variables 
    53        !!              - Calculation of surface temperature 
    54        !!              - Calculation of available heat for surface ablation 
    55        !!              - Calculation of the changes in internal temperature  
    56        !!                of the three-layer system, due to vertical diffusion  
    57        !!                processes 
    58        !!              - Performs surface ablation and bottom accretion-ablation 
    59        !!              - Performs snow-ice formation 
    60        !!              - Performs lateral ablation 
    61        !! 
    62        !! References : 
    63        !!   Fichefet T. and M. Maqueda 1997, J. Geophys. Res., 102(C6), 12609-12646    
    64        !!   Fichefet T. and M. Maqueda 1999, Clim. Dyn, 15(4), 251-268   
    65        !! 
    66        !! History : 
    67        !!   original    : 01-04 (LIM) 
    68        !!   addition    : 02-08 (C. Ethe, G. Madec) 
    69        !!------------------------------------------------------------------ 
    70        !! * Arguments 
    71        INTEGER , INTENT (in) ::  & 
    72           kideb ,  &  ! Start point on which the  the computation is applied 
    73           kiut        ! End point on which the  the computation is applied 
    74  
    75        !! * Local variables 
    76        INTEGER ::   ji       ! dummy loop indices 
    77  
    78        REAL(wp) , DIMENSION(jpij,2) ::  & 
    79           zqcmlt        ! energy due to surface( /1 ) and bottom melting( /2 ) 
    80  
    81        REAL(wp), DIMENSION(jpij) ::  & 
    82           ztsmlt      &    ! snow/ice surface melting temperature 
    83           ,ztbif      &    ! int. temp. at the mid-point of the 1st layer of the snow/ice sys.  
    84           ,zksn       &    ! effective conductivity of snow 
    85           ,zkic       &    ! effective conductivity of ice 
    86           ,zksndh     &    ! thermal cond. at the mid-point of the 1st layer of the snow/ice sys.  
    87           , zfcsu     &    ! conductive heat flux at the surface of the snow/ice system  
    88           , zfcsudt   &    ! = zfcsu * dt 
    89           , zi0       &    ! frac. of the net SW rad. which is not absorbed at the surface 
    90           , z1mi0     &    ! fraction of the net SW radiation absorbed at the surface 
    91           , zqmax     &    ! maximum energy stored in brine pockets 
    92           , zrcpdt    &    ! h_su*rho_su*cp_su/dt(h_su being the thick. of surf. layer) 
    93           , zts_old   &    ! previous surface temperature 
    94           , zidsn , z1midsn , zidsnic ! tempory variables 
    95  
    96        REAL(wp), DIMENSION(jpij) :: & 
     39      !!------------------------------------------------------------------ 
     40      !!                ***  ROUTINE lim_thd_zdf  *** 
     41      !!               
     42      !! ** Purpose : This routine determines the time evolution of snow  
     43      !!      and sea-ice thicknesses, concentration and heat content  
     44      !!      due to the vertical and lateral thermodynamic accretion- 
     45      !!      ablation processes. One only treats the case of lat. abl. 
     46      !!      For lateral accretion, see routine lim_lat_accr  
     47      !!  
     48      !! ** Method  : The representation of vertical growth and decay of  
     49      !!      the sea-ice model is based upon the diffusion of heat  
     50      !!      through the external and internal boundaries of a  
     51      !!      three-layer system (two layers of ice and one layer and  
     52      !!      one layer of snow, if present, on top of the ice). 
     53      !!  
     54      !! ** Action  : - Calculation of some intermediates variables 
     55      !!              - Calculation of surface temperature 
     56      !!              - Calculation of available heat for surface ablation 
     57      !!              - Calculation of the changes in internal temperature  
     58      !!                of the three-layer system, due to vertical diffusion  
     59      !!                processes 
     60      !!              - Performs surface ablation and bottom accretion-ablation 
     61      !!              - Performs snow-ice formation 
     62      !!              - Performs lateral ablation 
     63      !! 
     64      !! References : 
     65      !!   Fichefet T. and M. Maqueda 1997, J. Geophys. Res., 102(C6), 12609-12646    
     66      !!   Fichefet T. and M. Maqueda 1999, Clim. Dyn, 15(4), 251-268   
     67      !! 
     68      !! History : 
     69      !!   original    : 01-04 (LIM) 
     70      !!   addition    : 02-08 (C. Ethe, G. Madec) 
     71      !!------------------------------------------------------------------ 
     72      !! * Arguments 
     73      INTEGER , INTENT (in) ::  & 
     74         kideb ,  &  ! Start point on which the  the computation is applied 
     75         kiut        ! End point on which the  the computation is applied 
     76 
     77      !! * Local variables 
     78      INTEGER ::   ji       ! dummy loop indices 
     79 
     80      REAL(wp) , DIMENSION(jpij,2) ::  & 
     81         zqcmlt        ! energy due to surface( /1 ) and bottom melting( /2 ) 
     82 
     83      REAL(wp), DIMENSION(jpij) ::  & 
     84         ztsmlt      &    ! snow/ice surface melting temperature 
     85         ,ztbif      &    ! int. temp. at the mid-point of the 1st layer of the snow/ice sys.  
     86         ,zksn       &    ! effective conductivity of snow 
     87         ,zkic       &    ! effective conductivity of ice 
     88         ,zksndh     &    ! thermal cond. at the mid-point of the 1st layer of the snow/ice sys.  
     89         , zfcsu     &    ! conductive heat flux at the surface of the snow/ice system  
     90         , zfcsudt   &    ! = zfcsu * dt 
     91         , zi0       &    ! frac. of the net SW rad. which is not absorbed at the surface 
     92         , z1mi0     &    ! fraction of the net SW radiation absorbed at the surface 
     93         , zqmax     &    ! maximum energy stored in brine pockets 
     94         , zrcpdt    &    ! h_su*rho_su*cp_su/dt(h_su being the thick. of surf. layer) 
     95         , zts_old   &    ! previous surface temperature 
     96         , zidsn , z1midsn , zidsnic ! tempory variables 
     97 
     98      REAL(wp), DIMENSION(jpij) :: & 
    9799          zfnet       &  ! net heat flux at the top surface( incl. conductive heat flux) 
    98100          , zsprecip  &    ! snow accumulation 
     
    420422          zplediag(3) = 1 + 3.0 * sbeta * zkhic    
    421423 
    422           zsubdiag(1) = 0.0               
    423           zsubdiag(2) = -1.0 * z1midsn(ji) * sbeta * zkhicint 
    424           zsubdiag(3) = -1.0 * sbeta * zkhic  
    425  
    426           zsupdiag(1) =  -1.0 * z1midsn(ji) * sbeta * zkhsnint  
     424          zsubdiag(1) =  0.e0               
     425          zsubdiag(2) = -1.e0 * z1midsn(ji) * sbeta * zkhicint 
     426          zsubdiag(3) = -1.e0 * sbeta * zkhic  
     427 
     428          zsupdiag(1) = -1.e0 * z1midsn(ji) * sbeta * zkhsnint  
    427429          zsupdiag(2) = zsubdiag(3) 
    428           zsupdiag(3) = 0.0 
     430          zsupdiag(3) =  0.e0 
    429431           
    430432          !     6.3. Fulfill the idependent term vector. 
  • trunk/NEMO/LIM_SRC/limwri.F90

    r3 r88  
    3232 
    3333   !! * Module variables 
     34   INTEGER, PARAMETER ::   &  !: 
     35      jpnoumax = 40             !: maximum number of variable for ice output 
    3436   INTEGER  ::                                & 
    3537      noumef                                     ! number of fields 
    36    REAL(wp)           , DIMENSION(noumax) ::  & 
     38   REAL(wp)           , DIMENSION(jpnoumax) ::  & 
    3739      cmulti ,                                &  ! multiplicative constant 
    3840      cadd                                       ! additive constant 
    39    CHARACTER(len = 35), DIMENSION(noumax) ::  & 
     41   CHARACTER(len = 35), DIMENSION(jpnoumax) ::  & 
    4042      titn                                       ! title of the field 
    41    CHARACTER(len = 8 ), DIMENSION(noumax) ::  & 
     43   CHARACTER(len = 8 ), DIMENSION(jpnoumax) ::  & 
    4244      nam                                        ! name of the field 
    43    CHARACTER(len = 8 ), DIMENSION(noumax) ::  & 
     45   CHARACTER(len = 8 ), DIMENSION(jpnoumax) ::  & 
    4446      uni                                        ! unit of the field 
    45    INTEGER            , DIMENSION(noumax) ::  & 
     47   INTEGER            , DIMENSION(jpnoumax) ::  & 
    4648      nc                                         ! switch for saving field ( = 1 ) or not ( = 0 ) 
    4749 
    4850   REAL(wp)  ::            &  ! constant values 
    49       epsi16 = 1e-16   ,  & 
    50       zzero  = 0.0     ,  & 
    51       zone   = 1.0 
     51      epsi16 = 1.e-16   ,  & 
     52      zzero  = 0.e0     ,  & 
     53      zone   = 1.e0 
     54   !!------------------------------------------------------------------- 
    5255 
    5356CONTAINS 
     
    7073         zindh,zinda,zindb,  & 
    7174         ztmu 
    72       REAL(wp), DIMENSION(jpi,jpj,noumax) :: & 
     75      REAL(wp), DIMENSION(jpi,jpj,jpnoumax) :: & 
    7376         zcmo 
    7477      REAL(wp), DIMENSION(jpi,jpj) ::  & 
     
    8487         ndex51   
    8588      !!------------------------------------------------------------------- 
    86   
    87  
    8889       
    8990      IF ( numit == nstart ) THEN  
     
    111112         CALL wheneq  ( jpij , tmask(:,:,1), 1, 1., ndex51, ndim) 
    112113          
    113          DO jf = 1 , noumef 
     114         DO jf = 1, noumef 
    114115            IF ( nc(jf) == 1 ) THEN 
    115                CALL histdef( nice, nam(jf), titn(jf), uni(jf), jpi, jpj & 
     116               CALL histdef( nice, nam(jf), titn(jf), uni(jf), jpi, jpj   & 
    116117                  , nhorid, 1, 1, 1, -99, 32, clop, zsto, zout ) 
    117118            ENDIF 
     
    133134      !-- calculs des valeurs instantanees 
    134135       
    135       zcmo( 1:jpi, 1:jpj, 1:noumax ) = 0.0  
     136      zcmo(:,:, 1:jpnoumax ) = 0.e0  
    136137      DO jj = 2 , jpjm1 
    137138         DO ji = 2 , jpim1 
     
    229230         field_19 
    230231 
    231       TYPE(FIELD) , DIMENSION(noumax) :: zfield 
     232      TYPE(FIELD) , DIMENSION(jpnoumax) :: zfield 
    232233 
    233234      NAMELIST/namiceout/ noumef, & 
  • trunk/NEMO/LIM_SRC/par_ice.F90

    r12 r88  
    77   USE par_oce 
    88 
    9    INTEGER, PARAMETER ::   &  !: 
    10       kmax =   1    ,      &  !: ??? 
    11       nsmax =  2              !: ??? 
     9   IMPLICIT NONE 
     10   PUBLIC               ! allows par_oce and par_kind to be known in ice modules 
    1211 
    13    !!-- Parameter providing the number of vertical ice layers 
    14     
    15    INTEGER , PARAMETER ::      &  !: 
    16       nlayers   = 2 ,          &  !: ??? 
    17       nlayersp1 = nlayers + 1     !: ??? 
     12   INTEGER, PUBLIC, PARAMETER ::   &  !: 
     13      jpkmax =  1    ,      &  !: ??? 
     14      jpsmax =  2              !: ??? 
    1815 
    19    ! maximum number of variable for output 
    20    INTEGER, PARAMETER ::   &  !: 
    21       noumax = 40             !: ??? 
    22  
    23    ! Parameters for outputs to files "evolu" made by routine "informe" : ??? 
    24    INTEGER, PARAMETER ::       &  !: 
    25       ninfmx = 100        ,    &  !: maximum number of key variables 
    26       nchinf = 5          ,    &  !: ??? 
    27       nchsep = nchinf + 2         !: ??? 
     16   INTEGER, PUBLIC, PARAMETER ::   &  !:  
     17      jplayers   = 2 ,           &  !: number of vertical ice layers 
     18      jplayersp1 = jplayers + 1     !: ??? 
    2819 
    2920   !!====================================================================== 
  • trunk/NEMO/LIM_SRC/thd_ice.F90

    r12 r88  
    7676      dqla_ice_1d          !:    "                  "      dqla_ice 
    7777 
    78    REAL(wp), PUBLIC, DIMENSION(jpij,nlayersp1) ::   &  !: 
     78   REAL(wp), PUBLIC, DIMENSION(jpij,jplayersp1) ::   &  !: 
    7979      tbif_1d              !: corresponding to the 2D var  tbif 
    8080 
Note: See TracChangeset for help on using the changeset viewer.