LALPulsar  6.1.0.1-89842e6
PulsarCrossCorr.c
Go to the documentation of this file.
1 /*
2  * Copyright (C) 2007 Badri Krishnan
3  * Copyright (C) 2008 Christine Chung, Badri Krishnan and John Whelan
4  *
5  * This program is free software; you can redistribute it and/or modify
6  * it under the terms of the GNU General Public License as published by
7  * the Free Software Foundation; either version 2 of the License, or
8  * (at your option) any later version.
9  *
10  * This program is distributed in the hope that it will be useful,
11  * but WITHOUT ANY WARRANTY; without even the implied warranty of
12  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
13  * GNU General Public License for more details.
14  *
15  * You should have received a copy of the GNU General Public License
16  * along with with program; see the file COPYING. If not, write to the
17  * Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston,
18  * MA 02110-1301 USA
19  */
20 
21 #include <lal/DopplerScan.h>
22 #include <lal/PulsarCrossCorr.h>
23 #include <gsl/gsl_permutation.h>
24 
25 #define SQUARE(x) (x*x)
26 
27 /* this function is currently unused (20/07/09) */
29  INT4VectorSequence **out,
30  SFTListElement *in,
31  REAL8 lag,
32  INT4 listLength,
33  DetChoice detChoice,
34  BOOLEAN autoCorrelate )
35 {
36 
37  INT4 i, j, numPairs, initj;
38  INT4 thisPair;
39  INT4 sameDet = 0;
40  INT4Vector *List1, *List2;
41  INT4VectorSequence *ret;
42  COMPLEX8FrequencySeries *thisSFT1, *thisSFT2;
43  LIGOTimeGPS t1, t2;
44  REAL8 timeDiff;
45  SFTListElement *sfttmp;
46 
47  INITSTATUS( status );
49 
51 
52  *out = NULL;
53 
54 
55  List1 = XLALCreateINT4Vector( listLength );
56  List2 = XLALCreateINT4Vector( listLength );
57 
58  numPairs = 0; /* initialization */
59 
60  thisPair = 0;
61  sfttmp = in;
62 
63  /*just need to check the first sft against the others */
64  thisSFT1 = &( sfttmp->sft );
65  i = 0;
66 
67  /*if we're autocorrelating, then j starts from 0, otherwise it starts from 1*/
68  if ( autoCorrelate ) {
69  initj = 0;
70  } else {
71  initj = 1;
72  }
73 
74  for ( j = initj; j < listLength; j++ ) {
75 
76  if ( j > 0 ) {
77  sfttmp = ( SFTListElement * )sfttmp->nextSFT;
78  }
79 
80  thisSFT2 = &( sfttmp->sft );
81  /* calculate time difference */
82  t1 = thisSFT1->epoch;
83  t2 = thisSFT2->epoch;
84  timeDiff = XLALGPSDiff( &t1, &t2 );
85 
86  /*strcmp returns 0 if strings are equal, >0 if strings are different*/
87  sameDet = strcmp( thisSFT1->name, thisSFT2->name );
88 
89  /* if they are different, set sameDet to 1 so that it will match if
90  detChoice == DIFFERENT */
91  if ( sameDet != 0 ) {
92  sameDet = 1;
93  }
94 
95  /* however, if detChoice = ALL, then we want sameDet to match it */
96  if ( detChoice == ALL ) {
97  sameDet = detChoice;
98  }
99 
100  /* decide whether to add this pair or not */
101  if ( ( sameDet == ( INT4 )detChoice ) && ( fabs( timeDiff ) <= lag ) ) {
102  numPairs++;
103 
104  List1->data[thisPair] = i;
105  List2->data[thisPair++] = j;
106  } /* if ( numPairs < out->length) */
107 
108  thisSFT2 = NULL;
109  } /* end loop over second sft set */
110 
111  thisSFT1 = NULL;
112  /* } end loop over first sft set */
113 
114 
115  /* initialise pair list vector, if we have pairs*/
116  if ( numPairs > 0 ) {
117  ret = XLALCreateINT4VectorSequence( 2, numPairs );
118 
119  for ( i = 0; i < numPairs; i++ ) {
120 
121  ret->data[i] = List1->data[i];
122  ret->data[i + numPairs] = List2->data[i];
123  }
124  } else {
125  ret = NULL;
126  }
127 
128  ( *out ) = ret;
129 
130  XLALDestroyINT4Vector( List1 );
131  XLALDestroyINT4Vector( List2 );
132  sfttmp = NULL;
133 
135 
136  /* normal exit */
137  RETURN( status );
138 
139 } /* CreateSFTPairsIndicesFrom2SFTvectors */
140 
141 
142 /**
143  * Correlate a single pair of SFT at a parameter space point. This function calculates Y_alpha
144  * according to Eqn 4.1 in Dhurandar et al 2008, where
145  * Y_alpha = (xI* xJ)/Delta T^2
146  * sft1 and sft2 have been normalised by XLALNormalizeSFT in pulsar_crosscorr.c, so they are actually
147  * sft1 = xI/sqrt(psd1), sft2 = xJ/sqrt(psd2)
148  * Therefore, when calculating the output, we need to have
149  * out = sft1*sqrt(psd1)*sft2*sqrt(psd2)/Delta T^2
150  */
152  COMPLEX16 *out,
155  REAL8FrequencySeries *psd1,
156  REAL8FrequencySeries *psd2,
157  UINT4 bin1,
158  UINT4 bin2 )
159 {
160  REAL8 deltaF;
161  REAL8 re1, re2, im1, im2;
162 
163  INITSTATUS( status );
169 
170  /* assume both sfts have the same freq. resolution */
171  deltaF = sft1->deltaF;
172 
173  /* check that frequencies are in the right range */
174  if ( bin1 >= ( sft1->data->length ) ) {
176  }
177  /* check that frequencies are in the right range */
178  if ( bin2 >= ( sft2->data->length ) ) {
180  }
181 
182  re1 = crealf( sft1->data->data[bin1] );
183  im1 = cimagf( sft1->data->data[bin1] );
184  re2 = crealf( sft2->data->data[bin2] );
185  im2 = cimagf( sft2->data->data[bin2] );
186 
187  *( out ) = crect( ( deltaF * deltaF * sqrt( psd1->data->data[bin1] * psd2->data->data[bin2] ) ) * ( re1 * re2 + im1 * im2 ), ( deltaF * deltaF * sqrt( psd1->data->data[bin1] * psd2->data->data[bin2] ) ) * ( re1 * im2 - re2 * im1 ) );
188 
189  /*
190  printf("bin1 bin2 %d %d\n", bin1, bin2);
191  printf("psd1 psd2 %1.15g %1.15g\n", psd1->data->data[bin1], psd2->data->data[bin2]);
192  printf("sft1.re sft1.im %1.15g %1.15g\n", re1*sqrt(psd1->data->data[bin1]), im1*sqrt(psd1->data->data[bin1]));
193  printf("sft2.re sft2.im %1.15g %1.15g\n\n", re2*sqrt(psd2->data->data[bin2]), im2*sqrt(psd2->data->data[bin2]));
194  */
196 
197  /* normal exit */
198  RETURN( status );
199 
200 }
201 
202 
203 
204 
205 /** Calculate the frequency of the SFT at a given epoch */
206 /* This is according to Eqns 2.11 and 2.12 of Dhurandhar et al 2008 */
208  REAL8 *out,
209  LIGOTimeGPS *epoch,
210  PulsarDopplerParams *dopp,
211  REAL8Vector *vel_c )
212 {
213  UINT4 k;
214  REAL8 alpha, delta;
215  REAL8 vDotn_c, fhat, factor, timeDiff;
216 
217  INITSTATUS( status );
219 
223 
224  alpha = dopp->Alpha;
225  delta = dopp->Delta;
226 
227 
228  vDotn_c = cos( delta ) * cos( alpha ) * vel_c->data[0]
229  + cos( delta ) * sin( alpha ) * vel_c->data[1]
230  + sin( delta ) * vel_c->data[2];
231 
232  /* now calculate the intrinsic signal frequency in the SFT */
233  /* fhat = f_0 + f_1(t-t0) + f_2(t-t0)^2/2 + ... */
234 
235  /* this is the sft reference time - the pulsar reference time */
236  timeDiff = XLALGPSDiff( ( epoch ), &( dopp->refTime ) );
237  fhat = dopp->fkdot[0]; /* initialization */
238  factor = 1.0;
239  for ( k = 1; k < PULSAR_MAX_SPINS; k++ ) {
240  factor *= timeDiff / k;
241  fhat += dopp->fkdot[k] * factor;
242  }
243  *out = fhat * ( 1 + vDotn_c );
244 
246 
247  /* normal exit */
248  RETURN( status );
249 }
250 
251 
252 
253 /** Get signal phase at a given epoch */
254 /* This is according to Eqn 2.13 in Dhurandar et al 2008 */
255 /* and includes the 2nd order term that is left out in the paper */
257  REAL8 *out,
258  LIGOTimeGPS *epoch,
259  PulsarDopplerParams *dopp,
260  REAL8Vector *r_c )
261 {
262  UINT4 k;
263  REAL8 alpha, delta;
264  REAL8 rDotn_c, phihat, factor, timeDiff;
265  REAL8 epoch_plus_rdotn;
266 
267  INITSTATUS( status );
269 
273 
274  alpha = dopp->Alpha;
275  delta = dopp->Delta;
276 
277  rDotn_c = cos( delta ) * cos( alpha ) * r_c->data[0]
278  + cos( delta ) * sin( alpha ) * r_c->data[1]
279  + sin( delta ) * r_c->data[2];
280 
281 
282  /* now calculate the phase of the SFT */
283  /* phi(t) = phi_0 + 2pi(f_0 t + 0.5 f_1 t^2) + 2pi (f_0 + f_1 t) r.n/c */
284 
285  /* this is the sft reference time - the pulsar reference time */
286  /* we need to convert epoch to REAL8 first before adding rdotn
287  * because if LIGOTimeGPS only has INT4 accuracy. converting rdotn into LIGOTimeGPS
288  * will introduce rounding errors*/
289  epoch_plus_rdotn = XLALGPSGetREAL8( epoch ) + rDotn_c;
290  timeDiff = epoch_plus_rdotn - XLALGPSGetREAL8( &( dopp->refTime ) );
291 
292  phihat = 0.0;
293 
294  factor = 1.0;
295 
296  for ( k = 1; k <= PULSAR_MAX_SPINS; k++ ) {
297  factor *= timeDiff / k;
298  phihat += dopp->fkdot[k - 1] * factor;
299  }
300 
301  *out = LAL_TWOPI * ( phihat );
303  /* normal exit */
304  RETURN( status );
305 }
306 
307 /* This function calculates sigma_alpha^2 according to Eqn 4.13 in Dhurandar
308  * et al 2008, where
309  * sigma_alpha^2 = Sn1*Sn2/(4 DeltaT^2)
310  * psd1 and psd2 as returned by XLALNormalizeSFT are
311  * psd1 = DeltaT*Sn1/2, psd2 = DeltaT*Sn2/2
312  * so when calculating the output, we need to compute
313  * out = psd1*psd2/DeltaT^4
314  * where the factor of DeltaT^2/4 is absorbed in psd1 and psd2*/
316  REAL8 *out,
317  UINT4 bin1,
318  UINT4 bin2,
319  REAL8FrequencySeries *psd1,
320  REAL8FrequencySeries *psd2 )
321 {
322  REAL8 deltaF;
323 
324  INITSTATUS( status );
326 
329 
330  deltaF = psd1->deltaF;
331 
332  *out = SQUARE( deltaF ) * SQUARE( deltaF ) * psd1->data->data[bin1] * psd2->data->data[bin2];
334  /* normal exit */
335  RETURN( status );
336 
337 }
338 
339 /** Calculate pair weights (U_alpha) for an average over Psi and cos(iota) **/
340 /* G_IJ is calculated according to Eqn 3.17 in Dhurandhar et al 2008
341  * and Ualpha is calculated according to Eqn 4.10 of the same paper */
343  COMPLEX16 *out,
344  REAL8 phiI,
345  REAL8 phiJ,
346  REAL8 freqI,
347  REAL8 freqJ,
348  REAL8 deltaF,
349  CrossCorrBeamFn beamfnsI,
350  CrossCorrBeamFn beamfnsJ,
351  REAL8 sigmasq )
352 {
353  REAL8 deltaPhi;
354  REAL8 re, im;
355  INITSTATUS( status );
357 
358  deltaPhi = phiI - phiJ - LAL_PI * ( freqI - freqJ ) / deltaF;
359  /*calculate G_IJ. In this case, we have <G_IJ> = 0.1*(exp^(-i delta phi)) * (aIaJ + bIbJ)*/
360  re = 0.1 * cos( deltaPhi ) * ( ( beamfnsI.a * beamfnsJ.a ) + ( beamfnsI.b * beamfnsJ.b ) );
361  im = - 0.1 * sin( deltaPhi ) * ( ( beamfnsI.a * beamfnsJ.a ) + ( beamfnsI.b * beamfnsJ.b ) );
362 
363  /*calculate Ualpha*/
364  *( out ) = crect( re / ( sigmasq ), -im / ( sigmasq ) );
365 
367 
368  /* normal exit */
369  RETURN( status );
370 
371 
372 }
373 /** Calculate pair weights (U_alpha) for the general case **/
374 /* G_IJ is calculated according to Eqn 3.10 of Dhurandar et al 2008.
375  * deltaPhi is calculated from Eqn 3.11, and Ualpha is calculated according to
376  * Eqn 4.10 of the same paper.
377  * The Fplus, Fcross terms are calculated according to Eqns 2.9a and 2.9b */
379  COMPLEX16 *out,
380  CrossCorrAmps amplitudes,
381  REAL8 phiI,
382  REAL8 phiJ,
383  REAL8 freqI,
384  REAL8 freqJ,
385  REAL8 deltaF,
386  CrossCorrBeamFn beamfnsI,
387  CrossCorrBeamFn beamfnsJ,
388  REAL8 sigmasq,
389  REAL8 *psi,
390  COMPLEX16 *gplus,
391  COMPLEX16 *gcross )
392 {
393  REAL8 deltaPhi;
394  REAL8 re, im;
395  REAL8 FplusI, FplusJ, FcrossI, FcrossJ;
396  REAL8 FpIFpJ, FcIFcJ, FpIFcJ, FcIFpJ;
397 
398  INITSTATUS( status );
400 
401  deltaPhi = phiI - phiJ - LAL_PI * ( freqI - freqJ ) / deltaF;
402 
403 
404  /*if not averaging over psi, calculate F+, Fx exactly*/
405  if ( psi ) {
406  FplusI = ( beamfnsI.a * cos( 2.0 * ( *psi ) ) ) + ( beamfnsI.b * sin( 2.0 * ( *psi ) ) );
407  FplusJ = ( beamfnsJ.a * cos( 2.0 * ( *psi ) ) ) + ( beamfnsJ.b * sin( 2.0 * ( *psi ) ) );
408  FcrossI = ( beamfnsI.b * cos( 2.0 * ( *psi ) ) ) - ( beamfnsI.a * sin( 2.0 * ( *psi ) ) );
409  FcrossJ = ( beamfnsJ.b * cos( 2.0 * ( *psi ) ) ) - ( beamfnsJ.a * sin( 2.0 * ( *psi ) ) );;
410 
411  /*calculate G_IJ*/
412  re = 0.25 * ( ( cos( deltaPhi ) * ( FplusI * FplusJ * amplitudes.Aplussq + FcrossI * FcrossJ * amplitudes.Acrosssq ) )
413  - ( sin( deltaPhi ) * ( ( FplusI * FcrossJ - FcrossI * FplusJ ) * amplitudes.AplusAcross ) ) );
414 
415 
416  im = 0.25 * ( -( cos( deltaPhi ) * ( ( FplusI * FcrossJ - FcrossI * FplusJ ) * amplitudes.AplusAcross ) )
417  - ( sin( deltaPhi ) * ( FplusI * FplusJ * amplitudes.Aplussq + FcrossI * FcrossJ * amplitudes.Acrosssq ) ) );
418 
419  /*calculate estimators*/
420  *( gplus ) = crect( 0.25 * cos( deltaPhi ) * FplusI * FplusJ, 0.25 * ( -sin( deltaPhi ) ) * FplusI * FplusJ );
421 
422  *( gcross ) = crect( 0.25 * cos( deltaPhi ) * FcrossI * FcrossJ, 0.25 * ( -sin( deltaPhi ) ) * FcrossI * FcrossJ );
423 
424 
425  } else {
426  FpIFpJ = 0.5 * ( ( beamfnsI.a * beamfnsJ.a ) + ( beamfnsI.b * beamfnsJ.b ) );
427  FcIFcJ = 0.5 * ( ( beamfnsI.a * beamfnsJ.a ) + ( beamfnsI.b * beamfnsJ.b ) );
428  FpIFcJ = 0.5 * ( ( beamfnsI.a * beamfnsJ.b ) - ( beamfnsI.b * beamfnsJ.a ) );
429  FcIFpJ = 0.5 * ( ( beamfnsJ.a * beamfnsI.b ) - ( beamfnsJ.b * beamfnsI.a ) );
430 
431  /*calculate G_IJ*/
432  re = 0.25 * ( ( cos( deltaPhi ) *
433  ( ( FpIFpJ * amplitudes.Aplussq ) + ( FcIFcJ * amplitudes.Acrosssq ) ) )
434  - ( sin( deltaPhi ) * ( ( FpIFcJ - FcIFpJ ) * amplitudes.AplusAcross ) ) );
435 
436 
437  im = 0.25 * ( -( cos( deltaPhi ) * ( ( FpIFcJ - FcIFpJ ) * amplitudes.AplusAcross ) )
438  - ( sin( deltaPhi ) *
439  ( ( FpIFpJ * amplitudes.Aplussq ) + ( FcIFcJ * amplitudes.Acrosssq ) ) ) );
440 
441  }
442 
443 
444  /*calculate Ualpha*/
445  *( out ) = crect( re / ( sigmasq ), -im / ( sigmasq ) );
446 
447 
448 
450 
451  /* normal exit */
452  RETURN( status );
453 
454 }
455 
456 
457 /* Calculate rho, the cross correlation power,
458  * according to Eqn 4.4 in Dhurandhar et al 2008 */
460  REAL8 *out,
461  COMPLEX16Vector *yalpha,
462  COMPLEX16Vector *ualpha )
463 {
464  INT4 i;
465 
466  INITSTATUS( status );
468 
472 
473  *out = 0;
474 
475  for ( i = 0; i < ( INT4 )yalpha->length; i++ ) {
476 
477  *out += 2.0 * ( ( creal( yalpha->data[i] ) * creal( ualpha->data[i] ) ) - ( cimag( yalpha->data[i] ) * cimag( ualpha->data[i] ) ) );
478 
479  }
480 
482 
483  /* normal exit */
484  RETURN( status );
485 
486 }
487 
488 /* Calculate the variance of the cross correlation power.
489  * The variance is given by sigma^2 in Eqn 4.6 of Dhurandhar et al 2008 */
491  REAL8 *out,
492  COMPLEX16Vector *ualpha,
493  REAL8Vector *sigmaAlphasq )
494 {
495  INT4 i;
496  REAL8 variance = 0;
497 
498  INITSTATUS( status );
500 
504 
505 
506  for ( i = 0; i < ( INT4 )ualpha->length; i++ ) {
507  variance += ( SQUARE( creal( ualpha->data[i] ) ) + SQUARE( cimag( ualpha->data[i] ) ) ) * sigmaAlphasq->data[i];
508 
509  }
510 
511  variance *= 2.0;
512  *out = variance;
514 
515  /* normal exit */
516  RETURN( status );
517 
518 
519 }
520 
521 /* Calculate the estimators for Aplus, Asq.
522  * Eqn 6.4 of Dhurandhar et al 2008 */
524  REAL8 *aplussq1,
525  REAL8 *aplussq2,
526  REAL8 *acrossq1,
527  REAL8 *acrossq2,
528  COMPLEX16Vector *yalpha,
529  COMPLEX16Vector *gplus,
530  COMPLEX16Vector *gcross,
531  REAL8Vector *sigmaAlphasq )
532 {
533  INT4 i;
534  REAL8 ap1 = 0, ap2 = 0, ac1 = 0, ac2 = 0;
535 
536  INITSTATUS( status );
538 
542 
543 
544  for ( i = 0; i < ( INT4 )yalpha->length; i++ ) {
545  ap1 += 2.0 * ( SQUARE( creal( gplus->data[i] ) ) + SQUARE( cimag( gplus->data[i] ) ) ) / sigmaAlphasq->data[i];
546  ac1 += 2.0 * ( SQUARE( creal( gcross->data[i] ) ) + SQUARE( cimag( gcross->data[i] ) ) ) / sigmaAlphasq->data[i];
547  ap2 += 2.0 * ( ( creal( yalpha->data[i] ) * creal( gplus->data[i] ) ) + ( cimag( yalpha->data[i] ) * cimag( gplus->data[i] ) ) ) / sigmaAlphasq->data[i];
548  ac2 += 2.0 * ( ( creal( yalpha->data[i] ) * creal( gcross->data[i] ) ) + ( cimag( yalpha->data[i] ) * cimag( gcross->data[i] ) ) ) / sigmaAlphasq->data[i];
549  }
550 
551  *aplussq1 = ap1;
552  *aplussq2 = ap2;
553  *acrossq1 = ac1;
554  *acrossq2 = ac2;
556 
557  /* normal exit */
558  RETURN( status );
559 
560 
561 }
562 
int j
int k
static double double delta
#define ABORT(statusptr, code, mesg)
#define ATTATCHSTATUSPTR(statusptr)
#define ASSERT(assertion, statusptr, code, mesg)
#define DETATCHSTATUSPTR(statusptr)
#define INITSTATUS(statusptr)
#define RETURN(statusptr)
#define SQUARE(x)
INT4VectorSequence * XLALCreateINT4VectorSequence(UINT4 length, UINT4 veclen)
#define LAL_PI
#define LAL_TWOPI
#define crect(re, im)
unsigned char BOOLEAN
double complex COMPLEX16
double REAL8
uint32_t UINT4
int32_t INT4
#define PULSARCROSSCORR_ENULL
void LALCalculateEstimators(LALStatus *status, REAL8 *aplussq1, REAL8 *aplussq2, REAL8 *acrossq1, REAL8 *acrossq2, COMPLEX16Vector *yalpha, COMPLEX16Vector *gplus, COMPLEX16Vector *gcross, REAL8Vector *sigmaAlphasq)
#define PULSARCROSSCORR_EVAL
void LALCalculateAveUalpha(LALStatus *status, COMPLEX16 *out, REAL8 phiI, REAL8 phiJ, REAL8 freqI, REAL8 freqJ, REAL8 deltaF, CrossCorrBeamFn beamfnsI, CrossCorrBeamFn beamfnsJ, REAL8 sigmasq)
Calculate pair weights (U_alpha) for an average over Psi and cos(iota)
void LALCreateSFTPairsIndicesFrom2SFTvectors(LALStatus *status, INT4VectorSequence **out, SFTListElement *in, REAL8 lag, INT4 listLength, DetChoice detChoice, BOOLEAN autoCorrelate)
void LALCalculateSigmaAlphaSq(LALStatus *status, REAL8 *out, UINT4 bin1, UINT4 bin2, REAL8FrequencySeries *psd1, REAL8FrequencySeries *psd2)
void LALGetSignalFrequencyInSFT(LALStatus *status, REAL8 *out, LIGOTimeGPS *epoch, PulsarDopplerParams *dopp, REAL8Vector *vel_c)
Calculate the frequency of the SFT at a given epoch.
#define PULSARCROSSCORR_MSGENULL
void LALCorrelateSingleSFTPair(LALStatus *status, COMPLEX16 *out, COMPLEX8FrequencySeries *sft1, COMPLEX8FrequencySeries *sft2, REAL8FrequencySeries *psd1, REAL8FrequencySeries *psd2, UINT4 bin1, UINT4 bin2)
Correlate a single pair of SFT at a parameter space point.
void LALCalculateUalpha(LALStatus *status, COMPLEX16 *out, CrossCorrAmps amplitudes, REAL8 phiI, REAL8 phiJ, REAL8 freqI, REAL8 freqJ, REAL8 deltaF, CrossCorrBeamFn beamfnsI, CrossCorrBeamFn beamfnsJ, REAL8 sigmasq, REAL8 *psi, COMPLEX16 *gplus, COMPLEX16 *gcross)
Calculate pair weights (U_alpha) for the general case.
void LALGetSignalPhaseInSFT(LALStatus *status, REAL8 *out, LIGOTimeGPS *epoch, PulsarDopplerParams *dopp, REAL8Vector *r_c)
Get signal phase at a given epoch.
void LALCalculateCrossCorrPower(LALStatus *status, REAL8 *out, COMPLEX16Vector *yalpha, COMPLEX16Vector *ualpha)
#define PULSARCROSSCORR_MSGEVAL
void LALNormaliseCrossCorrPower(LALStatus *status, REAL8 *out, COMPLEX16Vector *ualpha, REAL8Vector *sigmaAlphasq)
DetChoice
@ ALL
#define PULSAR_MAX_SPINS
maximal number of spin-parameters (Freq + spindowns) we can handle
INT4Vector * XLALCreateINT4Vector(UINT4 length)
void XLALDestroyINT4Vector(INT4Vector *vector)
REAL8 XLALGPSGetREAL8(const LIGOTimeGPS *epoch)
REAL8 XLALGPSDiff(const LIGOTimeGPS *t1, const LIGOTimeGPS *t0)
out
int deltaF
double alpha
COMPLEX16 * data
CHAR name[LALNameLength]
COMPLEX8Sequence * data
COMPLEX8 * data
INT4 * data
Type containing the 'Doppler-parameters' affecting the time-evolution of the phase.
PulsarSpins fkdot
Intrinsic spins: [Freq, f1dot, f2dot, ...
REAL8 Delta
Sky position: DEC (latitude) in equatorial coords and radians.
LIGOTimeGPS refTime
Reference time of pulsar parameters (in SSB!)
REAL8 Alpha
Sky position: RA (longitude) in equatorial coords and radians.
REAL8Sequence * data
REAL8 * data
struct tagSFTListElement * nextSFT
enum @1 epoch