/[MITgcm]/MITgcm_contrib/nesting_sannino/nest_child/nest_child_readparms.F
ViewVC logotype

Annotation of /MITgcm_contrib/nesting_sannino/nest_child/nest_child_readparms.F

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


Revision 1.3 - (hide annotations) (download)
Sun Nov 28 02:13:01 2010 UTC (14 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +63 -32 lines
print Nesting parameter values.

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm_contrib/nesting_sannino/nest_child/nest_child_readparms.F,v 1.2 2009/10/23 19:44:02 sannino Exp $
2 heimbach 1.1 C $Name: $
3 jmc 1.3
4 heimbach 1.1 #include "NEST_CHILD_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7     CBOP 0
8     C !ROUTINE: NEST_CHILD_READPARMS
9    
10     C !INTERFACE:
11     SUBROUTINE NEST_CHILD_READPARMS( myThid )
12    
13     C !DESCRIPTION:
14     C Routine to read in file data.nest_child
15    
16     C !USES:
17     IMPLICIT NONE
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "PARAMS.h"
21     #include "GRID.h"
22     #include "NEST_CHILD_PARAMS.h"
23 jmc 1.3
24 heimbach 1.1 C !INPUT PARAMETERS:
25     INTEGER myThid
26     CEOP
27    
28 jmc 1.3 #ifdef ALLOW_NEST_CHILD
29     C !FUNCTIONS:
30     INTEGER ILNBLNK
31     EXTERNAL ILNBLNK
32    
33 heimbach 1.1 C !LOCAL VARIABLES:
34 jmc 1.3 C msgBuf :: Informational/error message buffer
35     C errIO :: IO error flag
36     C iUnit :: Work variable for IO unit number
37 heimbach 1.1
38     CHARACTER*(MAX_LEN_MBUF) msgBuf
39 jmc 1.3 INTEGER errIO, iUnit, iLen
40 heimbach 1.1
41     C-- NEST_CHILD coupler parameters
42     NAMELIST /NEST_CHILD_PARM01/
43     & nest_child_a,
44 sannino 1.2 & dirNEST_CHILD,
45     & dirCHILD
46 heimbach 1.1
47     _BEGIN_MASTER(myThid)
48    
49 jmc 1.3 WRITE(msgBuf,'(A)')
50     & ' NEST_CHILD_READPARAMS: opening "data.nest_child"'
51 heimbach 1.1 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
52 jmc 1.3 & SQUEEZE_RIGHT, myThid )
53 heimbach 1.1
54     CALL OPEN_COPY_DATA_FILE(
55     I 'data.nest_child', 'NEST_CHILD_READPARAMS',
56     O iUnit,
57     I myThid )
58    
59     C-- set default NEST_CHILD coupler parameters
60 jmc 1.3 nest_child_a = 0. _d 0
61 heimbach 1.1
62     C-- Read settings from model parameter file "data.nest_child".
63     READ(UNIT=iUnit,NML=NEST_CHILD_PARM01,IOSTAT=errIO)
64 jmc 1.3 IF ( errIO.LT.0 ) THEN
65     WRITE(msgBuf,'(2A)')
66     & 'S/R NEST_CHILD_READPARMS',
67     & ' reading parameter file "data.nest_child"'
68     CALL PRINT_ERROR( msgBuf, myThid )
69     WRITE(msgBuf,'(A,I4,A)')
70     & 'Error reading namelist NEST_CHILD_PARM01 (err=',
71     & errIO, ' )'
72     CALL PRINT_ERROR( msgBuf, myThid )
73     STOP 'ABNORMAL END: S/R NEST_CHILD_READPARMS'
74 heimbach 1.1 ENDIF
75    
76     CLOSE(iUnit)
77    
78 jmc 1.3 WRITE(msgBuf,'(2A)') ' NEST_CHILD_READPARMS:',
79     & ' finished reading "data.nest_child"'
80 heimbach 1.1 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
81 jmc 1.3 & SQUEEZE_RIGHT, myThid )
82    
83     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
84     C-- Print out nesting parameter:
85    
86     iUnit = standardMessageUnit
87     WRITE(msgBuf,'(A)') '// ==================================='
88     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
89     WRITE(msgBuf,'(A)') '// NEST_CHILD parameters :'
90     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
91     WRITE(msgBuf,'(A)') '// ==================================='
92     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
93    
94     WRITE(iUnit,*) 'NEST_CHILD: NST_LEV_TOT_C =', NST_LEV_TOT_C
95     WRITE(iUnit,*) 'NEST_CHILD: NST_LEV_C =', NST_LEV_C
96     WRITE(iUnit,*) 'NEST_CHILD: NCPUs_PAR_C =', NCPUs_PAR_C
97     WRITE(iUnit,*) 'NEST_CHILD: NCPUs_CLD_C =', NCPUs_CLD_C
98     WRITE(iUnit,*) 'NEST_CHILD: MSTR_DRV_C =', MSTR_DRV_C
99     WRITE(iUnit,*) 'NEST_CHILD: MSTR_PAR_C =', MSTR_PAR_C
100     WRITE(iUnit,*) 'NEST_CHILD: MSTR_CLD_C =', MSTR_CLD_C
101     WRITE(iUnit,*) 'NEST_CHILD: nest_child_a =', nest_child_a
102     iLen = MAX( 1, ILNBLNK(dirNEST_CHILD) )
103     WRITE(iUnit,*) 'NEST_CHILD: dirNEST_CHILD =',
104     & dirNEST_CHILD(1:iLen)
105     iLen = MAX( 1, ILNBLNK(dirCHILD) )
106     WRITE(iUnit,*) 'NEST_CHILD: dirCHILD =', dirCHILD(1:iLen)
107    
108     WRITE(msgBuf,'(A)') '// ==================================='
109     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
110     WRITE(msgBuf,'(A)') ' '
111     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
112    
113     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
114 heimbach 1.1
115     _END_MASTER(myThid)
116    
117     C-- Everyone else must wait for the parameters to be loaded
118     _BARRIER
119    
120     #endif /* ALLOW_NEST_CHILD */
121    
122 jmc 1.3 RETURN
123     END

  ViewVC Help
Powered by ViewVC 1.1.22