My Project
ice_calendar.f90
Go to the documentation of this file.
1 
2 
3 
4 
5 
6 
7 
8 
9 
10 
11 
12 !/===========================================================================/
13 ! CVS VERSION INFORMATION
14 ! $Id$
15 ! $Name$
16 ! $Revision$
17 !/===========================================================================/
18 
19 !=======================================================================
20 !BOP
21 !
22 ! !MODULE: ice_calendar - calendar routines for managing time
23 !
24 ! !DESCRIPTION:
25 !
26 ! Calendar routines for managing time
27 !
28 ! !REVISION HISTORY:
29 !
30 ! authors: Elizabeth C. Hunke, LANL
31 ! Tony Craig, NCAR
32 !
33 ! !INTERFACE:
34 !
35  module ice_calendar
36 !
37 ! !USES:
38 !
39  use ice_constants
40 
41 
42 !
43 !EOP
44 !
45  implicit none
46  save
47 
48  integer (kind=int_kind) ::&
49  daymo(12) & ! number of days in each month
50  , daycal(13) ! day number at end of month
51 
52  data daymo / 31,28,31, 30, 31, 30, 31, 31, 30, 31, 30, 31/
53  data daycal/ 0,31,59,90,120,151,181,212,243,273,304,334,365/
54 
55  integer (kind=int_kind) :: &
56  istep &! local step counter for time loop
57  , istep0 &! step counter, number of steps taken in previous run
58  , istep1 &! step counter, number of steps at current timestep
59  , mday &! day of the month
60  , week &! week of the year
61  , month &! 1 \le month \le 12
62  , monthp &! last month
63  , year_init &! initial year
64  , nyr &! year number
65  , idate &! date (yyyymmdd)
66  , sec &! elapsed seconds into date
67  , npt &! total number of time steps (dt)
68  , ndyn_dt &! reduced timestep for dynamics: ndyn_dt=dt/dyn_dt
69  , stop_now &! if 1, end program execution
70  , write_restart &! if 1, write restart now
71  , cpl_write_history &! if 1, write history on command from cpl
72  , diagfreq &! diagnostic output frequency (10 = once per 10 dt)
73  , dumpfreq_n ! restart output frequency (10 = once per 10 d,m,y)
74 
75  real (kind=dbl_kind) ::&
76 ! dt & ! thermodynamics timestep (s)
77  dtice, & ! thermodynamics timestep (s)
78 ! defined in old ice model dtice
79  dyn_dt & ! dynamics/transport/ridging timestep (s)
80  , dtei & ! 1/dte, where dte is the EVP timestep (1/s)
81 ! , time & ! total elapsed time (s)
82 ! ggao conflict
83  , time_forc & ! time of last forcing update (s)
84  , yday ! day of the year
85 
86  logical (kind=log_kind) :: &
87  new_year &! new year = .true.
88  , new_month &! new month = .true.
89  , new_week &! new week = .true.
90  , new_day &! new day = .true.
91  , write_ic &! write initial condition now
92  , write_history ! write history now
93 
94  character (len=1) :: &
95  histfreq &! history output frequency, 'y','m','d','1'
96  , dumpfreq ! restart frequency, 'y','m','d'
97 
98 !=======================================================================
99 
100  contains
101 
102 !=======================================================================
103 !BOP
104 !
105 ! !IROUTINE: init_calendar - initialize calendar variables
106 !
107 ! !INTERFACE:
108 !
109  subroutine init_calendar
110 !
111 ! !DESCRIPTION:
112 !
113 ! Initialize calendar variables
114 !
115 ! !REVISION HISTORY:
116 !
117 ! authors: Elizabeth C. Hunke, LANL
118 ! Tony Craig, NCAR
119 !
120 ! !USES:
121 !
122 ! !INPUT/OUTPUT PARAMETERS:
123 !
124 !EOP
125 !
126  istep1 = istep0 ! number of steps at current timestep
127  ! real (dumped) or imagined (use to set calendar)
128  istep = 0 ! local timestep number
129 ! time=istep0*dt ! s
130 ! time=istep0*dtice ! s
131 ! ggao be careful
132 
133  yday=c0i ! absolute day number
134  mday=0 ! day of the month
135  month=0 ! month
136  nyr=0 ! year
137  idate=00000101 ! date
138  sec=0 ! seconds into date
139  stop_now = 0 ! end program execution if stop_now=1
140 ! dyn_dt = dt/real(ndyn_dt,kind=dbl_kind) ! dynamics et al timestep
141  dyn_dt = dtice/real(ndyn_dt,kind=dbl_kind) ! dynamics et al timestep
142 ! ggao
143  end subroutine init_calendar
144 
145 !=======================================================================
146 !BOP
147 !
148 ! !IROUTINE: calendar - computes date at the end of the time step
149 !
150 ! !INTERFACE:
151 !
152  subroutine calendar(ttime)
153 !
154 ! !DESCRIPTION:
155 !
156 ! Determine the date at the end of the time step
157 !
158 ! !REVISION HISTORY:
159 !
160 ! authors: Elizabeth C. Hunke, LANL
161 ! Tony Craig, NCAR
162 !
163 ! !USES:
164  use ice_fileunits
165 !
166 ! !INPUT/OUTPUT PARAMETERS:
167 !
168  real (kind=dbl_kind), intent(in) :: &
169  ttime ! time variable
170 !
171 !EOP
172 !
173  integer (kind=int_kind) :: &
174  k &
175  , nyrp,mdayp,weekp & ! previous year, day, week
176  , elapsed_days & ! since beginning this run
177  , elapsed_months ! since beginning this run
178 
179  real (kind=dbl_kind) :: &
180  tday & ! absolute day number
181  , dayyr ! number of days per year
182 
183  dayyr = 365.0_dbl_kind
184 
185  nyrp=nyr
186  monthp=month
187  weekp=week
188  mdayp=mday
189  new_year=.false.
190  new_month=.false.
191  new_week=.false.
192  new_day=.false.
193  write_history=.false.
194  write_restart=0
195 
196  sec = mod(ttime,secday) ! elapsed seconds into date at
197  ! end of dt
198  tday = (ttime-sec)/secday + c1i ! absolute day number
199  yday = mod(tday-c1i,dayyr) + c1i ! day of the year
200  week = int(yday/c7i) + c1i ! week of the year
201  do k = 1, 12
202  if (yday > real(daycal(k),kind=dbl_kind)) month = k ! month
203  enddo
204  mday = int(yday) - daycal(month) ! day of the month
205  nyr = int((tday-c1i)/dayyr) + 1 ! year number
206  elapsed_months = (nyr - 1)*12 + month - 1
207  elapsed_days = int(tday) - 1
208 
209  idate = (nyr+year_init-1)*10000 + month*100 + mday ! date (yyyymmdd)
210 
211  if (istep >= npt+1) stop_now = 1
212  if (nyr /= nyrp) new_year = .true.
213  if (month /= monthp) new_month = .true.
214  if (week /= weekp) new_week = .true.
215  if (mday /= mdayp) new_day = .true.
216 
217  if (histfreq == '1') write_history=.true.
218  if (istep > 1) then
219  if (((histfreq == 'y'.or.histfreq == 'Y').and.new_year).or. &
220  ((histfreq == 'm'.or.histfreq == 'M').and.new_month).or. &
221  ((histfreq == 'w'.or.histfreq == 'W').and.new_week).or. &
222  ((histfreq == 'd'.or.histfreq == 'D').and.new_day)) &
223  write_history=.true.
224  select case (dumpfreq)
225  case ("y", "Y")
226  if (new_year .and. mod(nyr, dumpfreq_n)==0) &
227  write_restart = 1
228  case ("m", "M")
229  if (new_month .and. mod(elapsed_months,dumpfreq_n)==0) &
230  write_restart=1
231  case ("d", "D")
232  if (new_day .and. mod(elapsed_days, dumpfreq_n)==0) &
233  write_restart = 1
234  end select
235  endif
236 
237  if (my_task == master_task.and.mod(istep,diagfreq) == 0 &
238  .and.stop_now /= 1) then
239  write(nu_diag,*) ' '
240  write(nu_diag,'(a7,i10,4x,a6,i10,4x,a4,i10)') &
241  'istep1:', istep1, 'idate:', idate, 'sec:', sec
242  endif
243 
244  end subroutine calendar
245 
246 !=======================================================================
247 
248  end module ice_calendar
249 
250 !=======================================================================
integer(kind=int_kind) write_restart
logical(kind=log_kind) new_day
real(kind=dbl_kind) time_forc
real(kind=dbl_kind), parameter secday
integer(kind=int_kind) sec
integer(kind=int_kind) month
subroutine calendar(ttime)
real(kind=dbl_kind), parameter c0i
logical(kind=log_kind) new_week
logical(kind=log_kind) write_ic
integer(kind=int_kind) nyr
integer(kind=int_kind) mday
integer(kind=int_kind) istep
integer(kind=int_kind) stop_now
logical(kind=log_kind) new_month
subroutine init_calendar
integer(kind=int_kind) diagfreq
integer(kind=int_kind) cpl_write_history
integer(kind=int_kind) dumpfreq_n
integer(kind=int_kind) ndyn_dt
real(kind=dbl_kind) dtice
real(kind=dbl_kind) dyn_dt
integer(kind=int_kind) monthp
character(len=1) dumpfreq
real(kind=dbl_kind), parameter c7i
integer(kind=int_kind) year_init
real(kind=dbl_kind) yday
integer(kind=int_kind) idate
real(kind=dbl_kind), parameter c1i
character(len=1) histfreq
integer(kind=int_kind), dimension(13) daycal
integer(kind=int_kind), dimension(12) daymo
integer(kind=int_kind) istep1
logical(kind=log_kind) write_history
real(kind=dbl_kind) dtei
integer(kind=int_kind) istep0
integer(kind=int_kind) week
integer(kind=int_kind) npt
logical(kind=log_kind) new_year