/[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.3 - (hide annotations) (download)
Sat Sep 27 07:45:51 2003 UTC (20 years, 8 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint51k_post, checkpoint51o_pre, checkpoint51l_post, checkpoint52, checkpoint51f_post, checkpoint51t_post, checkpoint51n_post, checkpoint51s_post, checkpoint51j_post, checkpoint51n_pre, checkpoint51l_pre, checkpoint51q_post, checkpoint51h_pre, branchpoint-genmake2, checkpoint51r_post, checkpoint51i_post, checkpoint52a_pre, checkpoint51i_pre, checkpoint51o_post, checkpoint51g_post, ecco_c52_e35, checkpoint51m_post, checkpoint51p_post, checkpoint51u_post
Branch point for: branch-genmake2, branch-nonh, tg2-branch, checkpoint51n_branch
Changes since 1.2: +2 -1 lines
I/O bug fixes

1 dimitri 1.3 C $Header: /usr/local/gcmpack/MITgcm/pkg/ptracers/ptracers_readparms.F,v 1.2 2003/08/04 22:53:42 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     PTRACERS_numInUse=-1
46     DO iTracer=1,PTRACERS_num
47 dimitri 1.2 PTRACERS_advScheme(iTracer)=saltAdvScheme
48     PTRACERS_diffKh(iTracer)=diffKhS
49     PTRACERS_diffK4(iTracer)=diffK4S
50     PTRACERS_diffKr(iTracer)=diffKrS
51     PTRACERS_useGMRedi(iTracer)=useGMRedi
52     PTRACERS_useKPP(iTracer)=useKPP
53 adcroft 1.1 PTRACERS_initialFile(iTracer)=' '
54     ENDDO
55 dimitri 1.3 PTRACERS_useRecords=.FALSE.
56 adcroft 1.1
57     C Open and read the data.ptracers file
58     _BEGIN_MASTER(myThid)
59     WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'
60     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
61     & SQUEEZE_RIGHT , 1)
62     CALL OPEN_COPY_DATA_FILE(
63     I 'data.ptracers', 'PTRACERS_READPARMS',
64     O iUnit,
65     I myThid )
66     READ(UNIT=iUnit,NML=PTRACERS_PARM01)
67     WRITE(msgBuf,'(A)')
68     & ' PTRACERS_READPARMS: finished reading data.ptracers'
69     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
70     & SQUEEZE_RIGHT , 1)
71    
72     C Close the open data file
73     CLOSE(iUnit)
74     _END_MASTER(myThid)
75    
76     C Everyone else must wait for the parameters to be loaded
77     _BARRIER
78    
79     C Now set-up any remaining parameters that result from the input parameters
80    
81     C If PTRACERS_numInUse was not set in data.ptracers then we can assume
82     C that all PTRACERS fields will be in use
83     IF (PTRACERS_numInUse.LT.0) THEN
84     PTRACERS_numInUse=PTRACERS_num
85     ENDIF
86     C Check we are not trying to use more tracers than allowed
87     IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN
88     WRITE(msgBuf,'(A,I2,A,I2,A)')
89     & ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,
90     & ' tracers at run time when only ',PTRACERS_num,
91     & ' were specified at compile time. Naughty! '
92     CALL PRINT_ERROR(msgBuf, 1)
93     STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
94     ENDIF
95     C Check that enough parameters were specified
96     DO iTracer=1,PTRACERS_numInUse
97     IF (PTRACERS_advScheme(iTracer).EQ.0) THEN
98     WRITE(msgBuf,'(A,I2)')
99     & ' PTRACERS_READPARMS: No advect. scheme specified for tracer #',
100     & iTracer
101     CALL PRINT_ERROR(msgBuf, 1)
102     STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
103     ENDIF
104     ENDDO
105    
106    
107     #endif /* ALLOW_PTRACERS */
108    
109     RETURN
110     END

  ViewVC Help
Powered by ViewVC 1.1.22