/[MITgcm]/MITgcm/pkg/fizhi/fizhi_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/fizhi/fizhi_readparms.F

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


Revision 1.12 - (show annotations) (download)
Tue May 24 16:28:48 2005 UTC (19 years ago) by molod
Branch: MAIN
Changes since 1.11: +2 -2 lines
Bug fix - format msgbuf internal write correctly

1 C $Header: /u/gcmpack/MITgcm/pkg/fizhi/fizhi_readparms.F,v 1.11 2005/05/24 16:04:10 molod Exp $
2 C $Name: $
3
4 #include "FIZHI_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP 0
8 C !ROUTINE: FIZHI_MNC_INIT
9
10 C !INTERFACE:
11 SUBROUTINE FIZHI_READPARMS( myThid )
12
13 C !DESCRIPTION:
14 C Read Fizhi Namelist and Get the Model Date and Time from File
15
16 C !USES:
17 implicit none
18
19 #include "chronos.h"
20 #include "fizhi_io_comms.h"
21 #include "EEPARAMS.h"
22 #include "SIZE.h"
23 #include "PARAMS.h"
24
25 C !INPUT PARAMETERS:
26 integer myThid
27 CEOP
28
29 C !LOCAL VARIABLES:
30 character*(MAX_LEN_MBUF) msgBuf
31 integer ku, ku2
32 integer nymdbegin, nhmsbegin
33 integer nymdcurrent, nhmscurrent
34 real runlength
35 integer nincr
36 integer mmdd,hhmmss,nsecf2
37
38 namelist / fizhi_list /
39 . nymdbegin, nhmsbegin,
40 . fizhi_mnc_write_pickup, fizhi_mnc_read_pickup,
41 . runlength
42
43 C Set defaults
44 fizhi_mdsio_read_pickup = .TRUE.
45 fizhi_mdsio_write_pickup = .TRUE.
46 fizhi_mnc_write_pickup = .FALSE.
47 fizhi_mnc_read_pickup = .FALSE.
48 runlength = 0.0
49
50 C Read Fizhi Namelist
51 WRITE(msgBuf,'(A)') ' FIZHI_READPARMS: opening data.fizhi'
52 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,SQUEEZE_RIGHT,1)
53
54 CALL OPEN_COPY_DATA_FILE('data.fizhi', 'FIZHI_READPARMS',
55 & ku,myThid )
56 read (ku,NML=fizhi_list)
57 close (ku)
58
59 C Read Supplemental Ascii File with Current Time Info
60 CALL MDSFINDUNIT( ku2, myThid )
61 open(ku2,file='datetime0',form='formatted')
62 read(ku2,1000)nymdcurrent,nhmscurrent
63 close (ku2)
64 1000 format(i8,2x,i6)
65
66 C Change the length of the model run, ie, change ntimesteps
67 C if runlength has been set in the fizhi namelist
68
69 if(runlength.gt.0.) then
70 mmdd = int(runlength)
71 hhmmss = int((runlength - int(runlength))*1.e6)
72 nincr = nsecf2(hhmmss,mmdd,nymdcurrent)
73 ntimesteps = int(nincr/deltat)
74 endTime = startTime + deltat*float(ntimeSteps)
75 WRITE(msgBuf,'(A,I8)')
76 . ' CHANGING NUMBER OF MODEL TIMESTEPS TO',ntimesteps
77 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,SQUEEZE_RIGHT,1)
78 WRITE(msgBuf,'(A,F10.2)') ' CHANGING END TIME TO',endtime
79 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,SQUEEZE_RIGHT,1)
80 endif
81
82 C Fill chronos Common Block with Namelist and Other File Info
83 nymd0 = nymdbegin
84 nhms0 = nhmsbegin
85 nymd = nymdcurrent
86 nhms = nhmscurrent
87
88 C Echo Date and Time Info
89 _BEGIN_MASTER(myThid)
90 print *, ' Begin Date ',nymd0,' Begin Time ',nhms0
91 print *, 'Current Date ',nymd,' Current Time ',nhms
92 _END_MASTER(myThid)
93
94 return
95 end
96
97 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22