/[MITgcm]/MITgcm_contrib/nesting_sannino/nest_parent/nest_parent_readparms.F
ViewVC logotype

Annotation of /MITgcm_contrib/nesting_sannino/nest_parent/nest_parent_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:38:55 2010 UTC (14 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +62 -35 lines
print Nesting parameter values to STDOUT
 (avoid print*,'something' which is not very helpful with many procs)

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm_contrib/nesting_sannino/nest_parent/nest_parent_readparms.F,v 1.2 2009/10/23 19:42:00 sannino Exp $
2 heimbach 1.1 C $Name: $
3 jmc 1.3
4 heimbach 1.1 #include "NEST_PARENT_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7     CBOP 0
8     C !ROUTINE: NEST_PARENT_READPARMS
9    
10     C !INTERFACE:
11     SUBROUTINE NEST_PARENT_READPARMS( myThid )
12    
13     C !DESCRIPTION:
14     C Routine to read in file data.nest_parent
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_PARENT_PARAMS.h"
23    
24 jmc 1.3 C !INPUT PARAMETERS:
25     C myThid :: my Thread Id number
26     INTEGER myThid
27 heimbach 1.1 CEOP
28    
29 jmc 1.3 #ifdef ALLOW_NEST_PARENT
30     C !FUNCTIONS:
31     INTEGER ILNBLNK
32     EXTERNAL ILNBLNK
33 heimbach 1.1
34     C !LOCAL VARIABLES:
35 jmc 1.3 C msgBuf :: Informational/error message buffer
36     C errIO :: IO error flag
37     C iUnit :: Work variable for IO unit number
38 heimbach 1.1
39     CHARACTER*(MAX_LEN_MBUF) msgBuf
40 jmc 1.3 INTEGER errIO, iUnit, iLen
41 heimbach 1.1
42     C-- NEST_PARENT coupler parameters
43     NAMELIST /NEST_PARENT_PARM01/
44     & LeftB, RightB, dirNEST_PARENT
45    
46     _BEGIN_MASTER(myThid)
47    
48 jmc 1.3 WRITE(msgBuf,'(A)')
49     & ' NEST_PARENT_READPARAMS: opening "data.nest_parent"'
50 heimbach 1.1 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
51 jmc 1.3 & SQUEEZE_RIGHT, myThid )
52 heimbach 1.1
53     CALL OPEN_COPY_DATA_FILE(
54     I 'data.nest_parent', 'NEST_PARENT_READPARAMS',
55     O iUnit,
56     I myThid )
57    
58     C-- set default NEST_PARENT coupler parameters
59    
60     C-- Read settings from model parameter file "data.nest_parent".
61     READ(UNIT=iUnit,NML=NEST_PARENT_PARM01,IOSTAT=errIO)
62 jmc 1.3 IF ( errIO.LT.0 ) THEN
63     WRITE(msgBuf,'(2A)')
64     & 'S/R NEST_PARENT_READPARMS',
65     & ' reading parameter file "data.nest_parent"'
66     CALL PRINT_ERROR( msgBuf, myThid )
67     WRITE(msgBuf,'(A,I4,A)')
68     & 'Error reading namelist NEST_PARENT_PARM01 (err=',
69     & errIO, ' )'
70     CALL PRINT_ERROR( msgBuf, myThid )
71     STOP 'ABNORMAL END: S/R NEST_PARENT_READPARMS'
72 heimbach 1.1 ENDIF
73    
74     CLOSE(iUnit)
75    
76 jmc 1.3 WRITE(msgBuf,'(2A)') ' NEST_PARENT_READPARMS:',
77     & ' finished reading "data.nest_parent"'
78 heimbach 1.1 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
79 jmc 1.3 & SQUEEZE_RIGHT, myThid )
80    
81     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
82     C-- Print out nesting parameter:
83    
84     iUnit = standardMessageUnit
85     WRITE(msgBuf,'(A)') '// ==================================='
86     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
87     WRITE(msgBuf,'(A)') '// NEST_PARENT parameters :'
88     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
89     WRITE(msgBuf,'(A)') '// ==================================='
90     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
91    
92     WRITE(iUnit,*) 'NEST_PARENT: NST_LEV_TOT_P =', NST_LEV_TOT_P
93     WRITE(iUnit,*) 'NEST_PARENT: NST_LEV_P =', NST_LEV_P
94     WRITE(iUnit,*) 'NEST_PARENT: NCPUs_PAR_P =', NCPUs_PAR_P
95     WRITE(iUnit,*) 'NEST_PARENT: NCPUs_CLD_P =', NCPUs_CLD_P
96     WRITE(iUnit,*) 'NEST_PARENT: MSTR_DRV_P =', MSTR_DRV_P
97     WRITE(iUnit,*) 'NEST_PARENT: MSTR_PAR_P =', MSTR_PAR_P
98     WRITE(iUnit,*) 'NEST_PARENT: MSTR_CLD_P =', MSTR_CLD_P
99     WRITE(iUnit,*) 'NEST_PARENT: LeftB =', LeftB
100     WRITE(iUnit,*) 'NEST_PARENT: RightB =', RightB
101     iLen = MAX( 1, ILNBLNK(dirNEST_PARENT) )
102     WRITE(iUnit,*) 'NEST_PARENT: dirNEST_PARENT =',
103     & dirNEST_PARENT(1:iLen)
104    
105     WRITE(msgBuf,'(A)') '// ==================================='
106     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
107     WRITE(msgBuf,'(A)') ' '
108     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
109    
110     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
111 heimbach 1.1
112     _END_MASTER(myThid)
113    
114     C-- Everyone else must wait for the parameters to be loaded
115     _BARRIER
116    
117     #endif /* ALLOW_NEST_PARENT */
118    
119 jmc 1.3 RETURN
120     END

  ViewVC Help
Powered by ViewVC 1.1.22