Skip to content

Commit

Permalink
major changes to relaxation coefficient setting:
Browse files Browse the repository at this point in the history
- rename parameters cheapaml_taurelax & cheapaml_taurelaxocean (in days)
  to cheap_tauRelax & cheap_tauRelaxOce (now in seconds);
- if using cheapMaskFile, set relaxation coeff to: cheapMask/tauRelax
  (instead of 1/cheapMask over ocean and 1/tauRelax over land);
- with cheapMaskFile unset: set relaxation coeff according to land/ocean mask
  (unchanged) but skip increase near domain edges for periodic domain (in X
  or Y dir) when cheapamlX/Yperiodic=T ; also fix linear increase (over
  Cheapaml_mask_width grid points) of coeff towards domain edges (previously
  was increasing away from edges). Update output of experiment "cheapAML_box".
Leave old code under #ifdef CHEAPAML_OLD_MASK_SETTING / #endif
  • Loading branch information
jm-c committed Oct 13, 2017
1 parent 2d31068 commit f0e2fa5
Showing 1 changed file with 108 additions and 5 deletions.
113 changes: 108 additions & 5 deletions pkg/cheapaml/cheapaml_init_fixed.F
@@ -1,7 +1,8 @@
C $Header: /u/gcmpack/MITgcm/pkg/cheapaml/cheapaml_init_fixed.F,v 1.7 2017/10/12 15:40:07 jmc Exp $
C $Header: /u/gcmpack/MITgcm/pkg/cheapaml/cheapaml_init_fixed.F,v 1.8 2017/10/13 17:48:03 jmc Exp $
C $Name: $

#include "CHEAPAML_OPTIONS.h"
#undef CHEAPAML_OLD_MASK_SETTING

