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 8426 for branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO – NEMO

Ignore:
Timestamp:
2017-08-08T17:53:09+02:00 (7 years ago)
Author:
clem
Message:

last routine names to be changed

Location:
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3
Files:
4 added
6 deleted
12 edited

Legend:

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

    r8424 r8426  
    177177 
    178178   !                                     !!** ice-init namelist (namiceini) ** 
    179                                           ! -- iceistate -- ! 
     179                                          ! -- iceist -- ! 
    180180   LOGICAL , PUBLIC ::   ln_limini        ! initialization or not 
    181181   LOGICAL , PUBLIC ::   ln_limini_file   ! Ice initialization state from 2D netcdf file 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceadv.F90

    r8424 r8426  
    2929   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
    3030   USE timing         ! Timing 
    31    USE icecons        ! conservation tests 
    3231   USE icectl         ! control prints 
    3332 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icectl.F90

    r8420 r8426  
    3232   PRIVATE 
    3333 
     34   PUBLIC   ice_cons_hsm 
     35   PUBLIC   ice_cons_final 
    3436   PUBLIC   ice_ctl 
    3537   PUBLIC   ice_prt 
     
    4648CONTAINS 
    4749 
     50   SUBROUTINE ice_cons_hsm( icount, cd_routine, zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b ) 
     51      !!-------------------------------------------------------------------------------------------------------- 
     52      !!                                        ***  ROUTINE ice_cons_hsm *** 
     53      !! 
     54      !! ** Purpose : Test the conservation of heat, salt and mass for each ice routine 
     55      !!                     + test if ice concentration and volume are > 0 
     56      !! 
     57      !! ** Method  : This is an online diagnostics which can be activated with ln_limdiachk=true 
     58      !!              It prints in ocean.output if there is a violation of conservation at each time-step 
     59      !!              The thresholds (zv_sill, zs_sill, zh_sill) which determine violations are set to 
     60      !!              a minimum of 1 mm of ice (over the ice area) that is lost/gained spuriously during 100 years. 
     61      !!              For salt and heat thresholds, ice is considered to have a salinity of 10  
     62      !!              and a heat content of 3e5 J/kg (=latent heat of fusion)  
     63      !!-------------------------------------------------------------------------------------------------------- 
     64      INTEGER         , INTENT(in)    :: icount        ! determine wether this is the beggining of the routine (0) or the end (1) 
     65      CHARACTER(len=*), INTENT(in)    :: cd_routine    ! name of the routine 
     66      REAL(wp)        , INTENT(inout) :: zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b  
     67      REAL(wp)                        :: zvi,   zsmv,   zei,   zfs,   zfw,   zft 
     68      REAL(wp)                        :: zvmin, zamin, zamax  
     69      REAL(wp)                        :: zvtrp, zetrp 
     70      REAL(wp)                        :: zarea, zv_sill, zs_sill, zh_sill 
     71      REAL(wp), PARAMETER             :: zconv = 1.e-9 ! convert W to GW and kg to Mt 
     72 
     73      IF( icount == 0 ) THEN 
     74 
     75         ! salt flux 
     76         zfs_b  = glob_sum(  ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) +  & 
     77            &                  sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) + sfx_sub(:,:) + sfx_lam(:,:)    & 
     78            &                ) *  e1e2t(:,:) * tmask(:,:,1) * zconv ) 
     79 
     80         ! water flux 
     81         zfw_b  = glob_sum( -( wfx_bog(:,:) + wfx_bom(:,:)     + wfx_sum(:,:)     + wfx_sni(:,:)     +                     & 
     82            &                  wfx_opw(:,:) + wfx_res(:,:)     + wfx_dyn(:,:)     + wfx_lam(:,:)     + wfx_ice_sub(:,:) +  & 
     83            &                  wfx_snw_sni(:,:) + wfx_snw_sum(:,:) + wfx_snw_dyn(:,:) + wfx_snw_sub(:,:) + wfx_spr(:,:)        & 
     84            &                ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) 
     85 
     86         ! heat flux 
     87         zft_b  = glob_sum(  ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:)  &  
     88            &                - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:)   & 
     89            &                ) *  e1e2t(:,:) * tmask(:,:,1) * zconv ) 
     90 
     91         zvi_b  = glob_sum( SUM( v_i * rhoic + v_s * rhosn, dim=3 ) * e1e2t * tmask(:,:,1) * zconv ) 
     92 
     93         zsmv_b = glob_sum( SUM( smv_i * rhoic            , dim=3 ) * e1e2t * tmask(:,:,1) * zconv ) 
     94 
     95         zei_b  = glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) +  & 
     96            &                 SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 )    & 
     97                            ) * e1e2t * tmask(:,:,1) * zconv ) 
     98 
     99      ELSEIF( icount == 1 ) THEN 
     100 
     101         ! salt flux 
     102         zfs  = glob_sum(  ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) +  & 
     103            &                sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) + sfx_sub(:,:) + sfx_lam(:,:)    &  
     104            &              ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) - zfs_b 
     105 
     106         ! water flux 
     107         zfw  = glob_sum( -( wfx_bog(:,:) + wfx_bom(:,:)     + wfx_sum(:,:)     + wfx_sni(:,:)     +                     & 
     108            &                wfx_opw(:,:) + wfx_res(:,:)     + wfx_dyn(:,:)     + wfx_lam(:,:)     + wfx_ice_sub(:,:) +  & 
     109            &                wfx_snw_sni(:,:) + wfx_snw_sum(:,:) + wfx_snw_dyn(:,:) + wfx_snw_sub(:,:) + wfx_spr(:,:)        & 
     110            &              ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) - zfw_b 
     111 
     112         ! heat flux 
     113         zft  = glob_sum(  ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:)  &  
     114            &              - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:)   & 
     115            &              ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) - zft_b 
     116  
     117         ! outputs 
     118         zvi  = ( ( glob_sum( SUM( v_i * rhoic + v_s * rhosn, dim=3 )  & 
     119            &                    * e1e2t * tmask(:,:,1) * zconv ) - zvi_b ) * r1_rdtice - zfw ) * rday 
     120 
     121         zsmv = ( ( glob_sum( SUM( smv_i * rhoic            , dim=3 )  & 
     122            &                    * e1e2t * tmask(:,:,1) * zconv ) - zsmv_b ) * r1_rdtice + zfs ) * rday 
     123 
     124         zei  = ( glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) +  & 
     125            &                 SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 )    & 
     126            &                ) * e1e2t * tmask(:,:,1) * zconv ) - zei_b ) * r1_rdtice + zft 
     127 
     128         ! zvtrp and zetrp must be close to 0 if the advection scheme is conservative 
     129         zvtrp = glob_sum( ( diag_trp_vi * rhoic + diag_trp_vs * rhosn ) * e1e2t * tmask(:,:,1) * zconv ) * rday  
     130         zetrp = glob_sum( ( diag_trp_ei         + diag_trp_es         ) * e1e2t * tmask(:,:,1) * zconv ) 
     131 
     132         zvmin = glob_min( v_i ) 
     133         zamax = glob_max( SUM( a_i, dim=3 ) ) 
     134         zamin = glob_min( a_i ) 
     135 
     136         ! set threshold values and calculate the ice area (+epsi10 to set a threshold > 0 when there is no ice)  
     137         zarea   = glob_sum( SUM( a_i + epsi10, dim=3 ) * e1e2t * zconv ) ! in 1.e9 m2 
     138         zv_sill = zarea * 2.5e-5 
     139         zs_sill = zarea * 25.e-5 
     140         zh_sill = zarea * 10.e-5 
     141 
     142         IF(lwp) THEN 
     143            IF ( ABS( zvi  ) > zv_sill ) WRITE(numout,*) 'violation volume [Mt/day]     (',cd_routine,') = ',zvi 
     144            IF ( ABS( zsmv ) > zs_sill ) WRITE(numout,*) 'violation saline [psu*Mt/day] (',cd_routine,') = ',zsmv 
     145            IF ( ABS( zei  ) > zh_sill ) WRITE(numout,*) 'violation enthalpy [GW]       (',cd_routine,') = ',zei 
     146            IF ( ABS(zvtrp ) > zv_sill .AND. cd_routine == 'iceadv' ) THEN 
     147                                         WRITE(numout,*) 'violation vtrp [Mt/day]       (',cd_routine,') = ',zvtrp 
     148                                         WRITE(numout,*) 'violation etrp [GW]           (',cd_routine,') = ',zetrp 
     149            ENDIF 
     150            IF (     zvmin   < -epsi10 ) WRITE(numout,*) 'violation v_i<0  [m]          (',cd_routine,') = ',zvmin 
     151            IF (     zamax   > MAX( rn_amax_n, rn_amax_s ) + epsi10 .AND. & 
     152               &                         cd_routine /= 'iceadv' .AND. cd_routine /= 'icerdgrft' ) THEN 
     153                                         WRITE(numout,*) 'violation a_i>amax            (',cd_routine,') = ',zamax 
     154            IF (     zamax   > 1._wp   ) WRITE(numout,*) 'violation a_i>1               (',cd_routine,') = ',zamax 
     155            ENDIF 
     156            IF (      zamin  < -epsi10 ) WRITE(numout,*) 'violation a_i<0               (',cd_routine,') = ',zamin 
     157         ENDIF 
     158 
     159      ENDIF 
     160 
     161   END SUBROUTINE ice_cons_hsm 
     162 
     163 
     164   SUBROUTINE ice_cons_final( cd_routine ) 
     165      !!--------------------------------------------------------------------------------------------------------- 
     166      !!                                   ***  ROUTINE ice_cons_final *** 
     167      !! 
     168      !! ** Purpose : Test the conservation of heat, salt and mass at the end of each ice time-step 
     169      !! 
     170      !! ** Method  : This is an online diagnostics which can be activated with ln_limdiachk=true 
     171      !!              It prints in ocean.output if there is a violation of conservation at each time-step 
     172      !!              The thresholds (zv_sill, zs_sill, zh_sill) which determine the violation are set to 
     173      !!              a minimum of 1 mm of ice (over the ice area) that is lost/gained spuriously during 100 years. 
     174      !!              For salt and heat thresholds, ice is considered to have a salinity of 10  
     175      !!              and a heat content of 3e5 J/kg (=latent heat of fusion)  
     176      !!-------------------------------------------------------------------------------------------------------- 
     177      CHARACTER(len=*), INTENT(in)    :: cd_routine    ! name of the routine 
     178      REAL(wp)                        :: zhfx, zsfx, zvfx 
     179      REAL(wp)                        :: zarea, zv_sill, zs_sill, zh_sill 
     180      REAL(wp), PARAMETER             :: zconv = 1.e-9 ! convert W to GW and kg to Mt 
     181 
     182      ! heat flux 
     183      zhfx  = glob_sum( ( hfx_in - hfx_out - diag_heat - diag_trp_ei - diag_trp_es   & 
     184      !  &              - SUM( qevap_ice * a_i_b, dim=3 )                           & !!clem: I think this line must be commented (but need check) 
     185         &              ) * e1e2t * tmask(:,:,1) * zconv )  
     186      ! salt flux 
     187      zsfx  = glob_sum( ( sfx + diag_smvi ) * e1e2t * tmask(:,:,1) * zconv ) * rday 
     188      ! water flux 
     189      zvfx  = glob_sum( ( wfx_ice + wfx_snw + wfx_spr + wfx_sub + diag_vice + diag_vsnw ) * e1e2t * tmask(:,:,1) * zconv ) * rday 
     190 
     191      ! set threshold values and calculate the ice area (+epsi10 to set a threshold > 0 when there is no ice)  
     192      zarea   = glob_sum( SUM( a_i + epsi10, dim=3 ) * e1e2t * zconv ) ! in 1.e9 m2 
     193      zv_sill = zarea * 2.5e-5 
     194      zs_sill = zarea * 25.e-5 
     195      zh_sill = zarea * 10.e-5 
     196 
     197      IF( ABS( zvfx ) > zv_sill ) WRITE(numout,*) 'violation vfx    [Mt/day]       (',cd_routine,')  = ',(zvfx) 
     198      IF( ABS( zsfx ) > zs_sill ) WRITE(numout,*) 'violation sfx    [psu*Mt/day]   (',cd_routine,')  = ',(zsfx) 
     199      IF( ABS( zhfx ) > zh_sill ) WRITE(numout,*) 'violation hfx    [GW]           (',cd_routine,')  = ',(zhfx) 
     200 
     201   END SUBROUTINE ice_cons_final 
     202 
     203    
    48204   SUBROUTINE ice_ctl( kt ) 
    49205      !!----------------------------------------------------------------------- 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceforcing.F90

    r8414 r8426  
    1919   USE sbcblk          ! Surface boundary condition: bulk 
    2020   USE sbccpl          ! Surface boundary condition: coupled interface 
    21    USE icealbedo       ! ice albedo 
     21   USE icealb          ! ice albedo 
    2222   ! 
    2323   USE iom             ! I/O manager library 
     
    6464      IF( nn_timing == 1 )   CALL timing_start('ice_forcing_tau') 
    6565 
     66      IF( kt == nit000 .AND. lwp ) THEN 
     67         WRITE(numout,*) 
     68         WRITE(numout,*)'ice_forcing_tau' 
     69         WRITE(numout,*)'~~~~~~~~~~~~~~~' 
     70      ENDIF 
     71 
    6672      SELECT CASE( ksbc ) 
    6773         CASE( jp_usr     )   ;    CALL usrdef_sbc_ice_tau( kt )                 ! user defined formulation 
     
    7884            END DO 
    7985         END DO 
    80          CALL lbc_lnk( utau_ice, 'U', -1. ) 
    81          CALL lbc_lnk( vtau_ice, 'V', -1. ) 
     86         CALL lbc_lnk_multi( utau_ice, 'U', -1., vtau_ice, 'V', -1. ) 
    8287      ENDIF 
    8388 
     
    119124      IF( nn_timing == 1 )   CALL timing_start('ice_forcing_flx') 
    120125 
     126      IF( kt == nit000 .AND. lwp ) THEN 
     127         WRITE(numout,*) 
     128         WRITE(numout,*)'ice_forcing_flx' 
     129         WRITE(numout,*)'~~~~~~~~~~~~~~~' 
     130      ENDIF 
     131 
    121132      ! --- cloud-sky and overcast-sky ice albedos --- ! 
    122       CALL ice_albedo( t_su, ht_i, ht_s, a_ip_frac, h_ip, ln_pnd_rad, zalb_cs, zalb_os ) 
     133      CALL ice_alb( t_su, ht_i, ht_s, a_ip_frac, h_ip, ln_pnd_rad, zalb_cs, zalb_os ) 
    123134 
    124135      ! albedo depends on cloud fraction because of non-linear spectral effects 
     
    140151                                   CALL blk_ice_flx( t_su, alb_ice ) 
    141152            IF( ln_mixcpl      )   CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su ) 
    142             IF( nn_limflx /= 2 )   CALL ice_lim_flx( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx ) 
     153            IF( nn_limflx /= 2 )   CALL ice_flx_dist( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx ) 
    143154 
    144155         CASE ( jp_purecpl )                                     ! coupled formulation 
    145156                                   CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su ) 
    146             IF( nn_limflx == 2 )   CALL ice_lim_flx( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx ) 
     157            IF( nn_limflx == 2 )   CALL ice_flx_dist( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx ) 
    147158      END SELECT 
    148159 
     
    162173 
    163174 
    164    SUBROUTINE ice_lim_flx( ptn_ice, palb_ice, pqns_ice, pqsr_ice, pdqn_ice, pevap_ice, pdevap_ice, k_limflx ) 
    165       !!--------------------------------------------------------------------- 
    166       !!                  ***  ROUTINE ice_lim_flx  *** 
     175   SUBROUTINE ice_flx_dist( ptn_ice, palb_ice, pqns_ice, pqsr_ice, pdqn_ice, pevap_ice, pdevap_ice, k_limflx ) 
     176      !!--------------------------------------------------------------------- 
     177      !!                  ***  ROUTINE ice_flx_dist  *** 
    167178      !! 
    168179      !! ** Purpose :   update the ice surface boundary condition by averaging and / or 
     
    195206      !!---------------------------------------------------------------------- 
    196207      ! 
    197       IF( nn_timing == 1 )  CALL timing_start('ice_lim_flx') 
     208      IF( nn_timing == 1 )  CALL timing_start('ice_flx_dist') 
    198209      ! 
    199210      SELECT CASE( k_limflx )                              !==  averaged on all ice categories  ==! 
     
    231242      END SELECT 
    232243      ! 
    233       IF( nn_timing == 1 )  CALL timing_stop('ice_lim_flx') 
    234       ! 
    235    END SUBROUTINE ice_lim_flx 
     244      IF( nn_timing == 1 )  CALL timing_stop('ice_flx_dist') 
     245      ! 
     246   END SUBROUTINE ice_flx_dist 
    236247 
    237248 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceitd.F90

    r8424 r8426  
    2323   USE ice1D            ! LIM-3 thermodynamic variables 
    2424   USE ice              ! LIM-3 variables 
    25    USE icecons          ! conservation tests 
     25   USE icectl           ! conservation tests 
    2626   USE icetab 
    2727   ! 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icerdgrft.F90

    r8424 r8426  
    1919   USE ice              ! LIM variables 
    2020   USE icevar           ! LIM 
    21    USE icecons          ! conservation tests 
    2221   USE icectl           ! control prints 
    2322   ! 
     
    7877 
    7978 
    80    SUBROUTINE ice_rdgrft 
     79   SUBROUTINE ice_rdgrft( kt ) 
    8180      !!---------------------------------------------------------------------! 
    8281      !!                ***  ROUTINE ice_rdgrft *** 
     
    104103      !!  and Elizabeth C. Hunke, LANL are gratefully acknowledged 
    105104      !!--------------------------------------------------------------------! 
     105      INTEGER, INTENT(in) ::   kt     ! number of iteration 
     106      !! 
    106107      INTEGER  ::   ji, jj, jk, jl        ! dummy loop index 
    107108      INTEGER  ::   niter                 ! local integer  
     
    120121      !!----------------------------------------------------------------------------- 
    121122      IF( nn_timing == 1 )  CALL timing_start('icerdgrft') 
     123 
     124      IF( kt == nit000 .AND. lwp ) THEN 
     125         WRITE(numout,*) 
     126         WRITE(numout,*)'icerdgrft' 
     127         WRITE(numout,*)'~~~~~~~~~' 
     128      ENDIF 
    122129 
    123130      ! conservation test 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icerhg.F90

    r8424 r8426  
    1919   USE ice              ! LIM-3 variables 
    2020   USE icerhg_evp       ! EVP rheology 
    21    USE icecons          ! conservation tests 
    2221   USE icectl           ! control prints 
    2322   USE icevar 
     
    6160 
    6261      IF( nn_timing == 1 )  CALL timing_start('icerhg') 
     62 
     63      IF( kt == nit000 .AND. lwp ) THEN 
     64         WRITE(numout,*) 
     65         WRITE(numout,*)'icerhg' 
     66         WRITE(numout,*)'~~~~~~' 
     67      ENDIF 
    6368 
    6469      CALL ice_var_agg(1)   ! aggregate ice categories 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icestp.F90

    r8424 r8426  
    1111   !!            3.3  ! 2010-11  (G. Madec) ice-ocean stress always computed at each ocean time-step 
    1212   !!            3.4  ! 2011-01  (A Porter)  dynamical allocation 
    13    !!             -   ! 2012-10  (C. Rousset)  add ice_diahsb 
     13   !!             -   ! 2012-10  (C. Rousset)  add ice_dia 
    1414   !!            3.6  ! 2014-07  (M. Vancoppenolle, G. Madec, O. Marti) revise coupled interface 
    1515   !!            4.0  ! 2016-06  (L. Brodeau) new unified bulk routine (based on AeroBulk) 
     
    3737   USE icerdgrft       ! Ice ridging/rafting 
    3838   USE iceupdate       ! sea surface boundary condition 
    39    USE icediahsb       ! Ice budget diagnostics 
     39   USE icedia          ! Ice budget diagnostics 
    4040   USE icewri          ! Ice outputs 
    4141   USE icerst          ! Ice restarts 
    42    USE iceerr1         ! Ice corrections after dynamics 
    43    USE iceerr2         ! Ice corrections after thermo 
     42   USE icecor          ! Ice corrections 
    4443   USE icevar          ! Ice variables switch 
    4544   USE icectl          ! 
     
    4746   USE limmp 
    4847   ! END MV MP 2016 
    49    USE iceistate       ! LIM initial state 
     48   USE iceist          ! LIM initial state 
    5049   USE icethd_sal      ! LIM ice thermodynamics: salinity 
    5150   ! 
     
    130129         CALL eos_fzp( sss_m(:,:) , t_bo(:,:) ) 
    131130         t_bo(:,:) = ( t_bo(:,:) + rt0 ) * tmask(:,:,1) + rt0 * ( 1._wp - tmask(:,:,1) ) 
    132  
    133          ! Mask sea ice surface temperature (set to rt0 over land) 
    134          DO jl = 1, jpl 
    135             t_su(:,:,jl) = t_su(:,:,jl) * tmask(:,:,1) + rt0 * ( 1._wp - tmask(:,:,1) ) 
    136          END DO 
    137131         ! 
    138132                                      CALL ice_bef         ! Store previous ice values 
     
    156150                                      CALL ice_adv( kt )       ! -- advection 
    157151            IF( nn_limdyn == 2 .AND. nn_monocat /= 2 )  &      ! -- ridging/rafting 
    158                &                      CALL ice_rdgrft          
    159             IF( nn_limdyn == 2 )      CALL ice_err1( kt )      ! -- Corrections 
     152               &                      CALL ice_rdgrft( kt )          
     153            IF( nn_limdyn == 2 )      CALL ice_cor( kt , 1 )   ! -- Corrections 
    160154            ! 
    161155         ENDIF 
    162  
    163156         ! --- 
     157          
    164158#if defined key_agrif 
    165159         IF( .NOT. Agrif_Root() )     CALL agrif_interp_lim3('T') 
     
    196190         ! END MV MP 2016 
    197191 
    198          IF( ln_limthd )              CALL ice_err2( kt )       ! -- Corrections 
     192         IF( ln_limthd )              CALL ice_cor( kt , 2 )    ! -- Corrections 
    199193         ! --- 
    200194# if defined key_agrif 
     
    213207!!         IF( .NOT. Agrif_Root() )   CALL Agrif_ParentGrid_To_ChildGrid() 
    214208!!# endif 
    215          IF( ln_limdiahsb )           CALL ice_diahsb( kt )     ! -- Diagnostics and outputs  
     209         IF( ln_limdiahsb )           CALL ice_dia( kt )     ! -- Diagnostics and outputs  
    216210         ! 
    217211                                      CALL ice_wri( 1 )         ! -- Ice outputs  
     
    282276      !                                ! Initial sea-ice state 
    283277      IF( .NOT. ln_rstart ) THEN              ! start from rest: sea-ice deduced from sst 
    284          CALL ice_istate 
     278         CALL ice_ist 
    285279      ELSE                                    ! start from a restart file 
    286280         CALL ice_rst_read 
     
    291285      CALL ice_update_init                 ! ice surface boundary condition 
    292286      ! 
    293       IF( ln_limdiahsb) CALL ice_diahsb_init  ! initialization for diags 
     287      IF( ln_limdiahsb) CALL ice_dia_init  ! initialization for diags 
    294288      ! 
    295289      fr_i(:,:)     = at_i(:,:)         ! initialisation of sea-ice fraction 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd.F90

    r8424 r8426  
    3636   USE icetab         ! 1D <==> 2D transformation 
    3737   USE icevar         ! 
    38    USE icecons        ! conservation tests 
    3938   USE icectl         ! control print 
    4039   ! 
     
    9392 
    9493      IF( kt == nit000 .AND. lwp ) THEN 
    95          WRITE(numout,*)''  
    96          WRITE(numout,*)' ice_thd ' 
    97          WRITE(numout,*)' ~~~~~~~~' 
     94         WRITE(numout,*) 
     95         WRITE(numout,*)' icethd ' 
     96         WRITE(numout,*)' ~~~~~~~' 
    9897      ENDIF 
    9998       
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_lac.F90

    r8424 r8426  
    2323   USE ice            ! LIM variables 
    2424   USE icetab         ! LIM 2D <==> 1D 
    25    USE icecons        ! LIM conservation 
     25   USE icectl         ! LIM conservation 
    2626   USE icethd_ent 
    2727   USE icevar 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceupdate.F90

    r8414 r8426  
    3232   USE sbc_oce , ONLY : nn_fsbc, ln_ice_embd, sfx, fr_i, qsr_tot, qns, qsr, fmmflx, emp, taum, utau, vtau 
    3333   USE sbccpl         ! Surface boundary condition: coupled interface 
    34    USE icealbedo      ! albedo parameters 
     34   USE icealb         ! albedo parameters 
    3535   USE traqsr         ! add penetration of solar flux in the calculation of heat budget 
    3636   USE domvvl         ! Variable volume 
    3737   USE icectl         ! 
    38    USE icecons        ! 
    3938   USE bdy_oce  , ONLY: ln_bdy 
    4039   ! 
     
    4443   USE lib_mpp        ! MPP library 
    4544   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     45   USE timing         ! Timing 
    4646 
    4747   IMPLICIT NONE 
     
    108108      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zalb_cs, zalb_os     ! 3D workspace 
    109109      !!--------------------------------------------------------------------- 
     110      IF( nn_timing == 1 )  CALL timing_start('ice_update_flx') 
     111 
     112      IF( kt == nit000 .AND. lwp ) THEN 
     113         WRITE(numout,*) 
     114         WRITE(numout,*)'ice_update_flx' 
     115         WRITE(numout,*)'~~~~~~~~~~~~~~' 
     116      ENDIF 
    110117 
    111118      ! --- case we bypass ice thermodynamics --- ! 
     
    201208      !    Snow/ice albedo (only if sent to coupler, useless in forced mode)   ! 
    202209      !------------------------------------------------------------------------! 
    203       CALL ice_albedo( t_su, ht_i, ht_s, a_ip_frac, h_ip, ln_pnd_rad, zalb_cs, zalb_os ) ! cloud-sky and overcast-sky ice albedos 
     210      CALL ice_alb( t_su, ht_i, ht_s, a_ip_frac, h_ip, ln_pnd_rad, zalb_cs, zalb_os ) ! cloud-sky and overcast-sky ice albedos 
    204211 
    205212      alb_ice(:,:,:) = ( 1. - cldf_ice ) * zalb_cs(:,:,:) + cldf_ice * zalb_os(:,:,:) 
     
    211218      IF( ln_limctl )   CALL ice_prt( kt, iiceprt, jiceprt, 3, ' - Final state ice_update - ' ) 
    212219      IF( ln_ctl )      CALL ice_prt3D( 'iceupdate' ) 
     220 
     221      IF( nn_timing == 1 )  CALL timing_stop('ice_update_flx') 
    213222 
    214223   END SUBROUTINE ice_update_flx 
     
    247256      REAL(wp) ::   zat_v, zvtau_ice, zv_t, zrhoco  !   -      - 
    248257      !!--------------------------------------------------------------------- 
     258 
     259      IF( nn_timing == 1 )  CALL timing_start('ice_update_tau') 
     260 
     261      IF( kt == nit000 .AND. lwp ) THEN 
     262         WRITE(numout,*) 
     263         WRITE(numout,*)'ice_update_tau' 
     264         WRITE(numout,*)'~~~~~~~~~~~~~~' 
     265      ENDIF 
     266 
    249267      zrhoco = rau0 * rn_cio 
    250268      ! 
     
    285303      CALL lbc_lnk_multi( utau, 'U', -1., vtau, 'V', -1. )   ! lateral boundary condition 
    286304      ! 
     305      IF( nn_timing == 1 )  CALL timing_stop('ice_update_tau') 
    287306      !   
    288307   END SUBROUTINE ice_update_tau 
     
    304323      IF(lwp) WRITE(numout,*) 
    305324      IF(lwp) WRITE(numout,*) 'ice_update_init : LIM-3 sea-ice - surface boundary condition' 
    306       IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~   ' 
     325      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~   ' 
    307326 
    308327      !                                      ! allocate ice_update array 
     
    368387   END SUBROUTINE ice_update_init 
    369388 
    370 #else 
    371    !!---------------------------------------------------------------------- 
    372    !!   Default option :        Dummy module       NO LIM 3.0 sea-ice model 
    373    !!---------------------------------------------------------------------- 
    374 CONTAINS 
    375    SUBROUTINE ice_update           ! Dummy routine 
    376    END SUBROUTINE ice_update 
    377389#endif  
    378390 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icevar.F90

    r8424 r8426  
    612612      !!                  ice thickness distribution follows a gaussian law 
    613613      !!               around the concentration of the most likely ice thickness 
    614       !!                           (similar as iceistate.F90) 
     614      !!                           (similar as iceist.F90) 
    615615      !! 
    616616      !! ** Method:   Iterative procedure 
Note: See TracChangeset for help on using the changeset viewer.