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/iceistate.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/iceistate.F90

    r8531 r8534  
    22   !!====================================================================== 
    33   !!                     ***  MODULE  iceistate  *** 
    4    !!              Initialisation of diagnostics ice variables 
     4   !!   sea-ice : Initialization of ice variables 
    55   !!====================================================================== 
    66   !! History :  2.0  ! 2004-01 (C. Ethe, G. Madec)  Original code 
     
    1212#if defined key_lim3 
    1313   !!---------------------------------------------------------------------- 
    14    !!   'key_lim3'                                       LIM3 sea-ice model 
     14   !!   'key_lim3'                                       ESIM sea-ice model 
    1515   !!---------------------------------------------------------------------- 
    1616   !!   ice_istate       :  initialization of diagnostics ice variables 
    1717   !!   ice_istate_init  :  initialization of ice state and namelist read 
    1818   !!---------------------------------------------------------------------- 
    19    USE par_oce        ! ocean parameters 
    2019   USE phycst         ! physical constant 
    2120   USE oce            ! dynamics and tracers variables 
     
    2928   ! 
    3029   USE in_out_manager ! I/O manager 
     30   USE iom            ! I/O manager library 
    3131   USE lib_mpp        ! MPP library 
    32    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     32   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
    3333   USE fldread        ! read input fields 
    34    USE iom 
    3534 
    3635   IMPLICIT NONE 
     
    8281      !!                values in the namelist             
    8382      !! 
    84       !! ** Steps   :   1) Read namelist 
    85       !!                2) Basal temperature; ice and hemisphere masks 
     83      !! ** Steps   :   1) Set initial surface and basal temperatures 
     84      !!                2) Recompute or read sea ice state variables 
    8685      !!                3) Fill in the ice thickness distribution using gaussian 
    8786      !!                4) Fill in space-dependent arrays for state variables 
    88       !!                5) Diagnostic arrays 
    89       !!                6) Lateral boundary conditions 
     87      !!                5) snow-ice mass computation 
     88      !!                6) store before fields 
    9089      !! 
    9190      !! ** Notes   : o_i, t_su, t_s, t_i, s_i must be filled everywhere, even 
     
    109108 
    110109      !-------------------------------------------------------------------- 
    111       ! 1) Read namelist 
     110      ! 1) Set surface and bottom temperatures to initial values 
    112111      !-------------------------------------------------------------------- 
    113112      ! 
     
    122121      t_bo(:,:) = ( t_bo(:,:) + rt0 ) * tmask(:,:,1)  
    123122 
    124       !-------------------------------------------------------------------- 
    125       ! 2) Initialization of sea ice state variables 
    126       !-------------------------------------------------------------------- 
    127123      IF( ln_iceini ) THEN 
     124         !----------------------------------------------------------- 
     125         ! 2) Compute or read sea ice variables ===> single category 
     126         !----------------------------------------------------------- 
    128127         ! 
    129          IF( ln_iceini_file )THEN 
    130          ! 
     128         !                             !---------------! 
     129         IF( ln_iceini_file )THEN      ! Read a file   ! 
     130            !                          !---------------! 
     131            ! 
    131132            zht_i_ini(:,:)  = si(jp_hti)%fnow(:,:,1) 
    132133            zht_s_ini(:,:)  = si(jp_hts)%fnow(:,:,1) 
     
    139140            ELSEWHERE                       ; zswitch(:,:) = 0._wp 
    140141            END WHERE 
     142            zvt_i_ini(:,:) = zht_i_ini(:,:) * zat_i_ini(:,:) 
    141143            ! 
    142          ELSE ! ln_iceini_file = F 
    143  
    144             !-------------------------------------------------------------------- 
    145             ! 3) Basal temperature, ice mask 
    146             !-------------------------------------------------------------------- 
    147             ! no ice if sst <= t-freez + ttest 
     144         !                             !---------------! 
     145         ELSE                          ! Read namelist ! 
     146            !                          !---------------! 
     147 
     148           ! no ice if sst <= t-freez + ttest 
    148149            WHERE( ( sst_m(:,:) - (t_bo(:,:) - rt0) ) * tmask(:,:,1) >= rn_thres_sst ) ; zswitch(:,:) = 0._wp  
    149150            ELSEWHERE                                                                  ; zswitch(:,:) = tmask(:,:,1) 
    150151            END WHERE 
    151152 
    152             !----------------------------- 
    153             ! 3.1) Hemisphere-dependent arrays 
    154             !----------------------------- 
    155153            ! assign initial thickness, concentration, snow depth and salinity to an hemisphere-dependent array 
    156154            WHERE( ff_t(:,:) >= 0._wp ) 
     
    169167               ztm_i_ini(:,:) = rn_tmi_ini_s * zswitch(:,:) 
    170168            END WHERE 
     169            zvt_i_ini(:,:) = zht_i_ini(:,:) * zat_i_ini(:,:) 
    171170            ! 
    172          ENDIF ! ln_iceini_file 
     171         ENDIF 
    173172          
    174          zvt_i_ini(:,:) = zht_i_ini(:,:) * zat_i_ini(:,:)   ! ice volume 
    175          !--------------------------------------------------------------------- 
    176          ! 3.2) Distribute ice concentration and thickness into the categories 
    177          !--------------------------------------------------------------------- 
     173         !------------------------------------------------------------------ 
     174         ! 3) Distribute ice concentration and thickness into the categories 
     175         !------------------------------------------------------------------ 
    178176         ! a gaussian distribution for ice concentration is used 
    179177         ! then we check whether the distribution fullfills 
     
    187185               IF( zat_i_ini(ji,jj) > 0._wp .AND. zht_i_ini(ji,jj) > 0._wp )THEN 
    188186 
    189                   !--- jl0: most likely index where cc will be maximum 
     187                  ! find which category (jl0) the input ice thickness falls into 
    190188                  jl0 = jpl 
    191189                  DO jl = 1, jpl 
     
    196194                  END DO 
    197195                  ! 
    198                   ! initialisation of tests 
    199                   itest(:)  = 0 
    200                    
    201                   i_fill = jpl + 1                                             !==================================== 
    202                   DO WHILE ( ( SUM( itest(:) ) /= 4 ) .AND. ( i_fill >= 2 ) )  ! iterative loop on i_fill categories 
    203                      ! iteration                                               !==================================== 
     196                  itest(:) = 0 
     197                  i_fill   = jpl + 1                                            !------------------------------------ 
     198                  DO WHILE ( ( SUM( itest(:) ) /= 4 ) .AND. ( i_fill >= 2 ) )   ! iterative loop on i_fill categories 
     199                     !                                                          !------------------------------------ 
    204200                     i_fill = i_fill - 1 
    205  
    206                      ! initialisation of ice variables for each try 
     201                     ! 
    207202                     zh_i_ini(ji,jj,:) = 0._wp  
    208203                     za_i_ini(ji,jj,:) = 0._wp 
    209204                     itest(:) = 0 
    210205                     ! 
    211                      ! *** case very thin ice: fill only category 1 
    212                      IF ( i_fill == 1 ) THEN 
     206                     IF ( i_fill == 1 ) THEN      !-- case very thin ice: fill only category 1 
    213207                        zh_i_ini(ji,jj,1) = zht_i_ini(ji,jj) 
    214208                        za_i_ini(ji,jj,1) = zat_i_ini(ji,jj) 
    215  
    216                      ! *** case ice is thicker: fill categories >1 
    217                      ELSE 
    218  
    219                         ! Fill ice thicknesses in the (i_fill-1) cat by hmean  
     209                     ELSE                         !-- case ice is thicker: fill categories >1 
     210                        ! thickness 
    220211                        DO jl = 1, i_fill-1 
    221212                           zh_i_ini(ji,jj,jl) = hi_mean(jl) 
    222213                        END DO 
    223214                        ! 
    224                         !--- Concentrations 
     215                        ! concentration 
    225216                        za_i_ini(ji,jj,jl0) = zat_i_ini(ji,jj) / SQRT(REAL(jpl)) 
    226217                        DO jl = 1, i_fill - 1 
     
    230221                           ENDIF 
    231222                        END DO 
    232                         ! 
    233                         ! Concentration in the last (i_fill) category 
     223 
     224                        ! last category 
    234225                        za_i_ini(ji,jj,i_fill) = zat_i_ini(ji,jj) - SUM( za_i_ini(ji,jj,1:i_fill-1) ) 
    235  
    236                         ! Ice thickness in the last (i_fill) category 
    237226                        zV = SUM( za_i_ini(ji,jj,1:i_fill-1) * zh_i_ini(ji,jj,1:i_fill-1) ) 
    238227                        zh_i_ini(ji,jj,i_fill) = ( zvt_i_ini(ji,jj) - zV ) / MAX( za_i_ini(ji,jj,i_fill), epsi10 )  
     
    252241                        ENDIF 
    253242                        ! 
    254                      ENDIF ! case ice is thick or thin 
    255  
    256                      !--------------------- 
     243                     ENDIF 
     244 
    257245                     ! Compatibility tests 
    258                      !--------------------- 
    259                      ! Test 1: area conservation 
    260                      zconv = ABS( zat_i_ini(ji,jj) - SUM( za_i_ini(ji,jj,1:jpl) ) ) 
     246                     zconv = ABS( zat_i_ini(ji,jj) - SUM( za_i_ini(ji,jj,1:jpl) ) )           ! Test 1: area conservation 
    261247                     IF ( zconv < epsi06 ) itest(1) = 1 
    262248                      
    263                      ! Test 2: volume conservation 
    264                      zconv = ABS(       zat_i_ini(ji,jj)       * zht_i_ini(ji,jj)   & 
     249                     zconv = ABS(       zat_i_ini(ji,jj)       * zht_i_ini(ji,jj)   &         ! Test 2: volume conservation 
    265250                        &        - SUM( za_i_ini (ji,jj,1:jpl) * zh_i_ini (ji,jj,1:jpl) ) ) 
    266251                     IF ( zconv < epsi06 ) itest(2) = 1 
    267252                      
    268                      ! Test 3: thickness of the last category is in-bounds ? 
    269                      IF ( zh_i_ini(ji,jj,i_fill) >= hi_max(i_fill-1) ) itest(3) = 1 
     253                     IF ( zh_i_ini(ji,jj,i_fill) >= hi_max(i_fill-1) ) itest(3) = 1           ! Test 3: thickness of the last category is in-bounds ? 
    270254                      
    271                      ! Test 4: positivity of ice concentrations 
    272255                     itest(4) = 1 
    273256                     DO jl = 1, i_fill 
    274                         IF ( za_i_ini(ji,jj,jl) < 0._wp ) itest(4) = 0 
     257                        IF ( za_i_ini(ji,jj,jl) < 0._wp ) itest(4) = 0                        ! Test 4: positivity of ice concentrations 
    275258                     END DO 
    276                      !                                      !============================ 
    277                   END DO                                    ! end iteration on categories 
    278                   !                                         !============================ 
     259                     !                                                          !---------------------------- 
     260                  END DO                                                        ! end iteration on categories 
     261                  !                                                             !---------------------------- 
    279262                  ! 
    280263                  IF( lwp .AND. SUM(itest) /= 4 ) THEN  
     
    288271                  ENDIF 
    289272                
    290                ENDIF !  zat_i_ini(ji,jj) > 0._wp .AND. zht_i_ini(ji,jj) > 0._wp 
     273               ENDIF 
    291274               ! 
    292275            END DO    
     
    294277 
    295278         !--------------------------------------------------------------------- 
    296          ! 3.3) Space-dependent arrays for ice state variables 
     279         ! 4) Fill in sea ice arrays 
    297280         !--------------------------------------------------------------------- 
    298281 
     
    426409         at_i (:,:) = at_i (:,:) + a_i (:,:,jl) 
    427410      END DO 
    428  
    429       !-------------------------------------------------------------------- 
    430       ! 4) Global ice variables for output diagnostics                    |  
    431       !-------------------------------------------------------------------- 
     411      ! 
     412      ! --- set ice velocities --- ! 
    432413      u_ice (:,:)     = 0._wp 
    433414      v_ice (:,:)     = 0._wp 
    434415      ! 
    435       !-------------------------------------------------------------------- 
    436       ! Snow-ice mass (case ice is fully embedded)                    |  
    437       !-------------------------------------------------------------------- 
     416      !---------------------------------------------- 
     417      ! 5) Snow-ice mass (case ice is fully embedded) 
     418      !---------------------------------------------- 
    438419      snwice_mass  (:,:) = tmask(:,:,1) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  )   ! snow+ice mass 
    439420      snwice_mass_b(:,:) = snwice_mass(:,:) 
     
    556537         WRITE(numout,*) '~~~~~~~~~~~~~~~' 
    557538         WRITE(numout,*) '   Namelist namini:' 
    558          WRITE(numout,*) '      initialization with ice (T) or not (F)                 ln_iceini     = ', ln_iceini 
    559          WRITE(numout,*) '      ice initialization from a netcdf file                ln_iceini_file  = ', ln_iceini_file 
    560          WRITE(numout,*) '      max delta ocean temp. above Tfreeze with initial ice   rn_thres_sst  = ', rn_thres_sst 
    561          WRITE(numout,*) '      initial snow thickness in the north                    rn_hts_ini_n  = ', rn_hts_ini_n 
    562          WRITE(numout,*) '      initial snow thickness in the south                    rn_hts_ini_s  = ', rn_hts_ini_s  
    563          WRITE(numout,*) '      initial ice thickness  in the north                    rn_hti_ini_n  = ', rn_hti_ini_n 
    564          WRITE(numout,*) '      initial ice thickness  in the south                    rn_hti_ini_s  = ', rn_hti_ini_s 
    565          WRITE(numout,*) '      initial ice concentr.  in the north                    rn_ati_ini_n  = ', rn_ati_ini_n 
    566          WRITE(numout,*) '      initial ice concentr.  in the north                    rn_ati_ini_s  = ', rn_ati_ini_s 
    567          WRITE(numout,*) '      initial  ice salinity  in the north                    rn_smi_ini_n  = ', rn_smi_ini_n 
    568          WRITE(numout,*) '      initial  ice salinity  in the south                    rn_smi_ini_s  = ', rn_smi_ini_s 
    569          WRITE(numout,*) '      initial  ice/snw temp  in the north                    rn_tmi_ini_n  = ', rn_tmi_ini_n 
    570          WRITE(numout,*) '      initial  ice/snw temp  in the south                    rn_tmi_ini_s  = ', rn_tmi_ini_s 
     539         WRITE(numout,*) '      initialization with ice (T) or not (F)                 ln_iceini       = ', ln_iceini 
     540         WRITE(numout,*) '      ice initialization from a netcdf file                  ln_iceini_file  = ', ln_iceini_file 
     541         WRITE(numout,*) '      max delta ocean temp. above Tfreeze with initial ice   rn_thres_sst    = ', rn_thres_sst 
     542         WRITE(numout,*) '      initial snow thickness in the north                    rn_hts_ini_n    = ', rn_hts_ini_n 
     543         WRITE(numout,*) '      initial snow thickness in the south                    rn_hts_ini_s    = ', rn_hts_ini_s  
     544         WRITE(numout,*) '      initial ice thickness  in the north                    rn_hti_ini_n    = ', rn_hti_ini_n 
     545         WRITE(numout,*) '      initial ice thickness  in the south                    rn_hti_ini_s    = ', rn_hti_ini_s 
     546         WRITE(numout,*) '      initial ice concentr.  in the north                    rn_ati_ini_n    = ', rn_ati_ini_n 
     547         WRITE(numout,*) '      initial ice concentr.  in the north                    rn_ati_ini_s    = ', rn_ati_ini_s 
     548         WRITE(numout,*) '      initial  ice salinity  in the north                    rn_smi_ini_n    = ', rn_smi_ini_n 
     549         WRITE(numout,*) '      initial  ice salinity  in the south                    rn_smi_ini_s    = ', rn_smi_ini_s 
     550         WRITE(numout,*) '      initial  ice/snw temp  in the north                    rn_tmi_ini_n    = ', rn_tmi_ini_n 
     551         WRITE(numout,*) '      initial  ice/snw temp  in the south                    rn_tmi_ini_s    = ', rn_tmi_ini_s 
    571552      ENDIF 
    572553 
     
    595576#else 
    596577   !!---------------------------------------------------------------------- 
    597    !!   Default option :         Empty module          NO LIM sea-ice model 
     578   !!   Default option :         Empty module         NO ESIM sea-ice model 
    598579   !!---------------------------------------------------------------------- 
    599580#endif 
Note: See TracChangeset for help on using the changeset viewer.