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

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

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


Revision 1.2 - (show annotations) (download)
Mon Aug 4 22:53:42 2003 UTC (20 years, 10 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint51f_pre
Changes since 1.1: +9 -8 lines
checkpoint51f_post
o Added on-the-fly spatial interpolation capability
    "USE_EXF_INTERPOLATION" to pkg/exf.
    This is a temporary Cartesian-grid hack until
    the super-duper ESMF coupler becomes available.
    Usage example is in verification/global_with_exf.
o Bug fix to pkg/ptracers, pkg/generic_advdiff/gad_calc_rhs.F,
    and pkg/kpp/kpp_transport_ptr.F for dealing with tracer
    non-local transport term.

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

  ViewVC Help
Powered by ViewVC 1.1.22