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

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

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


Revision 1.15 - (hide annotations) (download)
Thu Jul 28 15:37:21 2005 UTC (18 years, 11 months ago) by molod
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, checkpoint57v_post, checkpoint58u_post, checkpoint57s_post, checkpoint58r_post, checkpoint57y_post, checkpoint58n_post, checkpoint58t_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58q_post, checkpoint58j_post, checkpoint57r_post, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58b_post, checkpoint58m_post
Changes since 1.14: +2 -2 lines
Use day counting when LESS than 1 month (not less than or equal)

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

  ViewVC Help
Powered by ViewVC 1.1.22