OB.DAAC Logo
NASA Logo
Ocean Color Science Software

ocssw V2022
attdet.f
Go to the documentation of this file.
1  subroutine attdet( navblk, navctl, nad_bod, attxfm,
2  1 pos, vel, widphse1, widphfl1, widphse2, widphfl2,
3  1 sun_bod, sunbodfl, att_prev, delta_t, covar)
4 c
5 c attdet( navblk, navctl, nad_bod, attxfm,
6 c pos, vel, widphse1, widphfl1, widphse2,
7 c widphfl2, sun_bod, sunbodfl, att_prev, delta_t, covar )
8 c
9 c purpose: perform the actual attitude determination for one line
10 c
11 c calling arguments:
12 c
13 c name Type i/o description
14 c -------- ---- --- -----------
15 c navblk struct i/o navigation block including:
16 c in: sun_ref - sun ref in geo coord sys
17 c lcl_vert - local vertical
18 c out: sen_frame - attitude matrix
19 c att_ang - attitude angles in the
20 c order yaw, roll, pitch
21 c navctl struct i navigation controls. used are:
22 c redoyaw - # iterations to redo yaw
23 c computation
24 c yawtol - difference between yaw guess
25 c and computed yaw
26 c nad_bod r*4 i size 3 unit nadir vector in spacecraft frame
27 c attxfm r*4 i size 3 by 3 attitude transform matrix -
28 c the transform from geocentric to
29 c orbit coordinates
30 c pos r*4 i size 3 orbit position vector(km)
31 c vel r*4 i size 3 orbit velocity vector(km/sec)
32 c widphse1 r*4 i size 2 processed earth width
33 c and phase for sensor 1
34 c widphfl1 i*4 i flag for earth sensor 1 - 0 = good
35 c widphse2 r*4 i size 2 processed earth width
36 c and phase for sensor 2
37 c widphfl2 i*4 i flag for earth sensor 2 - 0 = good
38 c sun_bod r*4 i size 3 weighted sun vectors in spacecraft
39 c frame
40 c sunbodfl i*4 i flag for sun sensor data - 0 = good
41 c att_prev r*4 i size 3 attitude angles from previous scan line
42 c delta_t r*4 i time difference from previous scan line
43 c(set to 0 if first line in frame, negative if
44 c propagating backwards in time)
45 c covar r*4 i size 3 array of covariance matrix diagonal
46 c elements
47 c
48 c
49 c by: w. robinson, gsc, 14 apr 93
50 c
51 c notes: the initial yaw used to create the nadir vector from the
52 c earth sensors is assumed to be the previous value. If the
53 c resultant yaw computed here id different from the guess by
54 c the value yawtol, and the redoyaw is set, the nadir vector
55 c will be re-computed by calling routine earth again. this will
56 c be repeated up to redoyaw number of times
57 c
58 c modification history:
59 c
60 c modified extraction of euler angles from attitude matrix to reflect
61 c actual order and sign of rotations implemented by osc in the acs.
62 c the order is 2-1-3 in the acs(not the spacecraft) frame. the acs
63 c axes defined as: x toward the velocity(spacecraft -y axis);
64 c y toward the negative orbit normal(spacecraft -z axis); z toward
65 c the nadir(spacecraft x axis). this is equivalent to a
66 c pitch-roll-yaw transformation, with the pitch and roll angles being
67 c negative about the spacecraft z and y axes.
68 c f. s. patt, gsc, october 4, 1996.
69 c
70 c modified the order of operations to first transform the matrix constructed
71 c from the reference vectors to the orbital frame, then use that matrix to
72 c compute the orbit-to-spacecraft transformation. this will give the same
73 c results as before, but allows the attitude matrix to be a small rotation.
74 c f. s. patt, saic gsc, february 3, 1998.
75 c
76 c modified attitude angle calculation to weight the yaw angle according to
77 c the sun/nadir angle to prevent blowing up at subsolar point.
78 c f. s. patt, saic gsc, march 9, 1998.
79 c
80 c rewrote this routine to implement attitude determination using a kalman
81 c filter instead of the deterministic algorithm used previously. this was
82 c done to resolve multiple issues: reduce jitter at sensor transitions,
83 c improve yaw accuracy at the subsolar point and handle sensor gaps. the
84 c initial version uses a simple dynamics model which assumes an inertial
85 c spin axis(not necessarily parallel to the orbit normal).
86 c all of the equations are taken from wertz, section 13.5.2, pp. 462-465.
87 c f. s. patt, saic gsc, june 1, 1998.
88 c
89 c reduced the state noise value(from 1.e-8 to 0.25e-8) to reduce the yaw
90 c variation in the middle of the orbit.
91 c f. s. patt, saic gsc, june 22, 1998.
92 c
93 c corrected a(minor) error in the calculation of the partial derivatives.
94 c f. s. patt, saic gsc, october 19, 1998.
95 c
96 c reduced the state noise value for roll and yaw to 6.e-10, to constrain the
97 c yaw angle near the subsolar point. f. s. patt, saic gsc, november 25, 1998.
98 c
99 c added data initialization statements for p and q to ensure they get saved
100 c between calls. f. s. patt, saic gsc, april 14, 1999
101 c
102 c modifed calculation of sun vector measurement covariance to avoid
103 c numerical round-off errors for sun vector very close to -x axis.
104 c f. s. patt, saic gsc, august 27, 1999
105 c
106 c increased state noise for roll and yaw to 2.5e-9 based on results of testing
107 c with revised horizon scanner calibration and sun sensor alignments.
108 c f. s. patt, saic gsc, september 20, 1999
109 c
110 c modified state noise calculation to use delta_t**2 (instead of abs(delta_t))
111 c to reduce noise for hrpt/lac, and changed qvar(from 2.5e-9 to 4.0e-9) to
112 c offset this for gac; this is based on initial results of testing for the
113 c mergered 1-km(mlac) files.
114 c f. s. patt, saic, november 22, 2002
115 
116  implicit none
117 #include "nav_cnst.fin"
118 #include "navblk_s.fin"
119 #include "navctl_s.fin"
120 c
121  type(navblk_struct) :: navblk ! note we only want the block for 1 line
122  type(navctl_struct) :: navctl
123  integer*4 widphfl1, widphfl2, sunbodfl
124  real*4 nad_bod(3), sun_bod(3), attxfm(3,3), widphse1(2),
125  1 widphse2(2), pos(3), vel(3), att_prev(3), delta_t, covar(3)
126 c
127  real*8 xk(3,6), p(3,3), r(6,6), g(6,3), xid(3,3), d(3,3), q(3,3)
128  real*8 t33(3,3), t66(6,6), t36(3,6), yg(6), gt(3,6), dt(3,3)
129  real*8 t6(6), t3(3), r33(3,3), s33(3,3), xx(6,3)
130  real*4 dmda(3,3,3), dvda(3,3), cpit, spit, crol, srol, cyaw, syaw
131  real*4 att_ap(3), apm(3,3), sunvar, earvar, qvar(3), vmag, tv(3)
132  integer*4 nyaw, ier, i, j, nadbodfl
133  real*4 pmag, yawest, sr(3), nr(3)
134  logical recomp, update
135 
136 c set variances for sun and earth vectors and state noise
137  data sunvar/1.e-6/, earvar/3.e-6/, qvar/2*4.0e-9,4.0e-9/
138 c identity matrix
139  data xid/1.d0,3*0.d0,1.d0,3*0.d0,1.d0/
140  data d/1.d0,3*0.d0,1.d0,3*0.d0,1.d0/
141  data p/1.d0,3*0.d0,1.d0,3*0.d0,1.d0/
142  data q/9*0.d0/
143  data r/36*0.d0/
144 
145 c compute state propagation and noise covariance matrices
146  d(2,1) = delta_t*.00106d0
147  d(1,2) = -d(2,1)
148  do i=1,3
149 c q(i,i) = abs(delta_t)*qvar(i)
150  q(i,i) = delta_t*delta_t*qvar(i)
151  end do
152 
153 c If first scan of scene(delta_t = 0), set state covariance and attitude
154  if (delta_t.eq.0.0) then
155  do i=1,3
156  att_ap(i) = 0.0
157  do j=1,3
158  p(i,j) = xid(i,j)
159  apm(i,j) = xid(i,j)
160  end do
161  enddo
162  else
163 
164 c compute a priori attitude and matrix based on previous attitude
165 
166 c propagate attitude using simple dynamics model(wertz, eq. 13-86)
167 c may replace this with a more sophisticated model at a later date
168 c need to do this in-line to handle mixed precision
169  do i=1,3
170  att_ap(i) = d(i,1)*att_prev(1) + d(i,2)*att_prev(2)
171  * + d(i,3)*att_prev(3)
172  end do
173  call euler(att_ap, apm)
174 
175 c propagate state covariance matrix and add state noise(wertz, eq. 13-88)
176  call dmatmp(d,p,t33,3,3,3)
177  call dxpose(d,dt,3,3)
178  call dmatmp(t33,dt,p,3,3,3)
179  do i=1,3
180  do j=1,3
181  p(i,j) = p(i,j) + q(i,j)
182  end do
183  end do
184  end if
185 
186 c call matmpy(apm, attxfm, m)
187 
188 c compute reference vectors in a prior spacecraft frame
189  pmag = vmag(pos)
190 c call matvec(m, pos, nr)
191 c do i=1,3
192 c nr(i) = -nr(i)/pmag
193 c end do
194 c call matvec(m, navblk%sun_ref(1), sr)
195 
196 c compute partial derivatives of attitude matrix with respect to angles
197  cyaw = cos(att_ap(1)/radeg)
198  syaw = sin(att_ap(1)/radeg)
199  crol = cos(att_ap(2)/radeg)
200  srol = sin(att_ap(2)/radeg)
201  cpit = cos(att_ap(3)/radeg)
202  spit = sin(att_ap(3)/radeg)
203  do i=1,3
204  dmda(1,i,1) = 0.0
205  dmda(2,i,1) = apm(3,i)
206  dmda(3,i,1) = -apm(2,i)
207  dmda(i,1,2) = -apm(i,3)*cpit
208  dmda(i,2,2) = apm(i,3)*spit
209  dmda(i,1,3) = apm(i,2)
210  dmda(i,2,3) = -apm(i,1)
211  dmda(i,3,3) = 0.0
212  end do
213  dmda(1,3,2) = crol
214  dmda(2,3,2) = -syaw*srol
215  dmda(3,3,2) = -cyaw*srol
216 
217 c initialize for yaw iteration if necessary
218 
219  nyaw = 0
220  recomp = .true.
221  update = .false.
222  yawest = att_ap(1)
223 c
224  dowhile( recomp )
225  call earth( pos, vel, widphse1, widphfl1, widphse2, widphfl2,
226  1 yawest, navctl, nad_bod, nadbodfl, navblk%sun_ref(3) )
227 
228 c initialize arrays
229  do i=1,6
230  yg(i) = 0.d0
231  r(i,i) = 1.d0
232  do j=1,3
233  g(i,j) = 0.d0
234  xk(j,i) = 0.d0
235  end do
236  end do
237 
238 c compute partial derivative matrix and difference vector
239 
240 c If there is valid sun data
241  if (sunbodfl.eq.0) then
242 
243 c compute partials of sun vector with respect to attitude angles
244  call matvec(attxfm, navblk%sun_ref(1), tv)
245 
246  do i=1,3
247  call matvec(dmda(1,1,i),tv,dvda(1,i))
248  end do
249  call matvec(apm,tv,sr)
250 
251 c load into g matrix and compute difference vector
252  do i=1,3
253  yg(i) = sun_bod(i) - sr(i)
254  r(i,i) = sunvar*(1.0001d0 - sr(i)*sr(i))
255 c r(i,i) = sunvar
256  do j=1,3
257  g(i,j) = dvda(i,j)
258  end do
259  end do
260  end if
261 
262 c If there is valid earth data
263  if (nadbodfl.eq.0) then
264 
265 c compute partials of earth vector with respect to attitude angles
266  call matvec(attxfm, pos,tv)
267  do i=1,3
268  tv(i) = -tv(i)/pmag
269  end do
270  do i=1,3
271  call matvec(dmda(1,1,i),tv,dvda(1,i))
272  end do
273  call matvec(apm,tv,nr)
274 
275 c load into g matrix and compute difference vector
276  do i=1,3
277  yg(i+3) = nad_bod(i) - nr(i)
278  r(i+3,i+3) = earvar
279  do j=1,3
280  g(i+3,j) = dvda(i,j)
281  end do
282  end do
283  end if
284 
285 c If there are observations, correct attitude and update covariance
286  if ( (sunbodfl.eq.0) .or. (nadbodfl.eq.0) ) then
287 
288 c compute gain matrix(wertz, eq. 13-74)
289  call dxpose(g,gt,6,3)
290  call dmatmp(p,gt,t36,3,3,6)
291  call dmatmp(g,t36,t66,6,3,6)
292  do i=1,6
293  t66(i,i) = t66(i,i) + r(i,i)
294  end do
295  call invert(t66,yg,6,6,t6,ier)
296  call dmatmp(gt,t66,t36,3,6,6)
297  call dmatmp(p,t36,xk,3,3,6)
298 
299 c compute update to attitude angles
300  call dmatmp(xk,yg,t3,3,6,1)
301  do i=1,3
302  navblk%att_ang(i) = att_ap(i) + radeg*t3(i)
303  end do
304  update = .true.
305 
306 c Else, use propagated attitude
307  else
308  do i=1,3
309  navblk%att_ang(i) = att_ap(i)
310  end do
311 
312  end if
313 c
314 c if the re-compute yaw value is greater than the
315 c the tolerence and
316 c
317  nyaw = nyaw + 1
318  if( navctl%redoyaw .ge. nyaw .and.
319  1 abs( navblk%att_ang(1) - yawest) .gt. navctl%yawtol ) then
320  recomp = .true.
321  yawest = navblk%att_ang(1)
322  else
323  recomp = .false.
324  end if
325  end do
326 
327 c update covariance matrix(wertz, eq. 13-76)
328  call dmatmp(xk,g,t33,3,6,3)
329  do i=1,3
330  do j=1,3
331  t33(i,j) = xid(i,j) - t33(i,j)
332  end do
333  end do
334  call dmatmp(t33,p,r33,3,3,3)
335  call dxpose(t33,s33,3,3)
336  call dmatmp(r33,s33,p,3,3,3)
337  call dmatmp(xk,r,t36,3,6,6)
338  call dxpose(xk,xx,3,6)
339  call dmatmp(t36,xx,t33,3,6,3)
340  do i=1,3
341  do j=1,3
342  p(i,j) = p(i,j) + t33(i,j)
343  end do
344  end do
345 
346  if (navctl%lvdbug.gt.2) then
347  write (66,*) ((att_ap(i) - att_prev(i)),i=1,3)
348  write (66,*) ((navblk%att_ang(i) - att_ap(i)),i=1,3)
349  write (66,*) yg
350  do i=1,6
351  t6(i) = 0.d0
352  do j=1,3
353  t6(i) = t6(i) + g(i,j)*t3(j)
354  end do
355  end do
356  write (66,*) t6
357  end if
358 
359 c add diagonal elements of covariance matrix to output array
360  do i=1,3
361  covar(i) = p(i,i)
362  end do
363 
364 c
365 c and end
366 c
367  return
368  end
369 
370  subroutine dmatmp(dm1, dm2, dm3, l, m, n)
371 c
372 c dmatmp( dm1, dm2, dm3, l, m, n)
373 c
374 c purpose: multiply two general double-precision matrices
375 c
376 c calling arguments:
377 c
378 c name Type i/o description
379 c -------- ---- --- -----------
380 c dm1 r*8 i input matrix of size l-by-m
381 c dm2 r*8 i input matrix of size m-by-n
382 c dm3 r*8 o output matrix of size l-by-n
383 c l i*4 i number of rows in dm1 and dm3
384 c m i*4 i number of columns in dm1 and rows in dm2
385 c n i*4 i number of columns in dm2 and dm3
386 c
387 c by: f. s. patt, saic gsc, june 2, 1998
388 c
389 c
390 c modification history:
391 c
392  implicit none
393  integer*4 l,m,n
394  real*8 dm1(l,m),dm2(m,n),dm3(l,n)
395  integer*4 i,j,k
396 
397 c compute dm3 as dm1 x dm2
398  do i=1,l
399  do j=1,n
400  dm3(i,j) = 0.d0
401  do k=1,m
402  dm3(i,j) = dm3(i,j) + dm1(i,k)*dm2(k,j)
403  end do
404  end do
405  end do
406 
407  return
408  end
409 
410  subroutine dxpose(din, dout, n, m)
411 c
412 c dxpose( din, dout, n, m )
413 c
414 c purpose: form the transpose of matrix din to matrix dout
415 c
416 c calling arguments:
417 c
418 c name Type i/o description
419 c -------- ---- --- -----------
420 c din r*8 i size n by m input matrix
421 c dout r*8 o size m by n output matrix
422 c n i*4 i number of rows in din
423 c m i*4 i number of columns in din
424 c
425 c by: f. s. patt, saic gsc, june 2, 1998
426 c
427 c notes:
428 c
429 c modification history:
430 c
431  implicit none
432  integer*4 n, m
433  real*8 din(n,m), dout(m,n)
434 c
435  integer*4 i, j
436 c
437 c
438  do i = 1, n
439  do j = 1, m
440  dout(j,i) = din(i,j)
441  end do
442  end do
443 c
444  return
445  end
int navigation(int32_t fileID)
Definition: l1_octs_hdf.c:696
float * vector(long nl, long nh)
Definition: nrutil.c:15
double reflect(double *pnts, double y[], double psum[], short ndim, FITSTRUCT *auxdata, double(*func)(FITSTRUCT *, double[]), short ibig, float fac)
Definition: amoeba.c:87
void spin(double st, double *pos1, double *pos2)
subroutine invert(a, b, n, l, c, ier)
Definition: invert.f:3
subroutine attdet(navblk, navctl, nad_bod, attxfm,
Definition: attdet.f:2
void initialize(int pixref_flag, int blkref_flag)
Definition: Usds.c:1371
subroutine earth(pos, vel, widphse1, widphfl1, widphse2,
Definition: earth.f:2
#define sign(x)
Definition: misc.h:95
float ** matrix(long nrl, long nrh, long ncl, long nch)
Definition: nrutil.c:60
#define real
Definition: DbAlgOcean.cpp:26
real *4 function vmag(vec)
Definition: vmag.f:2
subroutine dxpose(din, dout, n, m)
Definition: attdet.f:411
int state(double tjdTDB, JPLIntUtilType *util, double posvel[13][6], double *pnut)
subroutine matvec(xm, v1, v2)
Definition: matvec.f:2
#define re
Definition: l1_czcs_hdf.c:701
void load(float x1, float v[], float y[])
===========================================================================V5.0.48(Terra) 03/20/2015 Changes shown below are differences from MOD_PR02 V5.0.46(Terra)============================================================================Changes noted for V6.1.20(Terra) below were also instituted for this version.============================================================================V6.1.20(Terra) 03/12/2015 Changes shown below are differences from MOD_PR02 V6.1.18(Terra)============================================================================Changes from v6.1.18 which may affect scientific output:A situation can occur in which a scan which contains sector rotated data has a telemetry value indicating the completeness of the sector rotation. This issue is caused by the timing of the instrument command to perform the sector rotation and the recording of the telemetry point that reports the status of sector rotation. In this case a scan is considered valid by L1B and pass through the calibration - reporting extremely high radiances. Operationally the TEB calibration uses a 40 scan average coefficient, so the 20 scans(one mirror side) after the sector rotation are contaminated with anomalously high radiance values. A similar timing issue appeared before the sector rotation was fixed in V6.1.2. Our analysis indicates the ‘SET_FR_ENC_DELTA’ telemetry correlates well with the sector rotation encoder position. The use of this telemetry point to determine scans that are sector rotated should fix the anomaly occured before and after the sector rotation(usually due to the lunar roll maneuver). The fix related to the sector rotation in V6.1.2 is removed in this version.============================================================================V6.1.18(Terra) 10/01/2014 Changes shown below are differences from MOD_PR02 V6.1.16(Terra)============================================================================Added doi attributes to NRT(Near-Real-Time) product.============================================================================V6.1.16(Terra) 01/27/2014 Changes shown below are differences from MOD_PR02 V6.1.14(Terra)============================================================================Migrate to SDP Toolkit 5.2.17============================================================================V6.1.14(Terra) 06/26/2012 Changes shown below are differences from MOD_PR02 V6.1.12(Terra)============================================================================Added the doi metadata to L1B product============================================================================V6.1.12(Terra) 04/25/2011 Changes shown below are differences from MOD_PR02 V6.1.8(Terra)============================================================================1. The algorithm to calculate uncertainties for reflective solar bands(RSB) is updated. The current uncertainty in L1B code includes 9 terms from prelaunch analysis. The new algorithm regroups them with the new added contributions into 5 terms:u1:the common term(AOI and time independent) and
Definition: HISTORY.txt:126
subroutine dmatmp(dm1, dm2, dm3, l, m, n)
Definition: attdet.f:371
#define near(x, y)
Definition: l1_viirs_h5.c:30
void filter(fctlstr *fctl, l1qstr *l1que, l1str *l1rec, int32_t dscan)
Definition: filter.c:1396
set(CMAKE_CXX_FLAGS "${CMAKE_CXX_FLAGS} -DWITH_MPI") target_link_libraries(afrt_nc4 $
Definition: CMakeLists.txt:16
subroutine euler(a, xm)
Definition: euler.f:2
#define eq(a, b)
Definition: rice.h:167
subroutine phase
Definition: phase.f:2
#define f
Definition: l1_czcs_hdf.c:702
for(i=0;i< NROOTS;i++) s[i]
Definition: decode_rs.h:85
Definition: dataday.h:40
subroutine matmpy(xm1, xm2, xm3)
Definition: ocorient.f:197
#define abs(a)
Definition: misc.h:90
this program makes no use of any feature of the SDP Toolkit that could generate such a then geolocation is calculated at that and then aggregated up to Resolved feature request Bug by adding three new int8 SDSs for each high resolution offsets between the high resolution geolocation and a bi linear interpolation extrapolation of the positions This can be used to reconstruct the high resolution geolocation Resolved Bug by delaying cumulation of gflags until after validation of derived products Resolved Bug by setting Latitude and Longitude to the correct fill resolving to support Near Real Time because they may be unnecessary if use of entrained ephemeris and attitude data is turned on(as it will be in Near-Real-Time processing).
algorithm
Definition: DDProcess.h:25
void transpose(float *in[], float *out[])
Definition: get_zenaz.c:97