/[MITgcm]/MITgcm/pkg/ptracers/ptracers_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/ptracers/ptracers_readparms.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.4 - (hide annotations) (download)
Thu Nov 13 06:35:15 2003 UTC (20 years, 6 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, hrcube5, checkpoint52d_pre, checkpoint52j_pre, checkpoint52k_post, checkpoint54, checkpoint53, checkpoint52f_post, checkpoint52i_pre, hrcube_1, hrcube_2, hrcube_3, checkpoint52e_pre, checkpoint52e_post, checkpoint53d_post, checkpoint52b_pre, checkpoint54b_post, checkpoint52m_post, checkpoint52b_post, checkpoint52c_post, checkpoint52f_pre, checkpoint54a_pre, checkpoint53c_post, checkpoint54a_post, checkpoint53a_post, checkpoint52d_post, checkpoint53g_post, checkpoint52i_post, checkpoint52h_pre, checkpoint53f_post, checkpoint52j_post, branch-netcdf, checkpoint52l_post, checkpoint52n_post, checkpoint53b_pre, checkpoint53b_post, checkpoint52a_post, checkpoint53d_pre
Branch point for: netcdf-sm0
Changes since 1.3: +2 -1 lines
o modifications to make FREEZE flux visible to pkg/kpp
  - moved surfaceTendencyTice from pkg/seaice to main code
  - FREEZE moved to FORWARD_STEP
  - subroutine FREEZE now limits only surface temperature
    this means new output.txt for global_ocean.90x40x15,
    global_ocean.cs32x15, and global_with_exf, but note
    that results for these three experiments remain
    bit-identical to before if allowFreezing=.FALSE.
o added surface flux output variables to TIMEAVE_STATVARS
o time-averaged output for pkg/ptracers

1 dimitri 1.4 C $Header: /usr/local/gcmpack/MITgcm/pkg/ptracers/ptracers_readparms.F,v 1.3 2003/09/27 07:45:51 dimitri Exp $
2 dimitri 1.2 C $Name: $
3 adcroft 1.1
4     #include "PTRACERS_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: PTRACERS_READPARMS
8    
9     C !INTERFACE: ==========================================================
10     SUBROUTINE PTRACERS_READPARMS( myThid )
11    
12     C !DESCRIPTION:
13     C Initialize PTRACERS parameters, read in data.ptracers
14    
15     C !USES: ===============================================================
16     IMPLICIT NONE
17     #include "SIZE.h"
18     #include "EEPARAMS.h"
19     #include "PTRACERS.h"
20 dimitri 1.2 #include "PARAMS.h"
21 adcroft 1.1
22     C !INPUT PARAMETERS: ===================================================
23     C myThid :: thread number
24     INTEGER myThid
25    
26     C !OUTPUT PARAMETERS: ==================================================
27     C none
28    
29     #ifdef ALLOW_PTRACERS
30    
31     C !LOCAL VARIABLES: ====================================================
32     C iTracer :: loop indices
33     C iUnit :: unit number for I/O
34     C msgBuf :: message buffer
35     INTEGER iTracer
36     INTEGER iUnit
37     CHARACTER*(MAX_LEN_MBUF) msgBuf
38     CEOP
39    
40     C This routine has been called by the main model so we set our
41     C internal flag to indicate we are in business
42     PTRACERSisON=.TRUE.
43    
44     C Set defaults values for parameters in PTRACERS.h
45 dimitri 1.4 PTRACERS_taveFreq=taveFreq
46 adcroft 1.1 PTRACERS_numInUse=-1
47     DO iTracer=1,PTRACERS_num
48 dimitri 1.2 PTRACERS_advScheme(iTracer)=saltAdvScheme
49     PTRACERS_diffKh(iTracer)=diffKhS
50     PTRACERS_diffK4(iTracer)=diffK4S
51     PTRACERS_diffKr(iTracer)=diffKrS
52     PTRACERS_useGMRedi(iTracer)=useGMRedi
53     PTRACERS_useKPP(iTracer)=useKPP
54 adcroft 1.1 PTRACERS_initialFile(iTracer)=' '
55     ENDDO
56 dimitri 1.3 PTRACERS_useRecords=.FALSE.
57 adcroft 1.1
58     C Open and read the data.ptracers file
59     _BEGIN_MASTER(myThid)
60     WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'
61     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
62     & SQUEEZE_RIGHT , 1)
63     CALL OPEN_COPY_DATA_FILE(
64     I 'data.ptracers', 'PTRACERS_READPARMS',
65     O iUnit,
66     I myThid )
67     READ(UNIT=iUnit,NML=PTRACERS_PARM01)
68     WRITE(msgBuf,'(A)')
69     & ' PTRACERS_READPARMS: finished reading data.ptracers'
70     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
71     & SQUEEZE_RIGHT , 1)
72    
73     C Close the open data file
74     CLOSE(iUnit)
75     _END_MASTER(myThid)
76    
77     C Everyone else must wait for the parameters to be loaded
78     _BARRIER
79    
80     C Now set-up any remaining parameters that result from the input parameters
81    
82     C If PTRACERS_numInUse was not set in data.ptracers then we can assume
83     C that all PTRACERS fields will be in use
84     IF (PTRACERS_numInUse.LT.0) THEN
85     PTRACERS_numInUse=PTRACERS_num
86     ENDIF
87     C Check we are not trying to use more tracers than allowed
88     IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN
89     WRITE(msgBuf,'(A,I2,A,I2,A)')
90     & ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,
91     & ' tracers at run time when only ',PTRACERS_num,
92     & ' were specified at compile time. Naughty! '
93     CALL PRINT_ERROR(msgBuf, 1)
94     STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
95     ENDIF
96     C Check that enough parameters were specified
97     DO iTracer=1,PTRACERS_numInUse
98     IF (PTRACERS_advScheme(iTracer).EQ.0) THEN
99     WRITE(msgBuf,'(A,I2)')
100     & ' PTRACERS_READPARMS: No advect. scheme specified for tracer #',
101     & iTracer
102     CALL PRINT_ERROR(msgBuf, 1)
103     STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
104     ENDIF
105     ENDDO
106    
107    
108     #endif /* ALLOW_PTRACERS */
109    
110     RETURN
111     END

  ViewVC Help
Powered by ViewVC 1.1.22