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 8534 for branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icevar.F90 – NEMO

Ignore:
Timestamp:
2017-09-18T16:54:04+02:00 (7 years ago)
Author:
clem
Message:

changes in style - part6 - pure cosmetics

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icevar.F90

    r8522 r8534  
    22   !!====================================================================== 
    33   !!                       ***  MODULE icevar *** 
    4    !!                 Different sets of ice model variables  
     4   !!   sea-ice:     Different sets of ice model variables  
    55   !!                   how to switch from one to another 
    66   !! 
     
    3636#if defined key_lim3 
    3737   !!---------------------------------------------------------------------- 
    38    !!   'key_lim3'                                      LIM3 sea-ice model 
     38   !!   'key_lim3'                                       ESIM sea-ice model 
    3939   !!---------------------------------------------------------------------- 
    4040   !!   ice_var_agg       : integrate variables over layers and categories 
     
    4747   !!   ice_var_itd       : convert 1-cat to multiple cat 
    4848   !!---------------------------------------------------------------------- 
    49    USE par_oce        ! ocean parameters 
     49   USE dom_oce        ! ocean space and time domain 
    5050   USE phycst         ! physical constants (ocean directory)  
    5151   USE sbc_oce , ONLY : sss_m 
    52    USE ice            ! ice variables 
    53    USE ice1D          ! ice variables (thermodynamics) 
     52   USE ice            ! sea-ice: variables 
     53   USE ice1D          ! sea-ice: thermodynamics variables 
    5454   ! 
    5555   USE in_out_manager ! I/O manager 
    5656   USE lib_mpp        ! MPP library 
    57    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     57   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
    5858 
    5959   IMPLICIT NONE 
     
    7777 
    7878   SUBROUTINE ice_var_agg( kn ) 
    79       !!------------------------------------------------------------------ 
     79      !!------------------------------------------------------------------- 
    8080      !!                ***  ROUTINE ice_var_agg  *** 
    8181      !! 
    8282      !! ** Purpose :   aggregates ice-thickness-category variables to  
    8383      !!              all-ice variables, i.e. it turns VGLO into VAGG 
    84       !!------------------------------------------------------------------ 
     84      !!------------------------------------------------------------------- 
    8585      INTEGER, INTENT( in ) ::   kn     ! =1 state variables only 
    8686      !                                 ! >1 state variables + others 
     
    8888      INTEGER ::   ji, jj, jk, jl   ! dummy loop indices 
    8989      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   z1_at_i, z1_vt_i 
    90       !!------------------------------------------------------------------ 
     90      !!------------------------------------------------------------------- 
    9191      ! 
    9292      !                                      ! integrated values 
     
    143143 
    144144   SUBROUTINE ice_var_glo2eqv 
    145       !!------------------------------------------------------------------ 
     145      !!------------------------------------------------------------------- 
    146146      !!                ***  ROUTINE ice_var_glo2eqv *** 
    147147      !! 
    148148      !! ** Purpose :   computes equivalent variables as function of   
    149149      !!              global variables, i.e. it turns VGLO into VEQV 
    150       !!------------------------------------------------------------------ 
     150      !!------------------------------------------------------------------- 
    151151      INTEGER  ::   ji, jj, jk, jl   ! dummy loop indices 
    152152      REAL(wp) ::   ze_i             ! local scalars 
     
    155155      REAL(wp) ::   zlay_i, zlay_s                  !   -      - 
    156156      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z1_a_i, z1_v_i 
    157       !!------------------------------------------------------------------ 
     157      !!------------------------------------------------------------------- 
    158158 
    159159!!gm Question 2:  It is possible to define existence of sea-ice in a common way between  
     
    242242 
    243243   SUBROUTINE ice_var_eqv2glo 
    244       !!------------------------------------------------------------------ 
     244      !!------------------------------------------------------------------- 
    245245      !!                ***  ROUTINE ice_var_eqv2glo *** 
    246246      !! 
    247247      !! ** Purpose :   computes global variables as function of  
    248248      !!              equivalent variables,  i.e. it turns VEQV into VGLO 
    249       !!------------------------------------------------------------------ 
     249      !!------------------------------------------------------------------- 
    250250      ! 
    251251      v_i  (:,:,:) = ht_i(:,:,:) * a_i(:,:,:) 
     
    257257 
    258258   SUBROUTINE ice_var_salprof 
    259       !!------------------------------------------------------------------ 
     259      !!------------------------------------------------------------------- 
    260260      !!                ***  ROUTINE ice_var_salprof *** 
    261261      !! 
     
    270270      !! 
    271271      !! ** References : Vancoppenolle et al., 2007 
    272       !!------------------------------------------------------------------ 
     272      !!------------------------------------------------------------------- 
    273273      INTEGER  ::   ji, jj, jk, jl   ! dummy loop index 
    274274      REAL(wp) ::   zsal, z1_dS 
     
    277277      REAL(wp), PARAMETER :: zsi0 = 3.5_wp 
    278278      REAL(wp), PARAMETER :: zsi1 = 4.5_wp 
    279       !!------------------------------------------------------------------ 
     279      !!------------------------------------------------------------------- 
    280280 
    281281!!gm Question: Remove the option 3 ?  How many years since it last use ?  
     
    355355 
    356356   SUBROUTINE ice_var_bv 
    357       !!------------------------------------------------------------------ 
     357      !!------------------------------------------------------------------- 
    358358      !!                ***  ROUTINE ice_var_bv *** 
    359359      !! 
     
    363363      !! 
    364364      !! References : Vancoppenolle et al., JGR, 2007 
    365       !!------------------------------------------------------------------ 
     365      !!------------------------------------------------------------------- 
    366366      INTEGER  ::   ji, jj, jk, jl   ! dummy loop indices 
    367       !!------------------------------------------------------------------ 
     367      !!------------------------------------------------------------------- 
    368368      ! 
    369369!!gm I prefere to use WHERE / ELSEWHERE  to set it to zero only where needed   <<<=== to be done 
     
    398398      REAL(wp), PARAMETER :: zsi0 = 3.5_wp 
    399399      REAL(wp), PARAMETER :: zsi1 = 4.5_wp 
    400       !!--------------------------------------------------------------------- 
     400      !!------------------------------------------------------------------- 
    401401      ! 
    402402      SELECT CASE ( nn_icesal ) 
     
    543543 
    544544   SUBROUTINE ice_var_itd( zhti, zhts, zai, zht_i, zht_s, za_i ) 
    545       !!------------------------------------------------------------------ 
     545      !!------------------------------------------------------------------- 
    546546      !!                ***  ROUTINE ice_var_itd   *** 
    547547      !! 
     
    579579      INTEGER , DIMENSION(4)                  ::   itest 
    580580      !!------------------------------------------------------------------- 
    581  
    582       !-------------------------------------------------------------------- 
    583       ! initialisation of variables 
    584       !-------------------------------------------------------------------- 
     581      ! 
     582      ! ---------------------------------------- 
     583      ! distribution over the jpl ice categories 
     584      ! ---------------------------------------- 
     585      ! a gaussian distribution for ice concentration is used 
     586      ! then we check whether the distribution fullfills 
     587      ! volume and area conservation, positivity and ice categories bounds 
    585588      ijpij = SIZE( zhti , 1 ) 
    586589      zht_i(1:ijpij,1:jpl) = 0._wp 
     
    588591      za_i (1:ijpij,1:jpl) = 0._wp 
    589592 
    590       ! ---------------------------------------- 
    591       ! distribution over the jpl ice categories 
    592       ! ---------------------------------------- 
    593593      DO ji = 1, ijpij 
    594594          
     
    604604            END DO 
    605605 
    606             ! initialisation of tests 
    607             itest(:)  = 0 
    608           
    609             i_fill = jpl + 1                                             !==================================== 
    610             DO WHILE ( ( SUM( itest(:) ) /= 4 ) .AND. ( i_fill >= 2 ) )  ! iterative loop on i_fill categories 
    611                ! iteration                                               !==================================== 
     606            itest(:) = 0 
     607            i_fill   = jpl + 1                                            !------------------------------------ 
     608            DO WHILE ( ( SUM( itest(:) ) /= 4 ) .AND. ( i_fill >= 2 ) )   ! iterative loop on i_fill categories 
     609               !                                                          !------------------------------------ 
    612610               i_fill = i_fill - 1 
    613                 
    614                ! initialisation of ice variables for each try 
     611               ! 
    615612               zht_i(ji,1:jpl) = 0._wp 
    616613               za_i (ji,1:jpl) = 0._wp 
    617614               itest(:)        = 0       
    618615                
    619                ! *** case very thin ice: fill only category 1 
    620                IF ( i_fill == 1 ) THEN 
     616               IF ( i_fill == 1 ) THEN      !-- case very thin ice: fill only category 1 
    621617                  zht_i(ji,1) = zhti(ji) 
    622618                  za_i (ji,1) = zai (ji) 
    623                    
    624                ! *** case ice is thicker: fill categories >1 
    625                ELSE 
    626  
    627                   ! Fill ice thicknesses in the (i_fill-1) cat by hmean  
     619               ELSE                         !-- case ice is thicker: fill categories >1 
     620                  ! thickness 
    628621                  DO jl = 1, i_fill - 1 
    629622                     zht_i(ji,jl) = hi_mean(jl) 
    630623                  END DO 
    631624                   
    632                   ! Concentrations in the (i_fill-1) categories  
     625                  ! concentration 
    633626                  za_i(ji,jl0) = zai(ji) / SQRT(REAL(jpl)) 
    634627                  DO jl = 1, i_fill - 1 
     
    639632                  END DO 
    640633                   
    641                   ! Concentration in the last (i_fill) category 
     634                  ! last category 
    642635                  za_i(ji,i_fill) = zai(ji) - SUM( za_i(ji,1:i_fill-1) ) 
    643                    
    644                   ! Ice thickness in the last (i_fill) category 
    645636                  zV = SUM( za_i(ji,1:i_fill-1) * zht_i(ji,1:i_fill-1) ) 
    646637                  zht_i(ji,i_fill) = ( zhti(ji) * zai(ji) - zV ) / MAX( za_i(ji,i_fill), epsi10 )  
     
    659650                  ENDIF 
    660651                
    661                ENDIF ! case ice is thick or thin 
     652               ENDIF 
    662653             
    663                !--------------------- 
    664654               ! Compatibility tests 
    665                !---------------------  
    666                ! Test 1: area conservation 
    667                zconv = ABS( zai(ji) - SUM( za_i(ji,1:jpl) ) ) 
    668                IF ( zconv < epsi06 ) itest(1) = 1 
     655               zconv = ABS( zai(ji) - SUM( za_i(ji,1:jpl) ) )  
     656               IF ( zconv < epsi06 ) itest(1) = 1                                        ! Test 1: area conservation 
    669657             
    670                ! Test 2: volume conservation 
    671658               zconv = ABS( zhti(ji)*zai(ji) - SUM( za_i(ji,1:jpl)*zht_i(ji,1:jpl) ) ) 
    672                IF ( zconv < epsi06 ) itest(2) = 1 
     659               IF ( zconv < epsi06 ) itest(2) = 1                                        ! Test 2: volume conservation 
    673660                
    674                ! Test 3: thickness of the last category is in-bounds ? 
    675                IF ( zht_i(ji,i_fill) >= hi_max(i_fill-1) ) itest(3) = 1 
     661               IF ( zht_i(ji,i_fill) >= hi_max(i_fill-1) ) itest(3) = 1                  ! Test 3: thickness of the last category is in-bounds ? 
    676662                
    677                ! Test 4: positivity of ice concentrations 
    678663               itest(4) = 1 
    679664               DO jl = 1, i_fill 
    680                   IF ( za_i(ji,jl) < 0._wp ) itest(4) = 0 
     665                  IF ( za_i(ji,jl) < 0._wp ) itest(4) = 0                                ! Test 4: positivity of ice concentrations 
    681666               END DO 
    682                !                                         !============================ 
     667               !                                         !---------------------------- 
    683668            END DO                                       ! end iteration on categories 
    684                !                                         !============================ 
    685          ENDIF ! if zhti > 0 
    686       END DO ! i loop 
    687  
    688       ! ------------------------------------------------ 
    689       ! Adding Snow in each category where za_i is not 0 
    690       ! ------------------------------------------------  
     669               !                                         !---------------------------- 
     670         ENDIF 
     671      END DO 
     672 
     673      ! Add Snow in each category where za_i is not 0 
    691674      DO jl = 1, jpl 
    692675         DO ji = 1, ijpij 
     
    707690#else 
    708691   !!---------------------------------------------------------------------- 
    709    !!   Default option         Dummy module          NO  LIM3 sea-ice model 
     692   !!   Default option         Dummy module           NO ESIM sea-ice model 
    710693   !!---------------------------------------------------------------------- 
    711694#endif 
Note: See TracChangeset for help on using the changeset viewer.