OB.DAAC Logo
NASA Logo
Ocean Color Science Software

ocssw V2022
navtlm.f
Go to the documentation of this file.
1  subroutine navtlm(input,nframes,navctl,gaclac,tlm,tilts)
2 
3 c $Header: /app/shared/RCS/irix-5.2/seawifsd/src/mops/mopsV4.1/swfnav/navtlm.f,v 1.1 1995/01/17 23:02:29 seawifsd Exp seawifsd $
4 c $Log: navtlm.f,v $
5 c Revision 1.1 1995/01/17 23:02:29 seawifsd
6 c Initial revision
7 c
8 c
9 c navtim(input,nframes,navctl,tlm)
10 c
11 c Purpose: Fill navigation telemetry structure from input data structure
12 c
13 c Calling Arguments:
14 c
15 c Name Type I/O Description
16 c -------- ---- --- -----------
17 c input struct I input data structure containing SeaStar ID
18 c and time tag, converted spacecraft and
19 c instrument telemetry
20 c nframes I*4 I number of minor frames of input data
21 c gaclac I*4 I data type indicator (1=GAC)
22 c tlm struct O output navigation telemetry structure
23 c
24 c By: Frederick S. Patt, GSC, 10 August 93
25 c
26 c Notes:
27 c
28 c Instrument telemetry locations are as defined in the OSC L-band ICD.
29 c Instrument telemetry occurs in minor frames 1 and 3 for LAC and
30 c for GAC lines 1, 3, 4, 6, 7, 9, 10, 12, 13 and 15 in major frame.
31 
32 c Spacecraft telemetry locations are currently assumed as follows:
33 c Analog words 7 - 9: Attitude angles yaw, roll, pitch
34 c Analog words 10 - 15: Sun sensor angles
35 c Analog words 16 - 19: Earth scanner angles (phase and width)
36 c Discrete words 1 - 3: Sun sensor status (active sensor flag)
37 c
38 c Spacecraft telemetry is contained in minor frame 1 for LAC and GAC
39 c
40 c
41 c Modification History:
42 c
43 c June 24, 1994: Added tilt structure to pass tilt flags and record
44 c ranges to L1A software.
45 c Frederick S. Patt, GSC
46 c
47 c January 5, 1995: Corrected code to set tilt flags for fill frames.
48 c Frederick S. Patt, GSC
49 c
50 c March 30, 1995: Modified code to accept GAC minor frame sequence
51 c of 1, 3, 2. Frederick S. Patt, GSC
52 c
53 c May 2, 1995: Modified code to use actual tilt telemetry
54 c Frederick S. Patt, GSC
55 c
56 c Sept. 24, 1997: Modified to unpack Sun sensor time tags.
57 c Frederick S. Patt, GSC
58 c
59 c October 30, 1997: Increased tilt angle tolerance to allow test with
60 c new static tilt values. Frederick S. Patt, GSC
61 c
62 c December 1, 1997: Corrected tilt state logic to check for missing tilt
63 c telemetry at the start of a tilt change. Frederick S. Patt, GSC
64 c
65 c December 4, 1997: Limited tilt states to 20, to avoid overflow of
66 c tilts structure when processing corrupted telemetry. Also changed
67 c logic to ignore indeterminate tilt states, and therefor assume the
68 c actual state was equal to the previous state.
69 c B. A. Franz, GSC
70 c
71 c February 25, 1998: Modified tilt-state logic to incorporate state
72 c filtering for errors in tilt telemetry. B. A. Franz, GSC
73 c
74 c July 14, 1998: Modified tilt consistency checking logic to extend tilt
75 c change state through any adjacent missing or flagged values.
76 c F. S. Patt, SAIC GSC
77 c
78 c August 2, 1998: Included flagging of tilt telemetry for single-line tilt
79 c states; added a limit check for tilt motor angles. F. S. Patt, SAIC GSC
80 c
81 c September 22, 1998: Modified logic for checking attitude sensor delta times
82 c to reject positive values (since sensor times can't be later than frame
83 c times). F. S. Patt, SAIC GSC
84 
85  implicit none
86 #include "input_s.fin"
87 #include "navctl_s.fin"
88 #include "tlm_str.fin"
89 #include "tilt_s.fin"
90  type(input_struct) :: input(maxlin)
91  type(navctl_struct) :: navctl
92  type(tlm_struct) :: tlm
93  type(tilt_states) :: tilts
94 
95  real*4 ttilt, tilttol, tanglim(2)
96  integer*4 nframes, gaclac, nper, i, j, k, ip, mf, ilin
97  integer*4 itilt, tflag, ntlts, istime
98  byte stime(4)
99 
100  integer*4 tilt_flags(maxlin)
101  integer*4 nlines
102  logical gottwo
103  equivalence(istime,stime)
104  data tilttol/0.25/, tanglim/48.,225./
105 
106  tlm%ntlm = nframes
107  ntlts = 0
108 
109 c Determine if LAC or GAC
110  if (input(1)%sc_id(2).eq.15) then
111  gaclac = 1
112  nper = 5
113  else
114  gaclac = 0
115  nper = 1
116  end if
117 
118 c !
119 c ! Initialize tilt flag array
120 c !
121  nlines = nframes*nper
122  do i=1,nlines
123  tilt_flags(i) = -1
124  enddo
125 
126 c !
127 c ! Extract telemetry from each frame
128 c !
129  do i=1, nframes
130 
131 c Get minor frame number
132  mf = input(i)%sc_id(1)/128
133 
134 c If not fill frame
135  if (input(i)%flag.eq.0) then
136 
137 c Unpack tilt telemetry
138  do j=1,nper
139  ilin = mf - 1 + j
140 c If second of 3 scan lines then no tilt telemetry
141  if (mod(ilin,3).eq.2) then
142  tlm%tilt(1)%flag(j,i) = 1
143  tlm%tilt(2)%flag(j,i) = 1
144  tlm%tilt(1)%ang(j,i) = 0.
145  tlm%tilt(2)%ang(j,i) = 0.
146  tilt_flags((i-1)*nper+j) = -1
147  else
148 c Else get tilt telemetry
149 c Convert tilt motor angles to tilt angle
150  call conv_tilt(input(i)%inst_ana(23,j),
151  * input(i)%inst_ana(22,j),ttilt)
152 c Check tilt bits
153  itilt = input(i)%inst_dis(16,j)*4
154  * + input(i)%inst_dis(17,j)*2 + input(i)%inst_dis(18,j)
155  if (itilt.eq.7) then
156 c Tilt change in progress; get tilt from analog telemetry
157  if ((input(i)%inst_ana(22,j).gt.tanglim(1)).and.
158  * (input(i)%inst_ana(22,j).lt.tanglim(2)).and.
159  * (input(i)%inst_ana(23,j).gt.tanglim(1)).and.
160  * (input(i)%inst_ana(23,j).lt.tanglim(2))) then
161  tlm%tilt(1)%flag(j,i) = 2
162  tlm%tilt(2)%flag(j,i) = 2
163 c tlm%tilt(1)%ang(j,i) = input(i)%inst_ana(22,j)
164 c tlm%tilt(2)%ang(j,i) = input(i)%inst_ana(23,j)
165  tlm%tilt(1)%ang(j,i) = ttilt
166  tlm%tilt(2)%ang(j,i) = ttilt
167  tflag = 3
168  else
169  tlm%tilt(1)%flag(j,i) = 1
170  tlm%tilt(2)%flag(j,i) = 1
171  tlm%tilt(1)%ang(j,i) = 0.
172  tlm%tilt(2)%ang(j,i) = 0.
173  tflag = -1
174  end if
175 
176 
177  else if (itilt.eq.3) then
178 c Tilt nadir aligned
179  tlm%tilt(1)%flag(j,i) = 0
180  tlm%tilt(2)%flag(j,i) = 0
181  tlm%tilt(1)%ang(j,i) = 0.
182  tlm%tilt(2)%ang(j,i) = 0.
183  tflag = 0
184 
185  else if (itilt.eq.5) then
186 c Tilt aft aligned
187  tlm%tilt(1)%flag(j,i) = 0
188  tlm%tilt(2)%flag(j,i) = 0
189  tlm%tilt(1)%ang(j,i) = navctl%tiltaft
190  tlm%tilt(2)%ang(j,i) = navctl%tiltaft
191  tflag = 2
192 
193  else if (itilt.eq.6) then
194 c Tilt forward aligned
195  tlm%tilt(1)%flag(j,i) = 0
196  tlm%tilt(2)%flag(j,i) = 0
197  tlm%tilt(1)%ang(j,i) = navctl%tiltfor
198  tlm%tilt(2)%ang(j,i) = navctl%tiltfor
199  tflag = 1
200 
201  else
202 c Tilt status unknown
203  tlm%tilt(1)%flag(j,i) = 1
204  tlm%tilt(2)%flag(j,i) = 1
205  tlm%tilt(1)%ang(j,i) = 0.
206  tlm%tilt(2)%ang(j,i) = 0.
207  tflag = -1
208  end if
209 
210 c Check for inconsistency between tilt bits and angles
211  if (abs(ttilt-tlm%tilt(1)%ang(j,i)) .gt. tilttol) then
212  tlm%tilt(1)%flag(j,i) = 1
213  tlm%tilt(2)%flag(j,i) = 1
214  tlm%tilt(1)%ang(j,i) = 0.
215  tlm%tilt(2)%ang(j,i) = 0.
216  tflag = -1
217  end if
218 
219  tilt_flags((i-1)*nper+j) = tflag
220 
221  end if ! inst telemetry frame
222 
223  end do
224 
225 c Else if fill record, set flags
226  else
227  do j=1,nper
228  tlm%tilt(1)%flag(j,i) = 1
229  tlm%tilt(2)%flag(j,i) = 1
230  tlm%tilt(1)%ang(j,i) = 0.
231  tlm%tilt(2)%ang(j,i) = 0.
232  end do
233  end if
234 
235 c If minor frame 1, unpack ACS telemetry
236  if ((input(i)%flag.eq.0).and.(mf.eq.1)) then
237 
238 c Unpack attitude angles
239  do j=1,3
240  tlm%sc_att%att(j,i) = input(i)%sc_ana(j+6)
241  end do
242  tlm%sc_att%flag(i) = 0
243 
244 c Unpack Sun sensor angles and status
245  do j=1,3
246  if (input(i)%sc_dis(j).eq.3) then
247  tlm%sun(j)%active(i) = 0
248  else
249  tlm%sun(j)%active(i) = 1
250  end if
251  tlm%sun(j)%flag(i) = 0
252 c tlm%sun(j)%deltim(i) = 0.0
253  tlm%sun(j)%ang(1,i) = input(i)%sc_ana(2*j+8)
254  tlm%sun(j)%ang(2,i) = input(i)%sc_ana(2*j+9)
255 c Get delta time
256 #ifdef LINUX
257  do k=1,4
258  stime(k)=input(i)%sc_dis(16+4*j+5-k)
259  end do
260 #else
261  do k=1,4
262  stime(k)=input(i)%sc_dis(16+4*j+k)
263  end do
264 #endif
265  istime = mod(istime,86400000)
266  tlm%sun(j)%deltim(i) = (istime - input(i)%msec)/1.d3
267  if ((tlm%sun(j)%deltim(i).gt.0.).or.
268  * (tlm%sun(j)%deltim(i).lt.-10.))
269  * tlm%sun(j)%flag(i) = 1
270  end do
271 
272 c Unpack Earth scanner angles
273  do j=1,2
274  tlm%earth(j)%active(i) = 0
275  tlm%earth(j)%flag(i) = 0
276  tlm%earth(j)%deltim(i) = 0.0
277  tlm%earth(j)%widphse(1,i) = input(i)%sc_ana(2*j+15)
278  tlm%earth(j)%widphse(2,i) = input(i)%sc_ana(2*j+14)
279  if (tlm%earth(j)%widphse(2,i).gt.180.)
280  * tlm%earth(j)%widphse(2,i) = tlm%earth(j)%widphse(2,i) - 360.0
281 #ifdef LINUX
282  do k=1,4
283  stime(k)=input(i)%sc_dis(28+4*j+5-k)
284  end do
285 #else
286  do k=1,4
287  stime(k)=input(i)%sc_dis(28+4*j+k)
288  end do
289 #endif
290  istime = mod(istime,86400000)
291  tlm%earth(j)%deltim(i) = (istime - input(i)%msec)/1.d3
292  if ((tlm%earth(j)%deltim(i).gt.0.).or.
293  * (tlm%earth(j)%deltim(i).lt.-10.))
294  * tlm%earth(j)%flag(i) = 1
295  end do
296 
297  else
298 
299 c Set Attitude flags
300  do j=1,3
301  tlm%sc_att%att(j,i) = 0.
302  end do
303  tlm%sc_att%flag(i) = 1
304 
305 c Set Sun sensor angles, flags and status
306  do j=1,3
307  tlm%sun(j)%active(i) = 1
308  tlm%sun(j)%flag(i) = 1
309  tlm%sun(j)%deltim(i) = 0.
310  tlm%sun(j)%ang(1,i) = 0.
311  tlm%sun(j)%ang(2,i) = 0.
312  end do
313 
314 c Set Earth scanner angles
315  do j=1,2
316  tlm%earth(j)%active(i) = 1
317  tlm%earth(j)%flag(i) = 1
318  tlm%earth(j)%deltim(i) = 0.0
319  tlm%earth(j)%widphse(1,i) = 0.
320  tlm%earth(j)%widphse(2,i) = 0.
321  end do
322 
323  end if
324  end do
325 
326 c !
327 c ! Filter-out single line tilt states
328 c !
329 
330 c Find first unflagged value
331  ip = 1
332  do while (tilt_flags(ip) .eq. -1)
333  ip = ip + 1
334  end do
335 
336  gottwo = .false.
337 
338  do i = ip+1, nlines
339 
340 c Find next unflagged value
341  if (tilt_flags(i) .ne. -1) then
342  if (tilt_flags(i) .eq. tilt_flags(ip)) then
343  gottwo = .true.
344  else
345  if (.not.gottwo) then
346  tilt_flags(ip) = -1
347 c Also flag tilt telemetry for this line
348  j = mod( (ip-1), nper) + 1
349  k = (ip-1)/nper + 1
350  tlm%tilt(1)%flag(j,k) = 1
351  tlm%tilt(2)%flag(j,k) = 1
352  end if
353  gottwo = .false.
354  end if
355  ip = i
356  end if
357  end do
358  if (.not.gottwo) then
359  tilt_flags(ip) = -1
360  j = mod( (ip-1), nper) + 1
361  k = (ip-1)/nper + 1
362  tlm%tilt(1)%flag(j,k) = 1
363  tlm%tilt(2)%flag(j,k) = 1
364  end if
365 c !
366 c ! Now fill in missing tilt flags
367 c !
368 
369  ip = 1
370  do while (tilt_flags(ip) .eq. -1)
371  ip = ip + 1
372  end do
373 
374  do i=1,ip
375  tilt_flags(i) = tilt_flags(ip)
376  end do
377 
378  do i = ip+1, nlines
379 
380 c Find next unflagged value
381  if (tilt_flags(i) .ne. -1) then
382 
383 c Fill missing values if needed
384  if ((i - ip) .gt. 1) then
385 
386 c Use max value for flag to default to tilt change state
387  tflag = max(tilt_flags(ip),tilt_flags(i))
388  do j=ip+1, i-1
389  tilt_flags(j) = tflag
390  end do
391  end if
392  ip = i
393  end if
394  end do
395 
396  do i=ip, nlines
397  tilt_flags(i) = tilt_flags(ip)
398  end do
399 
400 c !
401 c ! Locate and store tilt-change periods
402 c !
403  ntlts = 1
404  tilts%tilt_ranges(1,ntlts) = 1
405  tilts%tilt_flags(ntlts) = tilt_flags(1)
406 c
407  do i=2,nlines
408 
409  if (tilt_flags(i) .ne. tilt_flags(i-1)) then
410  tilts%tilt_ranges(2,ntlts) = i-1
411  if (ntlts .eq. 20) then
412  write(*,*)
413  write(*,*) "navtlm: Error: excessive tilt changes."
414  write(*,*)
415  goto 10
416  endif
417  ntlts = ntlts+1
418  tilts%tilt_ranges(1,ntlts) = i
419  tilts%tilt_flags(ntlts) = tilt_flags(i)
420  endif
421 
422  enddo
423 c
424  10 continue
425  tilts%tilt_ranges(2,ntlts) = nper*nframes
426  tilts%ntilts = ntlts
427 
428 
429  990 continue
430  return
431  end
#define real
Definition: DbAlgOcean.cpp:26
subroutine navtlm(input, nframes, navctl, gaclac, tlm, tilts)
Definition: navtlm.f:2
#define max(A, B)
Definition: main_biosmap.c:61
#define abs(a)
Definition: misc.h:90
subroutine conv_tilt(ang_fm, ang_mm, tilt)
Definition: conv_tilt.f:2