MODULE tradmp !!====================================================================== !! *** MODULE tradmp *** !! Ocean physics: internal restoring trend on active tracers (T and S) !!====================================================================== !! History : 5.0 ! 91-03 (O. Marti, G. Madec) Original code !! ! 92-06 (M. Imbard) doctor norme !! ! 96-01 (G. Madec) statement function for e3 !! ! 97-05 (G. Madec) macro-tasked on jk-slab !! ! 98-07 (M. Imbard, G. Madec) ORCA version !! 7.0 ! 01-02 (M. Imbard) cofdis, Original code !! 8.1 ! 01-02 (G. Madec, E. Durand) cleaning !! 8.5 ! 02-08 (G. Madec, E. Durand) free form + modules !!---------------------------------------------------------------------- #if defined key_tradmp || defined key_esopa !!---------------------------------------------------------------------- !! key_tradmp internal damping !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! tra_dmp : update the tracer trend with the internal damping !! tra_dmp_init : initialization, namlist read, parameters control !! dtacof_zoom : restoring coefficient for zoom domain !! dtacof : restoring coefficient for global domain !! cofdis : compute the distance to the coastline !!---------------------------------------------------------------------- USE oce ! ocean dynamics and tracers variables USE dom_oce ! ocean space and time domain variables USE trdmod ! ocean active tracers trends USE trdmod_oce ! ocean variables trends USE zdf_oce ! ocean vertical physics USE in_out_manager ! I/O manager USE phycst ! Define parameters for the routines USE dtatem ! temperature data USE dtasal ! salinity data USE zdfmxl ! mixed layer depth USE lib_mpp ! distribued memory computing USE prtctl ! Print control IMPLICIT NONE PRIVATE PUBLIC tra_dmp ! routine called by step.F90 #if ! defined key_agrif LOGICAL, PUBLIC, PARAMETER :: lk_tradmp = .TRUE. !: internal damping flag #else LOGICAL, PUBLIC :: lk_tradmp = .TRUE. !: internal damping flag #endif REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) :: strdmp !: damping salinity trend (psu/s) REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) :: resto !: restoring coeff. on T and S (s-1) !!* newtonian damping namelist (mandmp) INTEGER :: ndmp = -1 ! = 0/-1/'latitude' for damping over T and S INTEGER :: ndmpf = 2 ! = 1 create a damping.coeff NetCDF file INTEGER :: nmldmp = 0 ! = 0/1/2 flag for damping in the mixed layer REAL(wp) :: sdmp = 50. ! surface time scale for internal damping (days) REAL(wp) :: bdmp = 360. ! bottom time scale for internal damping (days) REAL(wp) :: hdmp = 800. ! depth of transition between sdmp and bdmp (meters) NAMELIST/namtdp/ ndmp, ndmpf, nmldmp, sdmp, bdmp, hdmp !! * Substitutions # include "domzgr_substitute.h90" # include "vectopt_loop_substitute.h90" !!---------------------------------------------------------------------- !! OPA 9.0 , LOCEAN-IPSL (2006) !! $Header$ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE tra_dmp( kt ) !!---------------------------------------------------------------------- !! *** ROUTINE tra_dmp *** !! !! ** Purpose : Compute the tracer trend due to a newtonian damping !! of the tracer field towards given data field and add it to the !! general tracer trends. !! !! ** Method : Newtonian damping towards t_dta and s_dta computed !! and add to the general tracer trends: !! ta = ta + resto * (t_dta - tb) !! sa = sa + resto * (s_dta - sb) !! The trend is computed either throughout the water column !! (nlmdmp=0) or in area of weak vertical mixing (nlmdmp=1) or !! below the well mixed layer (nlmdmp=2) !! !! ** Action : - update the tracer trends (ta,sa) with the newtonian !! damping trends. !! - save the trends in (ttrd,strd) ('key_trdtra') !!---------------------------------------------------------------------- USE oce, ONLY : ztrdt => ua ! use ua as 3D workspace USE oce, ONLY : ztrds => va ! use va as 3D workspace !! INTEGER, INTENT( in ) :: kt ! ocean time-step index !! INTEGER :: ji, jj, jk ! dummy loop indices REAL(wp) :: ztest, zta, zsa ! temporary scalars !!---------------------------------------------------------------------- IF( kt == nit000 ) CALL tra_dmp_init ! Initialization IF( l_trdtra ) THEN ! Save ta and sa trends ztrdt(:,:,:) = ta(:,:,:) ztrds(:,:,:) = sa(:,:,:) ENDIF ! 1. Newtonian damping trends on tracer fields ! -------------------------------------------- ! compute the newtonian damping trends depending on nmldmp SELECT CASE ( nmldmp ) ! CASE( 0 ) ! newtonian damping throughout the water column DO jk = 1, jpkm1 DO jj = 2, jpjm1 DO ji = fs_2, fs_jpim1 ! vector opt. zta = resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) ) zsa = resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) ) ! add the trends to the general tracer trends ta(ji,jj,jk) = ta(ji,jj,jk) + zta sa(ji,jj,jk) = sa(ji,jj,jk) + zsa ! save the salinity trend (used in flx to close the salt budget) strdmp(ji,jj,jk) = zsa END DO END DO END DO ! CASE ( 1 ) ! no damping in the turbocline (avt > 5 cm2/s) DO jk = 1, jpkm1 DO jj = 2, jpjm1 DO ji = fs_2, fs_jpim1 ! vector opt. ztest = avt(ji,jj,jk) - 5.e-4 IF( ztest < 0. ) THEN zta = resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) ) zsa = resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) ) ELSE zta = 0.e0 zsa = 0.e0 ENDIF ! add the trends to the general tracer trends ta(ji,jj,jk) = ta(ji,jj,jk) + zta sa(ji,jj,jk) = sa(ji,jj,jk) + zsa ! save the salinity trend (used in flx to close the salt budget) strdmp(ji,jj,jk) = zsa END DO END DO END DO ! CASE ( 2 ) ! no damping in the mixed layer DO jk = 1, jpkm1 DO jj = 2, jpjm1 DO ji = fs_2, fs_jpim1 ! vector opt. IF( fsdept(ji,jj,jk) >= hmlp (ji,jj) ) THEN zta = resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) ) zsa = resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) ) ELSE zta = 0.e0 zsa = 0.e0 ENDIF ! add the trends to the general tracer trends ta(ji,jj,jk) = ta(ji,jj,jk) + zta sa(ji,jj,jk) = sa(ji,jj,jk) + zsa ! save the salinity trend (used in flx to close the salt budget) strdmp(ji,jj,jk) = zsa END DO END DO END DO ! END SELECT IF( l_trdtra ) THEN ! save the damping tracer trends for diagnostic ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:) ztrds(:,:,:) = sa(:,:,:) - ztrds(:,:,:) CALL trd_mod(ztrdt, ztrds, jptra_trd_dmp, 'TRA', kt) ENDIF ! ! Control print IF(ln_ctl) CALL prt_ctl( tab3d_1=ta, clinfo1=' dmp - Ta: ', mask1=tmask, & & tab3d_2=sa, clinfo2= ' Sa: ', mask2=tmask, clinfo3='tra' ) ! END SUBROUTINE tra_dmp SUBROUTINE tra_dmp_init !!---------------------------------------------------------------------- !! *** ROUTINE tra_dmp_init *** !! !! ** Purpose : Initialization for the newtonian damping !! !! ** Method : read the nammbf namelist and check the parameters !! called by tra_dmp at the first timestep (nit000) !!---------------------------------------------------------------------- REWIND ( numnam ) ! Read Namelist namtdp : temperature and salinity damping term READ ( numnam, namtdp ) IF( lzoom ) nmldmp = 0 ! restoring to climatology at closed north or south boundaries IF(lwp) THEN ! Namelist print WRITE(numout,*) WRITE(numout,*) 'tra_dmp : T and S newtonian damping' WRITE(numout,*) '~~~~~~~' WRITE(numout,*) ' Namelist namtdp : set damping parameter' WRITE(numout,*) ' T and S damping option ndmp = ', ndmp WRITE(numout,*) ' create a damping.coeff file ndmpf = ', ndmpf WRITE(numout,*) ' mixed layer damping option nmldmp = ', nmldmp, '(zoom: forced to 0)' WRITE(numout,*) ' surface time scale (days) sdmp = ', sdmp WRITE(numout,*) ' bottom time scale (days) bdmp = ', bdmp WRITE(numout,*) ' depth of transition (meters) hdmp = ', hdmp ENDIF SELECT CASE ( ndmp ) CASE ( -1 ) ; IF(lwp) WRITE(numout,*) ' tracer damping in the Med & Red seas only' CASE ( 1:90 ) ; IF(lwp) WRITE(numout,*) ' tracer damping poleward of', ndmp, ' degrees' CASE DEFAULT WRITE(ctmp1,*) ' bad flag value for ndmp = ', ndmp CALL ctl_stop(ctmp1) END SELECT SELECT CASE ( nmldmp ) CASE ( 0 ) ; IF(lwp) WRITE(numout,*) ' tracer damping throughout the water column' CASE ( 1 ) ; IF(lwp) WRITE(numout,*) ' no tracer damping in the turbocline (avt > 5 cm2/s)' CASE ( 2 ) ; IF(lwp) WRITE(numout,*) ' no tracer damping in the mixed layer' CASE DEFAULT WRITE(ctmp1,*) ' bad flag value for nmldmp = ', nmldmp CALL ctl_stop(ctmp1) END SELECT IF( .NOT.lk_dtasal .OR. .NOT.lk_dtatem ) & & CALL ctl_stop( 'no temperature and/or salinity data define key_dtatem and key_dtasal' ) strdmp(:,:,:) = 0.e0 ! internal damping salinity trend (used in ocesbc) ! ! Damping coefficients initialization IF( lzoom ) THEN ; CALL dtacof_zoom ELSE ; CALL dtacof ENDIF ! END SUBROUTINE tra_dmp_init SUBROUTINE dtacof_zoom !!---------------------------------------------------------------------- !! *** ROUTINE dtacof_zoom *** !! !! ** Purpose : Compute the damping coefficient for zoom domain !! !! ** Method : - set along closed boundary due to zoom a damping over !! 6 points with a max time scale of 5 days. !! - ORCA arctic/antarctic zoom: set the damping along !! south/north boundary over a latitude strip. !! !! ** Action : - resto, the damping coeff. for T and S !!---------------------------------------------------------------------- INTEGER :: ji, jj, jk, jn ! dummy loop indices REAL(wp) :: zlat, zlat0, zlat1, zlat2 ! temporary scalar REAL(wp), DIMENSION(6) :: zfact ! temporary workspace !!---------------------------------------------------------------------- zfact(1) = 1. zfact(2) = 1. zfact(3) = 11./12. zfact(4) = 8./12. zfact(5) = 4./12. zfact(6) = 1./12. zfact(:) = zfact(:) / ( 5. * rday ) ! 5 days max restoring time scale resto(:,:,:) = 0.e0 ! damping along the forced closed boundary over 6 grid-points DO jn = 1, 6 IF( lzoom_w ) resto( mi0(jn+jpizoom):mi1(jn+jpizoom), : , : ) = zfact(jn) ! west closed IF( lzoom_s ) resto( : , mj0(jn+jpjzoom):mj1(jn+jpjzoom), : ) = zfact(jn) ! south closed IF( lzoom_e ) resto( mi0(jpiglo+jpizoom-1-jn):mi1(jpiglo+jpizoom-1-jn) , : , : ) = zfact(jn) ! east closed IF( lzoom_n ) resto( : , mj0(jpjglo+jpjzoom-1-jn):mj1(jpjglo+jpjzoom-1-jn) , : ) = zfact(jn) ! north closed END DO IF( lzoom_arct .AND. lzoom_anta ) THEN ! ! ==================================================== ! ORCA configuration : arctic zoom or antarctic zoom ! ==================================================== IF(lwp) WRITE(numout,*) IF(lwp .AND. lzoom_arct ) WRITE(numout,*) ' dtacof_zoom : ORCA Arctic zoom' IF(lwp .AND. lzoom_arct ) WRITE(numout,*) ' dtacof_zoom : ORCA Antarctic zoom' IF(lwp) WRITE(numout,*) ! ... Initialization : ! zlat0 : latitude strip where resto decreases ! zlat1 : resto = 1 before zlat1 ! zlat2 : resto decreases from 1 to 0 between zlat1 and zlat2 resto(:,:,:) = 0.e0 zlat0 = 10. zlat1 = 30. zlat2 = zlat1 + zlat0 ! ... Compute arrays resto ; value for internal damping : 5 days DO jk = 2, jpkm1 DO jj = 1, jpj DO ji = 1, jpi zlat = ABS( gphit(ji,jj) ) IF ( zlat1 <= zlat .AND. zlat <= zlat2 ) THEN resto(ji,jj,jk) = 0.5 * ( 1./(5.*rday) ) * & ( 1. - cos(rpi*(zlat2-zlat)/zlat0) ) ELSE IF ( zlat < zlat1 ) THEN resto(ji,jj,jk) = 1./(5.*rday) ENDIF END DO END DO END DO ! ENDIF ! ... Mask resto array resto(:,:,:) = resto(:,:,:) * tmask(:,:,:) ! END SUBROUTINE dtacof_zoom SUBROUTINE dtacof !!---------------------------------------------------------------------- !! *** ROUTINE dtacof *** !! !! ** Purpose : Compute the damping coefficient !! !! ** Method : Arrays defining the damping are computed for each grid !! point for temperature and salinity (resto) !! Damping depends on distance to coast, depth and latitude !! !! ** Action : - resto, the damping coeff. for T and S !!---------------------------------------------------------------------- USE iom USE ioipsl !! INTEGER :: ji, jj, jk ! dummy loop indices INTEGER :: itime INTEGER :: ii0, ii1, ij0, ij1 ! " " INTEGER :: idmp ! logical unit for file restoring damping term INTEGER :: icot ! logical unit for file distance to the coast CHARACTER (len=32) :: clname3 REAL(wp) :: zdate0, zinfl, zlon ! temporary scalars REAL(wp) :: zlat, zlat0, zlat1, zlat2 ! " " REAL(wp) :: zsdmp, zbdmp ! " " REAL(wp), DIMENSION(jpk) :: zhfac REAL(wp), DIMENSION(jpi,jpj) :: zmrs REAL(wp), DIMENSION(jpi,jpj,jpk) :: zdct !!---------------------------------------------------------------------- ! ==================================== ! ORCA configuration : global domain ! ==================================== IF(lwp) WRITE(numout,*) IF(lwp) WRITE(numout,*) ' dtacof : Global domain of ORCA' IF(lwp) WRITE(numout,*) ' ------------------------------' ! ... Initialization : ! zdct() : distant to the coastline ! resto() : array of restoring coeff. on T and S resto(:,:,:) = 0.e0 IF ( ndmp > 0 ) THEN ! ------------------------------------ ! Damping poleward of 'ndmp' degrees ! ------------------------------------ IF(lwp) WRITE(numout,*) IF(lwp) WRITE(numout,*) ' Damping poleward of ', ndmp,' deg.' IF(lwp) WRITE(numout,*) ! ... Distance to coast (zdct) IF(lwp) WRITE(numout,*) IF(lwp) WRITE(numout,*) ' dtacof : distance to coast file' CALL iom_open ( 'dist.coast.nc', icot ) IF( icot > 0 ) THEN CALL iom_get ( icot, jpdom_data, 'Tcoast', zdct ) CALL iom_close (icot) ELSE ! ... Compute and save the distance-to-coast array (output in zdct) CALL cofdis( zdct ) ENDIF ! ... Compute arrays resto ! zinfl : distance of influence for damping term ! zlat0 : latitude strip where resto decreases ! zlat1 : resto = 0 between -zlat1 and zlat1 ! zlat2 : resto increases from 0 to 1 between |zlat1| and |zlat2| ! and resto = 1 between |zlat2| and 90 deg. zinfl = 1000.e3 zlat0 = 10 zlat1 = ndmp zlat2 = zlat1 + zlat0 DO jj = 1, jpj DO ji = 1, jpi zlat = ABS( gphit(ji,jj) ) IF ( zlat1 <= zlat .AND. zlat <= zlat2 ) THEN resto(ji,jj,1) = 0.5 * ( 1. - cos(rpi*(zlat-zlat1)/zlat0 ) ) ELSEIF ( zlat > zlat2 ) THEN resto(ji,jj,1) = 1. ENDIF END DO END DO ! ... North Indian ocean (20N/30N x 45E/100E) : resto=0 IF ( ndmp == 20 ) THEN DO jj = 1, jpj DO ji = 1, jpi zlat = gphit(ji,jj) zlon = MOD( glamt(ji,jj), 360. ) IF ( zlat1 < zlat .AND. zlat < zlat2 .AND. & 45. < zlon .AND. zlon < 100. ) THEN resto(ji,jj,1) = 0. ENDIF END DO END DO ENDIF zsdmp = 1./(sdmp * rday) zbdmp = 1./(bdmp * rday) DO jk = 2, jpkm1 DO jj = 1, jpj DO ji = 1, jpi zdct(ji,jj,jk) = MIN( zinfl, zdct(ji,jj,jk) ) ! ... Decrease the value in the vicinity of the coast resto(ji,jj,jk) = resto(ji,jj,1) * 0.5 * ( 1. - COS( rpi*zdct(ji,jj,jk)/zinfl) ) ! ... Vertical variation from zsdmp (sea surface) to zbdmp (bottom) resto(ji,jj,jk) = resto(ji,jj,jk) * ( zbdmp + (zsdmp-zbdmp)*EXP(-fsdept(ji,jj,jk)/hdmp) ) END DO END DO END DO ! ENDIF IF( cp_cfg == "orca" .AND. ( ndmp > 0 .OR. ndmp == -1 ) ) THEN ! ! ========================= ! ! Med and Red Sea damping ! ! ========================= IF(lwp)WRITE(numout,*) IF(lwp)WRITE(numout,*) ' ORCA configuration: Damping in Med and Red Seas' zmrs(:,:) = 0.e0 ! damping term on the Med or Red Sea SELECT CASE ( jp_cfg ) ! ! ======================= CASE ( 4 ) ! ORCA_R4 configuration ! ! ======================= ! Mediterranean Sea ij0 = 50 ; ij1 = 56 ii0 = 81 ; ii1 = 91 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 ij0 = 50 ; ij1 = 55 ii0 = 75 ; ii1 = 80 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 ij0 = 52 ; ij1 = 53 ii0 = 70 ; ii1 = 74 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 ! Smooth transition from 0 at surface to 1./rday at the 18th level in Med and Red Sea DO jk = 1, 17 zhfac (jk) = 0.5*( 1.- COS( rpi*(jk-1)/16. ) ) / rday END DO DO jk = 18, jpkm1 zhfac (jk) = 1./rday END DO ! ! ======================= CASE ( 2 ) ! ORCA_R2 configuration ! ! ======================= ! Mediterranean Sea ij0 = 96 ; ij1 = 110 ii0 = 157 ; ii1 = 181 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 ij0 = 100 ; ij1 = 110 ii0 = 144 ; ii1 = 156 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 ij0 = 100 ; ij1 = 103 ii0 = 139 ; ii1 = 143 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 ! Decrease before Gibraltar Strait ij0 = 101 ; ij1 = 102 ii0 = 139 ; ii1 = 141 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.e0 ii0 = 142 ; ii1 = 142 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 / 90.e0 ii0 = 143 ; ii1 = 143 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.40e0 ii0 = 144 ; ii1 = 144 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.75e0 ! Red Sea ij0 = 87 ; ij1 = 96 ii0 = 147 ; ii1 = 163 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 ! Decrease before Bab el Mandeb Strait ij0 = 91 ; ij1 = 91 ii0 = 153 ; ii1 = 160 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.80e0 ij0 = 90 ; ij1 = 90 ii0 = 153 ; ii1 = 160 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.40e0 ij0 = 89 ; ij1 = 89 ii0 = 158 ; ii1 = 160 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 / 90.e0 ij0 = 88 ; ij1 = 88 ii0 = 160 ; ii1 = 163 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.e0 ! Smooth transition from 0 at surface to 1./rday at the 18th level in Med and Red Sea DO jk = 1, 17 zhfac (jk) = 0.5*( 1.- COS( rpi*(jk-1)/16. ) ) / rday END DO DO jk = 18, jpkm1 zhfac (jk) = 1./rday END DO ! ! ======================= CASE ( 05 ) ! ORCA_R05 configuration ! ! ======================= ! Mediterranean Sea ii0 = 568 ; ii1 = 574 ij0 = 324 ; ij1 = 333 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 ii0 = 575 ; ii1 = 658 ij0 = 314 ; ij1 = 366 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 ! Black Sea (remaining part ii0 = 641 ; ii1 = 651 ij0 = 367 ; ij1 = 372 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 ! Decrease before Gibraltar Strait ij0 = 324 ; ij1 = 333 ii0 = 565 ; ii1 = 565 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 / 90.e0 ii0 = 566 ; ii1 = 566 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.40 ii0 = 567 ; ii1 = 567 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.75 ! Red Sea ii0 = 641 ; ii1 = 665 ij0 = 270 ; ij1 = 310 ; zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 ! Decrease before Bab el Mandeb Strait ii0 = 666 ; ii1 = 675 ij0 = 270 ; ij1 = 290 DO ji = mi0(ii0), mi1(ii1) zmrs( ji , mj0(ij0):mj1(ij1) ) = 0.1 * ABS( FLOAT(ji - mi1(ii1)) ) END DO zsdmp = 1./(sdmp * rday) zbdmp = 1./(bdmp * rday) DO jk = 1, jpk zhfac (jk) = ( zbdmp + (zsdmp-zbdmp) * EXP(-fsdept(1,1,jk)/hdmp) ) END DO ! ! ======================== CASE ( 025 ) ! ORCA_R025 configuration ! ! ======================== CALL ctl_stop( ' Not yet implemented in ORCA_R025' ) ! END SELECT DO jk = 1, jpkm1 resto(:,:,jk) = zmrs(:,:) * zhfac(jk) + ( 1. - zmrs(:,:) ) * resto(:,:,jk) END DO ! Mask resto array and set to 0 first and last levels resto(:,:, : ) = resto(:,:,:) * tmask(:,:,:) resto(:,:, 1 ) = 0.e0 resto(:,:,jpk) = 0.e0 ELSE ! ------------ ! No damping ! ------------ CALL ctl_stop( 'Choose a correct value of ndmp or DO NOT defined key_tradmp' ) ENDIF ! ---------------------------- ! Create Print damping array ! ---------------------------- ! ndmpf : = 1 create a damping.coeff NetCDF file IF( ndmpf == 1 ) THEN IF(lwp) WRITE(numout,*) ' create damping.coeff.nc file' itime = 0 clname3 = 'damping.coeff' CALL ymds2ju( 0 , 1 , 1 , 0.e0 , zdate0 ) CALL restini( 'NONE', jpi , jpj , glamt, gphit, & & jpk , gdept_0, clname3, itime, zdate0, & & rdt , idmp, domain_id=nidom ) CALL restput( idmp, 'Resto', jpi, jpj, jpk, & & 0 , resto ) CALL restclo( idmp ) ENDIF ! END SUBROUTINE dtacof SUBROUTINE cofdis( pdct ) !!---------------------------------------------------------------------- !! *** ROUTINE cofdis *** !! !! ** Purpose : Compute the distance between ocean T-points and the !! ocean model coastlines. Save the distance in a NetCDF file. !! !! ** Method : For each model level, the distance-to-coast is !! computed as follows : !! - The coastline is defined as the serie of U-,V-,F-points !! that are at the ocean-land bound. !! - For each ocean T-point, the distance-to-coast is then !! computed as the smallest distance (on the sphere) between the !! T-point and all the coastline points. !! - For land T-points, the distance-to-coast is set to zero. !! C A U T I O N : Computation not yet implemented in mpp case. !! !! ** Action : - pdct, distance to the coastline (argument) !! - NetCDF file 'dist.coast.nc' !!---------------------------------------------------------------------- USE ioipsl ! IOipsl librairy !! REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( out ) :: pdct ! distance to the coastline !! INTEGER :: ji, jj, jk, jl ! dummy loop indices INTEGER :: iju, ijt ! temporary integers INTEGER :: icoast, itime INTEGER :: icot ! logical unit for file distance to the coast LOGICAL, DIMENSION(jpi,jpj) :: llcotu, llcotv, llcotf ! ??? CHARACTER (len=32) :: clname REAL(wp) :: zdate0 REAL(wp), DIMENSION(jpi,jpj) :: zxt, zyt, zzt, zmask ! cartesian coordinates for T-points REAL(wp), DIMENSION(3*jpi*jpj) :: zxc, zyc, zzc, zdis ! temporary workspace !!---------------------------------------------------------------------- ! 0. Initialization ! ----------------- IF(lwp) WRITE(numout,*) IF(lwp) WRITE(numout,*) 'cofdis : compute the distance to coastline' IF(lwp) WRITE(numout,*) '~~~~~~' IF(lwp) WRITE(numout,*) IF( lk_mpp ) & & CALL ctl_stop(' Computation not yet implemented with key_mpp_...', & & ' Rerun the code on another computer or ', & & ' create the "dist.coast.nc" file using IDL' ) pdct(:,:,:) = 0.e0 zxt(:,:) = cos( rad * gphit(:,:) ) * cos( rad * glamt(:,:) ) zyt(:,:) = cos( rad * gphit(:,:) ) * sin( rad * glamt(:,:) ) zzt(:,:) = sin( rad * gphit(:,:) ) ! 1. Loop on vertical levels ! -------------------------- ! ! =============== DO jk = 1, jpkm1 ! Horizontal slab ! ! =============== ! Define the coastline points (U, V and F) DO jj = 2, jpjm1 DO ji = 2, jpim1 zmask(ji,jj) = ( tmask(ji,jj+1,jk) + tmask(ji+1,jj+1,jk) & & + tmask(ji,jj ,jk) + tmask(ji+1,jj ,jk) ) llcotu(ji,jj) = ( tmask(ji,jj, jk) + tmask(ji+1,jj ,jk) == 1. ) llcotv(ji,jj) = ( tmask(ji,jj ,jk) + tmask(ji ,jj+1,jk) == 1. ) llcotf(ji,jj) = ( zmask(ji,jj) > 0. ) .AND. ( zmask(ji,jj) < 4. ) END DO END DO ! Lateral boundaries conditions llcotu(:, 1 ) = umask(:, 2 ,jk) == 1 llcotu(:,jpj) = umask(:,jpjm1,jk) == 1 llcotv(:, 1 ) = vmask(:, 2 ,jk) == 1 llcotv(:,jpj) = vmask(:,jpjm1,jk) == 1 llcotf(:, 1 ) = fmask(:, 2 ,jk) == 1 llcotf(:,jpj) = fmask(:,jpjm1,jk) == 1 IF( nperio == 1 .OR. nperio == 4 .OR. nperio == 6 ) THEN llcotu( 1 ,:) = llcotu(jpim1,:) llcotu(jpi,:) = llcotu( 2 ,:) llcotv( 1 ,:) = llcotv(jpim1,:) llcotv(jpi,:) = llcotv( 2 ,:) llcotf( 1 ,:) = llcotf(jpim1,:) llcotf(jpi,:) = llcotf( 2 ,:) ELSE llcotu( 1 ,:) = umask( 2 ,:,jk) == 1 llcotu(jpi,:) = umask(jpim1,:,jk) == 1 llcotv( 1 ,:) = vmask( 2 ,:,jk) == 1 llcotv(jpi,:) = vmask(jpim1,:,jk) == 1 llcotf( 1 ,:) = fmask( 2 ,:,jk) == 1 llcotf(jpi,:) = fmask(jpim1,:,jk) == 1 ENDIF IF( nperio == 3 .OR. nperio == 4 ) THEN DO ji = 1, jpim1 iju = jpi - ji + 1 llcotu(ji,jpj ) = llcotu(iju,jpj-2) llcotf(ji,jpjm1) = llcotf(iju,jpj-2) llcotf(ji,jpj ) = llcotf(iju,jpj-3) END DO DO ji = jpi/2, jpim1 iju = jpi - ji + 1 llcotu(ji,jpjm1) = llcotu(iju,jpjm1) END DO DO ji = 2, jpi ijt = jpi - ji + 2 llcotv(ji,jpjm1) = llcotv(ijt,jpj-2) llcotv(ji,jpj ) = llcotv(ijt,jpj-3) END DO ENDIF IF( nperio == 5 .OR. nperio == 6 ) THEN DO ji = 1, jpim1 iju = jpi - ji llcotu(ji,jpj ) = llcotu(iju,jpjm1) llcotf(ji,jpj ) = llcotf(iju,jpj-2) END DO DO ji = jpi/2, jpim1 iju = jpi - ji llcotf(ji,jpjm1) = llcotf(iju,jpjm1) END DO DO ji = 1, jpi ijt = jpi - ji + 1 llcotv(ji,jpj ) = llcotv(ijt,jpjm1) END DO DO ji = jpi/2+1, jpi ijt = jpi - ji + 1 llcotv(ji,jpjm1) = llcotv(ijt,jpjm1) END DO ENDIF ! Compute cartesian coordinates of coastline points ! and the number of coastline points icoast = 0 DO jj = 1, jpj DO ji = 1, jpi IF( llcotf(ji,jj) ) THEN icoast = icoast + 1 zxc(icoast) = COS( rad*gphif(ji,jj) ) * COS( rad*glamf(ji,jj) ) zyc(icoast) = COS( rad*gphif(ji,jj) ) * SIN( rad*glamf(ji,jj) ) zzc(icoast) = SIN( rad*gphif(ji,jj) ) ENDIF IF( llcotu(ji,jj) ) THEN icoast = icoast+1 zxc(icoast) = COS( rad*gphiu(ji,jj) ) * COS( rad*glamu(ji,jj) ) zyc(icoast) = COS( rad*gphiu(ji,jj) ) * SIN( rad*glamu(ji,jj) ) zzc(icoast) = SIN( rad*gphiu(ji,jj) ) ENDIF IF( llcotv(ji,jj) ) THEN icoast = icoast+1 zxc(icoast) = COS( rad*gphiv(ji,jj) ) * COS( rad*glamv(ji,jj) ) zyc(icoast) = COS( rad*gphiv(ji,jj) ) * SIN( rad*glamv(ji,jj) ) zzc(icoast) = SIN( rad*gphiv(ji,jj) ) ENDIF END DO END DO ! Distance for the T-points DO jj = 1, jpj DO ji = 1, jpi IF( tmask(ji,jj,jk) == 0. ) THEN pdct(ji,jj,jk) = 0. ELSE DO jl = 1, icoast zdis(jl) = ( zxt(ji,jj) - zxc(jl) )**2 & & + ( zyt(ji,jj) - zyc(jl) )**2 & & + ( zzt(ji,jj) - zzc(jl) )**2 END DO pdct(ji,jj,jk) = ra * SQRT( MINVAL( zdis(1:icoast) ) ) ENDIF END DO END DO ! ! =============== END DO ! End of slab ! ! =============== ! 2. Create the distance to the coast file in NetCDF format ! ---------------------------------------------------------- clname = 'dist.coast' itime = 0 CALL ymds2ju( 0 , 1 , 1 , 0.e0 , zdate0 ) CALL restini( 'NONE', jpi , jpj , glamt, gphit , & & jpk , gdept_0, clname, itime, zdate0, & & rdt , icot ) CALL restput( icot, 'Tcoast', jpi, jpj, jpk, 0, pdct ) CALL restclo( icot ) END SUBROUTINE cofdis #else !!---------------------------------------------------------------------- !! Default key NO internal damping !!---------------------------------------------------------------------- LOGICAL , PUBLIC, PARAMETER :: lk_tradmp = .FALSE. !: internal damping flag CONTAINS SUBROUTINE tra_dmp( kt ) ! Empty routine WRITE(*,*) 'tra_dmp: You should not have seen this print! error?', kt END SUBROUTINE tra_dmp #endif !!====================================================================== END MODULE tradmp