CBOP
C !ROUTINE: CHEAPAML_INIT_FIXED
Expand Down Expand Up @@ -42,12 +43,15 @@ SUBROUTINE CHEAPAML_INIT_FIXED( myThid )
INTEGER i, j
INTEGER iG,jG
INTEGER xmw
_RL xmf
_RL recipMW
_RL xmf, tmpVar
_RL relaxMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
_RL xgs (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
INTEGER iL, ioUnit
CHARACTER*(MAX_LEN_MBUF) msgBuf
#ifdef CHEAPAML_OLD_MASK_SETTING
_RL recipMW
_RL cheapaml_taurelax, cheapaml_taurelaxocean
#endif /* CHEAPAML_OLD_MASK_SETTING */
CEOP

C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
Expand All @@ -66,6 +70,10 @@ SUBROUTINE CHEAPAML_INIT_FIXED( myThid )
ENDDO
ENDDO

#ifdef CHEAPAML_OLD_MASK_SETTING
cheapaml_taurelax = cheap_tauRelax /86400. _d 0
cheapaml_taurelaxocean = cheap_tauRelaxOce/86400. _d 0

c-- Setup CheapAML mask (for relaxation):
C Do mask
IF ( cheapMaskFile .NE. ' ') THEN
Expand Down Expand Up @@ -148,9 +156,104 @@ SUBROUTINE CHEAPAML_INIT_FIXED( myThid )
ENDDO
ENDDO
ENDDO
c _EXCH_XY_RL( xgs, myThid )
c _EXCH_XY_RL( xrelf, myThid )

#else /* CHEAPAML_OLD_MASK_SETTING */

C-- Setup CheapAML mask (for relaxation):
IF ( cheapMaskFile .NE. ' ' ) THEN
C- read mask from file
iL = ILNBLNK(cheapMaskFile)
WRITE(msgBuf,'(4A)') 'CHEAPAML_INIT_VARIA: ',
& 'Relaxation Mask read from ->', cheapMaskFile(1:iL), '<-'
CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
CALL READ_FLD_XY_RL( cheapMaskFile,' ',relaxMask,0,myThid )
ELSE
WRITE(msgBuf,'(4A)') 'CHEAPAML_INIT_VARIA: ',
& 'Generate Cheapaml mask'
CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
DO bj = myByLo(myThid), myByHi(myThid)
DO bi = myBxLo(myThid), myBxHi(myThid)
C- set mask according to boundaries
IF ( Cheapaml_mask_width.LE.0 .OR.
& ( cheapamlXperiodic .AND. cheapamlYperiodic ) ) THEN
DO j=1,sNy
DO i=1,sNx
relaxMask(i,j,bi,bj) = 0.
ENDDO
ENDDO
ELSE
xmw = Cheapaml_mask_width
tmpVar = xmw
tmpVar = oneRL / tmpVar
DO j=1,sNy
DO i=1,sNx
xmf = 0. _d 0
iG = myXGlobalLo-1+(bi-1)*sNx+i
jG = myYGlobalLo-1+(bj-1)*sNy+j
IF ( .NOT.cheapamlXperiodic ) THEN
IF (iG.LE.xmw) xmf = oneRL - (iG-1 )*tmpVar
IF (iG.GE.Nx-xmw+1) xmf = oneRL - (Nx-iG)*tmpVar
ENDIF
IF ( .NOT.cheapamlYperiodic ) THEN
IF (jG.LE.xmw)
& xmf = MAX( xmf, oneRL - (jG-1 )*tmpVar )
IF (jG.GE.Ny-xmw+1)
& xmf = MAX( xmf, oneRL - (Ny-jG)*tmpVar )
ENDIF
relaxMask(i,j,bi,bj) = xmf
ENDDO
ENDDO
ENDIF
C- set mask to one over land:
DO j=1,sNy
DO i=1,sNx
relaxMask(i,j,bi,bj) = MAX( relaxMask(i,j,bi,bj),
& (oneRL - maskC(i,j,1,bi,bj)) )
ENDDO
ENDDO
ENDDO
ENDDO
ENDIF
_EXCH_XY_RL( relaxMask, myThid )

_EXCH_XY_RL( xgs, myThid )
_EXCH_XY_RL( xrelf, myThid )
C- Set relaxation coeff "xgs"
DO bj = myByLo(myThid), myByHi(myThid)
DO bi = myBxLo(myThid), myBxHi(myThid)
IF ( cheap_tauRelax .LE. zeroRL ) THEN
DO j=1-OLy,sNy+OLy
DO i=1-OLx,sNx+OLx
xgs(i,j,bi,bj) = 0. _d 0
ENDDO
ENDDO
ELSE
tmpVar = oneRL/cheap_tauRelax
DO j=1-OLy,sNy+OLy
DO i=1-OLx,sNx+OLx
xgs(i,j,bi,bj) = relaxMask(i,j,bi,bj)*tmpVar
ENDDO
ENDDO
ENDIF
IF ( cheap_tauRelaxOce .GT. zeroRL
& .AND. cheapMaskFile .EQ. ' ' ) THEN
tmpVar = oneRL/cheap_tauRelaxOce
DO j=1-OLy,sNy+OLy
DO i=1-OLx,sNx+OLx
xgs(i,j,bi,bj) = MAX( xgs(i,j,bi,bj), tmpVar )
ENDDO
ENDDO
ENDIF
C- Calculate implicit relaxation factor "xrelf"
DO j=1-OLy,sNy+OLy
DO i=1-OLx,sNx+OLx
tmpVar = xgs(i,j,bi,bj)*deltaT
xrelf(i,j,bi,bj)= tmpVar/( oneRL + tmpVar )
ENDDO
ENDDO
ENDDO
ENDDO
#endif /* CHEAPAML_OLD_MASK_SETTING */

IF ( debugLevel.GE.debLevB .AND. nIter0.EQ.0 ) THEN
CALL WRITE_FLD_XY_RL('CheapMask', ' ', relaxMask, 0, myThid )
Expand Down

0 comments on commit f0e2fa5

Please sign in to comment.