[MITgcm-support] NaNQ
Patrick Rosendahl
Patrick.Rosendahl at zmaw.de
Tue Mar 20 11:47:06 EDT 2007
Sergey Vinogradov wrote:
> Hi
> Does anyone know how to make MITgcm break its execution once it starts
> to produce NaNQs? I'm not sure if it is platform/compiler- dependent;
> NaNQs are being dumped if a numerical instability is encountered (or by
> some other reasons??) but the model continues to run further and burn
> precious CPU time.
> Thanks,
>
Had the same problems here. Assuming that instabilities occur in the
velocity variables result in NaNs also in the Temperature, I modded the
monitor package to check for very large and very negative values. If you
are unsure about the stability, use a small value for the "monitorFreq"
variable in PARM03.
---------
C $Header: /u/gcmpack/MITgcm/pkg/monitor/mon_solution.F,v 1.4 2004/11/10
20:53:13 jmc Exp $
C $Name: $
#include "MONITOR_OPTIONS.h"
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
CBOP
C !ROUTINE: MON_SOLUTION
C !INTERFACE:
SUBROUTINE MON_SOLUTION(
I statsTemp,
I myTime, myIter, myThid )
C !DESCRIPTION:
C Checks that the solutions is within bounds
C patros: Check for NaNs
C !USES:
IMPLICIT NONE
#include "SIZE.h"
#include "EEPARAMS.h"
#include "PARAMS.h"
#include "DYNVARS.h"
#include "GRID.h"
#include "MONITOR.h"
C !INPUT PARAMETERS:
_RL statsTemp(*)
_RL myTime
INTEGER myIter
INTEGER myThid
CEOP
C !LOCAL VARIABLES:
CHARACTER*(MAX_LEN_MBUF) msgBuf
_RL tMin,tMax,tMean,tSD,tDel2,tVol,big
IF ( statsTemp(1) .LE. statsTemp(2) ) THEN
C take statistics from the input argument "statsTemp":
tMin = statsTemp(1)
tMax = statsTemp(2)
ELSE
C Statistics for T
CALL MON_STATS_RL(
I Nr, theta, maskC,hFacC,rA,drF,
O tMin,tMax,tMean,tSD,tDel2,tVol,
I myThid )
ENDIF
C Check for NaN
big=1d33
IF ( .NOT. tMax.GT.-big.AND.tMax.LT.big ) THEN
_BEGIN_MASTER(myThid)
WRITE(msgBuf,'(A,1P2E12.3)')
& 'SOLUTION IS OUT OF BOUNDS: tMin,tMax=',tMin,tMax
CALL PRINT_MESSAGE(msgBuf,errorMessageUnit,SQUEEZE_RIGHT, 1)
WRITE(msgBuf,'(A)') 'MON_SOLUTION: STOPPING CALCULATION'
CALL PRINT_MESSAGE(msgBuf,errorMessageUnit,SQUEEZE_RIGHT, 1)
_END_MASTER(myThid)
C jmc: add this "if not ..." to avoid beeing stuck when using coupler;
IF ( .NOT. useCoupler ) CALL EEDIE
STOP 'MON_SOLUTION: STOPPED DUE TO EXTREME VALUES OF SOLUTION'
ENDIF
IF (tMax-tMin.GT.1.e3) THEN
_BEGIN_MASTER(myThid)
WRITE(msgBuf,'(A,1P2E12.3)')
& 'SOLUTION IS HEADING OUT OF BOUNDS: tMin,tMax=',tMin,tMax
CALL PRINT_MESSAGE(msgBuf,errorMessageUnit,SQUEEZE_RIGHT, 1)
WRITE(msgBuf,'(A)') 'MON_SOLUTION: STOPPING CALCULATION'
CALL PRINT_MESSAGE(msgBuf,errorMessageUnit,SQUEEZE_RIGHT, 1)
_END_MASTER(myThid)
C jmc: add this "if not ..." to avoid beeing stuck when using coupler;
IF ( .NOT. useCoupler ) CALL EEDIE
STOP 'MON_SOLUTION: STOPPED DUE TO EXTREME VALUES OF SOLUTION'
ENDIF
RETURN
END
More information about the MITgcm-support
mailing list