Back to home page

MITgcm

 
 

    


File indexing completed on 2018-03-02 18:37:28 UTC

view on githubraw file Latest commit add29e06 on 2018-01-31 20:35:05 UTC
09a6f3668a Jeff*0001 #include "ctrparam.h"
                0002 #include "ATM2D_OPTIONS.h"
9274434acc Jean*0003       SUBROUTINE ATM2D_WRITE_PICKUP(
                0004      I     modelEnd,
                0005      I     myTime,
                0006      I     myIter,
09a6f3668a Jeff*0007      I     myThid )
                0008 
                0009 C     *==========================================================*
                0010 C     | Write pickup files for atm2d package which needs it to   |
                0011 C     |restart. It writes both "rolling-checkpoint" files (ckptA,|
                0012 C     |ckptB) and permanent checkpoint files. NOT called from    |
                0013 C     |the usual MITGCM WRITE_PICKUP routine in forward step, as |
                0014 C     |NORM_OCN_FLUXES must be done before these fluxes are ready|
                0015 C     *==========================================================*
                0016 
9274434acc Jean*0017 C     Note this routine was pilfered from the MITGCM code prior to
09a6f3668a Jeff*0018 C     JMC's changes in 8/06.
                0019 
                0020 C     !USES:
                0021       IMPLICIT NONE
                0022 #include "SIZE.h"
                0023 #include "EEPARAMS.h"
                0024 #include "PARAMS.h"
41e10ac353 Jean*0025 #include "RESTART.h"
09a6f3668a Jeff*0026 
                0027       LOGICAL  DIFFERENT_MULTIPLE
                0028       EXTERNAL DIFFERENT_MULTIPLE
                0029       INTEGER  IO_ERRCOUNT
                0030       EXTERNAL IO_ERRCOUNT
                0031 
                0032 C     !INPUT/OUTPUT PARAMETERS:
                0033 C     == Routine arguments ==
                0034 C     modelEnd    :: Checkpoint call at end of model run.
                0035 C     myThid :: Thread number for this instance of the routine.
                0036 C     myIter :: Iteration number
                0037 C     myTime :: Current time of simulation ( s )
9274434acc Jean*0038       LOGICAL modelEnd
09a6f3668a Jeff*0039       INTEGER myThid
                0040       INTEGER myIter
                0041       _RL     myTime
                0042 
                0043 C     !LOCAL VARIABLES:
                0044 C     == Local variables ==
                0045 C     permCheckPoint :: Flag indicating whether a permanent checkpoint will
                0046 C                       be written.
                0047 C     tempCheckPoint :: Flag indicating if it is time to write a non-permanent
                0048 C                       checkpoint (that will be permanent if permCheckPoint=T)
9274434acc Jean*0049       LOGICAL permCheckPoint, tempCheckPoint
09a6f3668a Jeff*0050 CEOP
                0051 
                0052       permCheckPoint = .FALSE.
                0053       tempCheckPoint = .FALSE.
                0054       permCheckPoint=
                0055      &     DIFFERENT_MULTIPLE(pChkPtFreq,myTime,deltaTClock)
                0056       tempCheckPoint=
                0057      &     DIFFERENT_MULTIPLE( chkPtFreq,myTime,deltaTClock)
                0058 
                0059 #ifdef ALLOW_CAL
                0060       IF ( useCAL ) THEN
7a31080eb8 Jean*0061          CALL CAL_TIME2DUMP( zeroRL, pChkPtFreq, deltaTClock,
09a6f3668a Jeff*0062      U                       permCheckPoint,
                0063      I                       myTime, myIter, myThid )
7a31080eb8 Jean*0064          CALL CAL_TIME2DUMP( zeroRL, chkPtFreq,  deltaTClock,
09a6f3668a Jeff*0065      U                       tempCheckPoint,
                0066      I                       myTime, myIter, myThid )
                0067       ENDIF
                0068 #endif /* ALLOW_CAL */
                0069 
                0070       IF (
                0071      &     ( .NOT.modelEnd .AND. (permCheckPoint.OR.tempCheckPoint) )
                0072      &     .OR.
7b5b62b00f Jeff*0073      &     ( modelEnd .AND. .NOT.(permCheckPoint.OR.tempCheckPoint) )
09a6f3668a Jeff*0074      &     ) THEN
                0075 
                0076         IF (tempCheckPoint)   !toggle was done prematurely...
                0077      &       nCheckLev = MOD(nCheckLev, maxNoChkptLev)+1
                0078 
9274434acc Jean*0079         CALL ATM2D_WRITE_PICKUP_NOW(
09a6f3668a Jeff*0080      &       permCheckPoint, myTime, myIter, myThid )
                0081 
                0082         IF (tempCheckPoint)   !note this works for A/B chpt only
                0083      &       nCheckLev = MOD(nCheckLev, maxNoChkptLev)+1
                0084 
                0085       ENDIF
                0086 
                0087       RETURN
                0088       END
                0089 
                0090 
                0091 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0092 #include "ctrparam.h"
                0093 #include "ATM2D_OPTIONS.h"
                0094 CBOP
                0095 C     !ROUTINE: ATM2D_WRITE_PICKUP_NOW
                0096 
                0097 C     !INTERFACE:
