MODULE iceadv !!====================================================================== !! *** MODULE iceadv *** !! LIM transport ice model : sea-ice advection/diffusion !!====================================================================== !! History : LIM-2 ! 2000-01 (M.A. Morales Maqueda, H. Goosse, and T. Fichefet) Original code !! 3.0 ! 2005-11 (M. Vancoppenolle) Multi-layer sea ice, salinity variations !! 4.0 ! 2011-02 (G. Madec) dynamical allocation !!---------------------------------------------------------------------- #if defined key_lim3 !!---------------------------------------------------------------------- !! 'key_lim3' LIM3 sea-ice model !!---------------------------------------------------------------------- !! ice_adv : advection/diffusion process of sea ice !!---------------------------------------------------------------------- USE phycst ! physical constant USE dom_oce ! ocean domain USE sbc_oce , ONLY : nn_fsbc ! frequency of sea-ice call USE ice ! sea-ice: variables USE icevar ! sea-ice: operations USE iceadv_prather ! sea-ice: advection scheme (Prather) USE iceadv_umx ! sea-ice: advection scheme (ultimate-macho) USE icectl ! sea-ice: control prints ! USE in_out_manager ! I/O manager USE lbclnk ! lateral boundary conditions -- MPP exchanges USE lib_mpp ! MPP library USE prtctl ! Print control USE lib_fortran ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) USE timing ! Timing USE iom ! IMPLICIT NONE PRIVATE PUBLIC ice_adv ! called by icestp PUBLIC ice_adv_init ! called by icestp INTEGER :: nice_adv ! choice of the type of advection scheme ! ! associated indices: INTEGER, PARAMETER :: np_advPRA = 1 ! Prather scheme INTEGER, PARAMETER :: np_advUMx = 2 ! Ultimate-Macho scheme ! ! ** namelist (namice_adv) ** LOGICAL :: ln_adv_Pra ! Prather advection scheme LOGICAL :: ln_adv_UMx ! Ultimate-Macho advection scheme INTEGER :: nn_UMx ! order of the UMx advection scheme ! !! * Substitution # include "vectopt_loop_substitute.h90" !!---------------------------------------------------------------------- !! NEMO/ICE 4.0 , NEMO Consortium (2017) !! $Id: iceadv.F90 8373 2017-07-25 17:44:54Z clem $ !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE ice_adv( kt ) !!---------------------------------------------------------------------- !! *** ROUTINE ice_adv *** !! !! ** purpose : advection of sea ice !! !! ** method : variables included in the process are scalar, !! other values are considered as second order. !! For advection, one can choose between !! a) an Ultimate-Macho scheme (whose order is defined by nn_UMx) => ln_adv_UMx !! b) and a second order Prather scheme => ln_adv_Pra !! !! ** action : !!---------------------------------------------------------------------- INTEGER, INTENT(in) :: kt ! number of iteration !!--------------------------------------------------------------------- IF( nn_timing == 1 ) CALL timing_start('iceadv') IF( kt == nit000 .AND. lwp ) THEN WRITE(numout,*) WRITE(numout,*) 'ice_adv: sea-ice advection' WRITE(numout,*) '~~~~~~~' ENDIF ! conservation test IF( ln_icediachk ) CALL ice_cons_hsm(0, 'iceadv', rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft) !---------- ! Advection !---------- SELECT CASE( nice_adv ) ! !-----------------------! CASE( np_advUMx ) ! ULTIMATE-MACHO scheme ! ! !-----------------------! CALL ice_adv_umx( nn_UMx, kt, u_ice, v_ice, & & ato_i, v_i, v_s, smv_i, oa_i, a_i, a_ip, v_ip, e_s, e_i ) ! !-----------------------! CASE( np_advPRA ) ! PRATHER scheme ! ! !-----------------------! CALL ice_adv_prather( kt, u_ice, v_ice, & & ato_i, v_i, v_s, smv_i, oa_i, a_i, a_ip, v_ip, e_s, e_i ) END SELECT !------------ ! diagnostics !------------ diag_trp_ei (:,:) = SUM(SUM( e_i (:,:,1:nlay_i,:) - e_i_b (:,:,1:nlay_i,:), dim=4 ), dim=3 ) * r1_rdtice diag_trp_es (:,:) = SUM(SUM( e_s (:,:,1:nlay_s,:) - e_s_b (:,:,1:nlay_s,:), dim=4 ), dim=3 ) * r1_rdtice diag_trp_smv(:,:) = SUM( smv_i(:,:,:) - smv_i_b(:,:,:) , dim=3 ) * r1_rdtice diag_trp_vi (:,:) = SUM( v_i (:,:,:) - v_i_b (:,:,:) , dim=3 ) * r1_rdtice diag_trp_vs (:,:) = SUM( v_s (:,:,:) - v_s_b (:,:,:) , dim=3 ) * r1_rdtice IF( iom_use('icetrp') ) CALL iom_put( "icetrp" , diag_trp_vi * rday ) ! ice volume transport IF( iom_use('snwtrp') ) CALL iom_put( "snwtrp" , diag_trp_vs * rday ) ! snw volume transport IF( iom_use('saltrp') ) CALL iom_put( "saltrp" , diag_trp_smv * rday * rhoic ) ! salt content transport IF( iom_use('deitrp') ) CALL iom_put( "deitrp" , diag_trp_ei ) ! advected ice enthalpy (W/m2) IF( iom_use('destrp') ) CALL iom_put( "destrp" , diag_trp_es ) ! advected snw enthalpy (W/m2) IF( lrst_ice ) THEN !* write Prather fields in the restart file IF( ln_adv_Pra ) CALL adv_pra_rst( 'WRITE', kt ) ENDIF ! controls IF( ln_icediachk ) CALL ice_cons_hsm(1, 'iceadv', rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft) ! conservation IF( ln_icectl ) CALL ice_prt (kt, iiceprt, jiceprt,-1, ' - ice dyn & trp - ') ! prints IF( nn_timing == 1 ) CALL timing_stop ('iceadv') ! timing ! END SUBROUTINE ice_adv SUBROUTINE ice_adv_init !!------------------------------------------------------------------- !! *** ROUTINE ice_adv_init *** !! !! ** Purpose : Physical constants and parameters linked to the ice !! dynamics !! !! ** Method : Read the namice_adv namelist and check the ice-dynamic !! parameter values called at the first timestep (nit000) !! !! ** input : Namelist namice_adv !!------------------------------------------------------------------- INTEGER :: ios, ioptio ! Local integer output status for namelist read !! NAMELIST/namice_adv/ ln_adv_Pra, ln_adv_UMx, nn_UMx !!------------------------------------------------------------------- ! REWIND( numnam_ice_ref ) ! Namelist namice_adv in reference namelist : Ice dynamics READ ( numnam_ice_ref, namice_adv, IOSTAT = ios, ERR = 901) 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_adv in reference namelist', lwp ) ! REWIND( numnam_ice_cfg ) ! Namelist namice_adv in configuration namelist : Ice dynamics READ ( numnam_ice_cfg, namice_adv, IOSTAT = ios, ERR = 902 ) 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_adv in configuration namelist', lwp ) IF(lwm) WRITE ( numoni, namice_adv ) ! IF(lwp) THEN ! control print WRITE(numout,*) WRITE(numout,*) 'ice_adv_init: ice parameters for ice dynamics ' WRITE(numout,*) '~~~~~~~~~~~~' WRITE(numout,*) ' Namelist namice_adv' WRITE(numout,*) ' type of advection scheme (Prather) ln_adv_Pra = ', ln_adv_Pra WRITE(numout,*) ' type of advection scheme (Ulimate-Macho) ln_adv_UMx = ', ln_adv_UMx WRITE(numout,*) ' order of the Ultimate-Macho scheme nn_UMx = ', nn_UMx ENDIF ! ! !== set the choice of ice advection ==! ioptio = 0 IF( ln_adv_Pra ) THEN ; ioptio = ioptio + 1 ; nice_adv = np_advPRA ; ENDIF IF( ln_adv_UMx ) THEN ; ioptio = ioptio + 1 ; nice_adv = np_advUMx ; ENDIF IF( ioptio /= 1 ) CALL ctl_stop( 'ice_adv_init: choose one and only one ice advection scheme (ln_adv_Pra or ln_adv_UMx)' ) ! IF( ln_adv_Pra ) CALL adv_pra_rst( 'READ' ) !* read or initialize all required files ! END SUBROUTINE ice_adv_init #else !!---------------------------------------------------------------------- !! Default option Empty Module No sea-ice model !!---------------------------------------------------------------------- #endif !!====================================================================== END MODULE iceadv