9274434acc Jean*0098       SUBROUTINE ATM2D_WRITE_PICKUP_NOW(
                0099      I     permCheckPoint,
                0100      I     myTime,
                0101      I     myIter,
09a6f3668a Jeff*0102      I     myThid )
                0103 
                0104 C     !DESCRIPTION:
                0105 C     Write pickup files for atm2d package which needs it to restart and
                0106 C     do it NOW.
                0107 
                0108 C     !USES:
                0109       IMPLICIT NONE
                0110 #include "ATMSIZE.h"
                0111 #include "SIZE.h"
                0112 #include "EEPARAMS.h"
                0113 #include "PARAMS.h"
b38881c85b Jeff*0114 #include "RESTART.h"
09a6f3668a Jeff*0115 #include "THSICE_VARS.h"
                0116 #include "ATM2D_VARS.h"
                0117 
                0118 
                0119 C     !INPUT/OUTPUT PARAMETERS:
                0120 C     permCheckPoint  :: Checkpoint is permanent
                0121 C     myThid :: Thread number for this instance of the routine.
                0122 C     myIter :: Iteration number
                0123 C     myTime :: Current time of simulation ( s )
                0124       LOGICAL permCheckPoint
                0125       INTEGER myThid
                0126       INTEGER myIter
                0127       _RL     myTime
                0128 
                0129 C     == Common blocks ==
                0130       COMMON /PCKP_GBLFLS/ globalFile
                0131       LOGICAL globalFile
                0132 
                0133 C     !LOCAL VARIABLES:
                0134 C     == Local variables ==
                0135 C     oldPrc :: Temp. for holding I/O precision
                0136 C     fn     :: Temp. for building file name string.
                0137       CHARACTER*(MAX_LEN_FNAM) fn
                0138       INTEGER prec, i,j
                0139 CEOP
                0140 
                0141       prec = precFloat64
9274434acc Jean*0142 
09a6f3668a Jeff*0143 C     Create suffix to pass on to package pickup routines
                0144       IF ( permCheckPoint ) THEN
                0145        WRITE(fn,'(A,I10.10)') 'pickup_atm2d.',myIter
                0146       ELSE
                0147        WRITE(fn,'(A,A)') 'pickup_atm2d.',checkPtSuff(nCheckLev)
                0148       ENDIF
                0149 
9f24b0ff20 Jean*0150       CALL WRITE_REC_3D_RL( fn,prec,1,pass_slp,      1,myIter,myThid )
                0151       CALL WRITE_REC_3D_RL( fn,prec,1,pass_qnet,     2,myIter,myThid )
                0152       CALL WRITE_REC_3D_RL( fn,prec,1,pass_solarnet, 3,myIter,myThid )
                0153       CALL WRITE_REC_3D_RL( fn,prec,1,pass_fu,       4,myIter,myThid )
                0154       CALL WRITE_REC_3D_RL( fn,prec,1,pass_fv,       5,myIter,myThid )
                0155       CALL WRITE_REC_3D_RL( fn,prec,1,pass_precip,   6,myIter,myThid )
                0156       CALL WRITE_REC_3D_RL( fn,prec,1,pass_evap,     7,myIter,myThid )
                0157       CALL WRITE_REC_3D_RL( fn,prec,1,pass_runoff,   8,myIter,myThid )
                0158       CALL WRITE_REC_3D_RL( fn,prec,1,pass_wspeed,   9,myIter,myThid )
                0159       CALL WRITE_REC_3D_RL( fn,prec,1,pass_pCO2,    10,myIter,myThid )
                0160       CALL WRITE_REC_3D_RL( fn,prec,1,pass_sIceLoad,11,myIter,myThid )
                0161 
                0162       CALL WRITE_REC_3D_RL( fn,prec,1,sHeating,     12,myIter,myThid )
                0163       CALL WRITE_REC_3D_RL( fn,prec,1,flxCndBt,     13,myIter,myThid )
                0164       CALL WRITE_REC_3D_RL( fn,prec,1,pass_prcAtm,  14,myIter,myThid )
                0165       CALL WRITE_REC_3D_RL( fn,prec,1,snowPrc,      15,myIter,myThid )
                0166       CALL WRITE_REC_3D_RL( fn,prec,1,icFrwAtm,     16,myIter,myThid )
                0167       CALL WRITE_REC_3D_RL( fn,prec,1,icFlxSw,      17,myIter,myThid )
                0168       CALL WRITE_REC_3D_RL( fn,prec,1,siceAlb,      18,myIter,myThid )
09a6f3668a Jeff*0169 
                0170       RETURN
                0171       END
                0172