lsp.c 18 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641
  1. /*---------------------------------------------------------------------------*\
  2. Original copyright
  3. FILE........: lsp.c
  4. AUTHOR......: David Rowe
  5. DATE CREATED: 24/2/93
  6. Heavily modified by Jean-Marc Valin (c) 2002-2006 (fixed-point,
  7. optimizations, additional functions, ...)
  8. This file contains functions for converting Linear Prediction
  9. Coefficients (LPC) to Line Spectral Pair (LSP) and back. Note that the
  10. LSP coefficients are not in radians format but in the x domain of the
  11. unit circle.
  12. Speex License:
  13. Redistribution and use in source and binary forms, with or without
  14. modification, are permitted provided that the following conditions
  15. are met:
  16. - Redistributions of source code must retain the above copyright
  17. notice, this list of conditions and the following disclaimer.
  18. - Redistributions in binary form must reproduce the above copyright
  19. notice, this list of conditions and the following disclaimer in the
  20. documentation and/or other materials provided with the distribution.
  21. - Neither the name of the Xiph.org Foundation nor the names of its
  22. contributors may be used to endorse or promote products derived from
  23. this software without specific prior written permission.
  24. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
  25. ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
  26. LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
  27. A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE FOUNDATION OR
  28. CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL,
  29. EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO,
  30. PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR
  31. PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
  32. LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING
  33. NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
  34. SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
  35. */
  36. /*---------------------------------------------------------------------------*\
  37. Introduction to Line Spectrum Pairs (LSPs)
  38. ------------------------------------------
  39. LSPs are used to encode the LPC filter coefficients {ak} for
  40. transmission over the channel. LSPs have several properties (like
  41. less sensitivity to quantisation noise) that make them superior to
  42. direct quantisation of {ak}.
  43. A(z) is a polynomial of order lpcrdr with {ak} as the coefficients.
  44. A(z) is transformed to P(z) and Q(z) (using a substitution and some
  45. algebra), to obtain something like:
  46. A(z) = 0.5[P(z)(z+z^-1) + Q(z)(z-z^-1)] (1)
  47. As you can imagine A(z) has complex zeros all over the z-plane. P(z)
  48. and Q(z) have the very neat property of only having zeros _on_ the
  49. unit circle. So to find them we take a test point z=exp(jw) and
  50. evaluate P (exp(jw)) and Q(exp(jw)) using a grid of points between 0
  51. and pi.
  52. The zeros (roots) of P(z) also happen to alternate, which is why we
  53. swap coefficients as we find roots. So the process of finding the
  54. LSP frequencies is basically finding the roots of 5th order
  55. polynomials.
  56. The root so P(z) and Q(z) occur in symmetrical pairs at +/-w, hence
  57. the name Line Spectrum Pairs (LSPs).
  58. To convert back to ak we just evaluate (1), "clocking" an impulse
  59. thru it lpcrdr times gives us the impulse response of A(z) which is
  60. {ak}.
  61. \*---------------------------------------------------------------------------*/
  62. #ifdef HAVE_CONFIG_H
  63. #include "config.h"
  64. #endif
  65. #include <math.h>
  66. #include "lsp.h"
  67. #include "stack_alloc.h"
  68. #include "math_approx.h"
  69. #ifndef M_PI
  70. #define M_PI 3.14159265358979323846 /* pi */
  71. #endif
  72. #ifndef NULL
  73. #define NULL 0
  74. #endif
  75. #ifdef FIXED_POINT
  76. #define FREQ_SCALE 16384
  77. /*#define ANGLE2X(a) (32768*cos(((a)/8192.)))*/
  78. #define ANGLE2X(a) (SHL16(spx_cos(a),2))
  79. /*#define X2ANGLE(x) (acos(.00006103515625*(x))*LSP_SCALING)*/
  80. #define X2ANGLE(x) (spx_acos(x))
  81. #ifdef BFIN_ASM
  82. #include "lsp_bfin.h"
  83. #endif
  84. #else
  85. /*#define C1 0.99940307
  86. #define C2 -0.49558072
  87. #define C3 0.03679168*/
  88. #define FREQ_SCALE 1.
  89. #define ANGLE2X(a) (spx_cos(a))
  90. #define X2ANGLE(x) (acos(x))
  91. #endif
  92. #ifndef DISABLE_ENCODER
  93. /*---------------------------------------------------------------------------*\
  94. FUNCTION....: cheb_poly_eva()
  95. AUTHOR......: David Rowe
  96. DATE CREATED: 24/2/93
  97. This function evaluates a series of Chebyshev polynomials
  98. \*---------------------------------------------------------------------------*/
  99. #ifdef FIXED_POINT
  100. #ifndef OVERRIDE_CHEB_POLY_EVA
  101. static inline spx_word32_t cheb_poly_eva(
  102. spx_word16_t *coef, /* P or Q coefs in Q13 format */
  103. spx_word16_t x, /* cos of freq (-1.0 to 1.0) in Q14 format */
  104. int m, /* LPC order/2 */
  105. char *stack
  106. )
  107. {
  108. int i;
  109. spx_word16_t b0, b1;
  110. spx_word32_t sum;
  111. /*Prevents overflows*/
  112. if (x>16383)
  113. x = 16383;
  114. if (x<-16383)
  115. x = -16383;
  116. /* Initialise values */
  117. b1=16384;
  118. b0=x;
  119. /* Evaluate Chebyshev series formulation using an iterative approach */
  120. sum = ADD32(EXTEND32(coef[m]), EXTEND32(MULT16_16_P14(coef[m-1],x)));
  121. for(i=2;i<=m;i++)
  122. {
  123. spx_word16_t tmp=b0;
  124. b0 = SUB16(MULT16_16_Q13(x,b0), b1);
  125. b1 = tmp;
  126. sum = ADD32(sum, EXTEND32(MULT16_16_P14(coef[m-i],b0)));
  127. }
  128. return sum;
  129. }
  130. #endif
  131. #else
  132. static float cheb_poly_eva(spx_word32_t *coef, spx_word16_t x, int m, char *stack)
  133. {
  134. int k;
  135. float b0, b1, tmp;
  136. /* Initial conditions */
  137. b0=0; /* b_(m+1) */
  138. b1=0; /* b_(m+2) */
  139. x*=2;
  140. /* Calculate the b_(k) */
  141. for(k=m;k>0;k--)
  142. {
  143. tmp=b0; /* tmp holds the previous value of b0 */
  144. b0=x*b0-b1+coef[m-k]; /* b0 holds its new value based on b0 and b1 */
  145. b1=tmp; /* b1 holds the previous value of b0 */
  146. }
  147. return(-b1+.5*x*b0+coef[m]);
  148. }
  149. #endif
  150. /*---------------------------------------------------------------------------*\
  151. FUNCTION....: lpc_to_lsp()
  152. AUTHOR......: David Rowe
  153. DATE CREATED: 24/2/93
  154. This function converts LPC coefficients to LSP
  155. coefficients.
  156. \*---------------------------------------------------------------------------*/
  157. #ifdef FIXED_POINT
  158. #define SIGN_CHANGE(a,b) ((((a)^(b))&0x80000000)||(b==0))
  159. #else
  160. #define SIGN_CHANGE(a,b) (((a)*(b))<0.0)
  161. #endif
  162. int lpc_to_lsp (spx_coef_t *a,int lpcrdr,spx_lsp_t *freq,int nb,spx_word16_t delta, char *stack)
  163. /* float *a lpc coefficients */
  164. /* int lpcrdr order of LPC coefficients (10) */
  165. /* float *freq LSP frequencies in the x domain */
  166. /* int nb number of sub-intervals (4) */
  167. /* float delta grid spacing interval (0.02) */
  168. {
  169. spx_word16_t temp_xr,xl,xr,xm=0;
  170. spx_word32_t psuml,psumr,psumm,temp_psumr/*,temp_qsumr*/;
  171. int i,j,m,k;
  172. VARDECL(spx_word32_t *Q); /* ptrs for memory allocation */
  173. VARDECL(spx_word32_t *P);
  174. VARDECL(spx_word16_t *Q16); /* ptrs for memory allocation */
  175. VARDECL(spx_word16_t *P16);
  176. spx_word32_t *px; /* ptrs of respective P'(z) & Q'(z) */
  177. spx_word32_t *qx;
  178. spx_word32_t *p;
  179. spx_word32_t *q;
  180. spx_word16_t *pt; /* ptr used for cheb_poly_eval()
  181. whether P' or Q' */
  182. int roots=0; /* DR 8/2/94: number of roots found */
  183. m = lpcrdr/2; /* order of P'(z) & Q'(z) polynomials */
  184. /* Allocate memory space for polynomials */
  185. ALLOC(Q, (m+1), spx_word32_t);
  186. ALLOC(P, (m+1), spx_word32_t);
  187. /* determine P'(z)'s and Q'(z)'s coefficients where
  188. P'(z) = P(z)/(1 + z^(-1)) and Q'(z) = Q(z)/(1-z^(-1)) */
  189. px = P; /* initialise ptrs */
  190. qx = Q;
  191. p = px;
  192. q = qx;
  193. #ifdef FIXED_POINT
  194. *px++ = LPC_SCALING;
  195. *qx++ = LPC_SCALING;
  196. for(i=0;i<m;i++){
  197. *px++ = SUB32(ADD32(EXTEND32(a[i]),EXTEND32(a[lpcrdr-i-1])), *p++);
  198. *qx++ = ADD32(SUB32(EXTEND32(a[i]),EXTEND32(a[lpcrdr-i-1])), *q++);
  199. }
  200. px = P;
  201. qx = Q;
  202. for(i=0;i<m;i++)
  203. {
  204. /*if (fabs(*px)>=32768)
  205. speex_warning_int("px", *px);
  206. if (fabs(*qx)>=32768)
  207. speex_warning_int("qx", *qx);*/
  208. *px = PSHR32(*px,2);
  209. *qx = PSHR32(*qx,2);
  210. px++;
  211. qx++;
  212. }
  213. /* The reason for this lies in the way cheb_poly_eva() is implemented for fixed-point */
  214. P[m] = PSHR32(P[m],3);
  215. Q[m] = PSHR32(Q[m],3);
  216. #else
  217. *px++ = LPC_SCALING;
  218. *qx++ = LPC_SCALING;
  219. for(i=0;i<m;i++){
  220. *px++ = (a[i]+a[lpcrdr-1-i]) - *p++;
  221. *qx++ = (a[i]-a[lpcrdr-1-i]) + *q++;
  222. }
  223. px = P;
  224. qx = Q;
  225. for(i=0;i<m;i++){
  226. *px = 2**px;
  227. *qx = 2**qx;
  228. px++;
  229. qx++;
  230. }
  231. #endif
  232. px = P; /* re-initialise ptrs */
  233. qx = Q;
  234. /* now that we have computed P and Q convert to 16 bits to
  235. speed up cheb_poly_eval */
  236. ALLOC(P16, m+1, spx_word16_t);
  237. ALLOC(Q16, m+1, spx_word16_t);
  238. for (i=0;i<m+1;i++)
  239. {
  240. P16[i] = P[i];
  241. Q16[i] = Q[i];
  242. }
  243. /* Search for a zero in P'(z) polynomial first and then alternate to Q'(z).
  244. Keep alternating between the two polynomials as each zero is found */
  245. xr = 0; /* initialise xr to zero */
  246. xl = FREQ_SCALE; /* start at point xl = 1 */
  247. for(j=0;j<lpcrdr;j++){
  248. if(j&1) /* determines whether P' or Q' is eval. */
  249. pt = Q16;
  250. else
  251. pt = P16;
  252. psuml = cheb_poly_eva(pt,xl,m,stack); /* evals poly. at xl */
  253. while(xr >= -FREQ_SCALE){
  254. spx_word16_t dd;
  255. /* Modified by JMV to provide smaller steps around x=+-1 */
  256. #ifdef FIXED_POINT
  257. dd = MULT16_16_Q15(delta,SUB16(FREQ_SCALE, MULT16_16_Q14(MULT16_16_Q14(xl,xl),14000)));
  258. if (psuml<512 && psuml>-512)
  259. dd = PSHR16(dd,1);
  260. #else
  261. dd=delta*(1-.9*xl*xl);
  262. if (fabs(psuml)<.2)
  263. dd *= .5;
  264. #endif
  265. xr = SUB16(xl, dd); /* interval spacing */
  266. psumr = cheb_poly_eva(pt,xr,m,stack);/* poly(xl-delta_x) */
  267. temp_psumr = psumr;
  268. temp_xr = xr;
  269. /* if no sign change increment xr and re-evaluate poly(xr). Repeat til
  270. sign change.
  271. if a sign change has occurred the interval is bisected and then
  272. checked again for a sign change which determines in which
  273. interval the zero lies in.
  274. If there is no sign change between poly(xm) and poly(xl) set interval
  275. between xm and xr else set interval between xl and xr and repeat till
  276. root is located within the specified limits */
  277. if(SIGN_CHANGE(psumr,psuml))
  278. {
  279. roots++;
  280. psumm=psuml;
  281. for(k=0;k<=nb;k++){
  282. #ifdef FIXED_POINT
  283. xm = ADD16(PSHR16(xl,1),PSHR16(xr,1)); /* bisect the interval */
  284. #else
  285. xm = .5*(xl+xr); /* bisect the interval */
  286. #endif
  287. psumm=cheb_poly_eva(pt,xm,m,stack);
  288. /*if(psumm*psuml>0.)*/
  289. if(!SIGN_CHANGE(psumm,psuml))
  290. {
  291. psuml=psumm;
  292. xl=xm;
  293. } else {
  294. psumr=psumm;
  295. xr=xm;
  296. }
  297. }
  298. /* once zero is found, reset initial interval to xr */
  299. freq[j] = X2ANGLE(xm);
  300. xl = xm;
  301. break;
  302. }
  303. else{
  304. psuml=temp_psumr;
  305. xl=temp_xr;
  306. }
  307. }
  308. }
  309. return(roots);
  310. }
  311. #endif /* DISABLE_ENCODER */
  312. /*---------------------------------------------------------------------------*\
  313. FUNCTION....: lsp_to_lpc()
  314. AUTHOR......: David Rowe
  315. DATE CREATED: 24/2/93
  316. Converts LSP coefficients to LPC coefficients.
  317. \*---------------------------------------------------------------------------*/
  318. #ifdef FIXED_POINT
  319. void lsp_to_lpc(const spx_lsp_t *freq,spx_coef_t *ak,int lpcrdr, char *stack)
  320. /* float *freq array of LSP frequencies in the x domain */
  321. /* float *ak array of LPC coefficients */
  322. /* int lpcrdr order of LPC coefficients */
  323. {
  324. int i,j;
  325. spx_word32_t xout1,xout2,xin;
  326. spx_word32_t mult, a;
  327. VARDECL(spx_word16_t *freqn);
  328. VARDECL(spx_word32_t **xp);
  329. VARDECL(spx_word32_t *xpmem);
  330. VARDECL(spx_word32_t **xq);
  331. VARDECL(spx_word32_t *xqmem);
  332. int m = lpcrdr>>1;
  333. /*
  334. Reconstruct P(z) and Q(z) by cascading second order polynomials
  335. in form 1 - 2cos(w)z(-1) + z(-2), where w is the LSP frequency.
  336. In the time domain this is:
  337. y(n) = x(n) - 2cos(w)x(n-1) + x(n-2)
  338. This is what the ALLOCS below are trying to do:
  339. int xp[m+1][lpcrdr+1+2]; // P matrix in QIMP
  340. int xq[m+1][lpcrdr+1+2]; // Q matrix in QIMP
  341. These matrices store the output of each stage on each row. The
  342. final (m-th) row has the output of the final (m-th) cascaded
  343. 2nd order filter. The first row is the impulse input to the
  344. system (not written as it is known).
  345. The version below takes advantage of the fact that a lot of the
  346. outputs are zero or known, for example if we put an inpulse
  347. into the first section the "clock" it 10 times only the first 3
  348. outputs samples are non-zero (it's an FIR filter).
  349. */
  350. ALLOC(xp, (m+1), spx_word32_t*);
  351. ALLOC(xpmem, (m+1)*(lpcrdr+1+2), spx_word32_t);
  352. ALLOC(xq, (m+1), spx_word32_t*);
  353. ALLOC(xqmem, (m+1)*(lpcrdr+1+2), spx_word32_t);
  354. for(i=0; i<=m; i++) {
  355. xp[i] = xpmem + i*(lpcrdr+1+2);
  356. xq[i] = xqmem + i*(lpcrdr+1+2);
  357. }
  358. /* work out 2cos terms in Q14 */
  359. ALLOC(freqn, lpcrdr, spx_word16_t);
  360. for (i=0;i<lpcrdr;i++)
  361. freqn[i] = ANGLE2X(freq[i]);
  362. #define QIMP 21 /* scaling for impulse */
  363. xin = SHL32(EXTEND32(1), (QIMP-1)); /* 0.5 in QIMP format */
  364. /* first col and last non-zero values of each row are trivial */
  365. for(i=0;i<=m;i++) {
  366. xp[i][1] = 0;
  367. xp[i][2] = xin;
  368. xp[i][2+2*i] = xin;
  369. xq[i][1] = 0;
  370. xq[i][2] = xin;
  371. xq[i][2+2*i] = xin;
  372. }
  373. /* 2nd row (first output row) is trivial */
  374. xp[1][3] = -MULT16_32_Q14(freqn[0],xp[0][2]);
  375. xq[1][3] = -MULT16_32_Q14(freqn[1],xq[0][2]);
  376. xout1 = xout2 = 0;
  377. /* now generate remaining rows */
  378. for(i=1;i<m;i++) {
  379. for(j=1;j<2*(i+1)-1;j++) {
  380. mult = MULT16_32_Q14(freqn[2*i],xp[i][j+1]);
  381. xp[i+1][j+2] = ADD32(SUB32(xp[i][j+2], mult), xp[i][j]);
  382. mult = MULT16_32_Q14(freqn[2*i+1],xq[i][j+1]);
  383. xq[i+1][j+2] = ADD32(SUB32(xq[i][j+2], mult), xq[i][j]);
  384. }
  385. /* for last col xp[i][j+2] = xq[i][j+2] = 0 */
  386. mult = MULT16_32_Q14(freqn[2*i],xp[i][j+1]);
  387. xp[i+1][j+2] = SUB32(xp[i][j], mult);
  388. mult = MULT16_32_Q14(freqn[2*i+1],xq[i][j+1]);
  389. xq[i+1][j+2] = SUB32(xq[i][j], mult);
  390. }
  391. /* process last row to extra a{k} */
  392. for(j=1;j<=lpcrdr;j++) {
  393. int shift = QIMP-13;
  394. /* final filter sections */
  395. a = PSHR32(xp[m][j+2] + xout1 + xq[m][j+2] - xout2, shift);
  396. xout1 = xp[m][j+2];
  397. xout2 = xq[m][j+2];
  398. /* hard limit ak's to +/- 32767 */
  399. if (a < -32767) a = -32767;
  400. if (a > 32767) a = 32767;
  401. ak[j-1] = (short)a;
  402. }
  403. }
  404. #else
  405. void lsp_to_lpc(const spx_lsp_t *freq,spx_coef_t *ak,int lpcrdr, char *stack)
  406. /* float *freq array of LSP frequencies in the x domain */
  407. /* float *ak array of LPC coefficients */
  408. /* int lpcrdr order of LPC coefficients */
  409. {
  410. int i,j;
  411. float xout1,xout2,xin1,xin2;
  412. VARDECL(float *Wp);
  413. float *pw,*n1,*n2,*n3,*n4=NULL;
  414. VARDECL(float *x_freq);
  415. int m = lpcrdr>>1;
  416. ALLOC(Wp, 4*m+2, float);
  417. pw = Wp;
  418. /* initialise contents of array */
  419. for(i=0;i<=4*m+1;i++){ /* set contents of buffer to 0 */
  420. *pw++ = 0.0;
  421. }
  422. /* Set pointers up */
  423. pw = Wp;
  424. xin1 = 1.0;
  425. xin2 = 1.0;
  426. ALLOC(x_freq, lpcrdr, float);
  427. for (i=0;i<lpcrdr;i++)
  428. x_freq[i] = ANGLE2X(freq[i]);
  429. /* reconstruct P(z) and Q(z) by cascading second order
  430. polynomials in form 1 - 2xz(-1) +z(-2), where x is the
  431. LSP coefficient */
  432. for(j=0;j<=lpcrdr;j++){
  433. int i2=0;
  434. for(i=0;i<m;i++,i2+=2){
  435. n1 = pw+(i*4);
  436. n2 = n1 + 1;
  437. n3 = n2 + 1;
  438. n4 = n3 + 1;
  439. xout1 = xin1 - 2.f*x_freq[i2] * *n1 + *n2;
  440. xout2 = xin2 - 2.f*x_freq[i2+1] * *n3 + *n4;
  441. *n2 = *n1;
  442. *n4 = *n3;
  443. *n1 = xin1;
  444. *n3 = xin2;
  445. xin1 = xout1;
  446. xin2 = xout2;
  447. }
  448. xout1 = xin1 + *(n4+1);
  449. xout2 = xin2 - *(n4+2);
  450. if (j>0)
  451. ak[j-1] = (xout1 + xout2)*0.5f;
  452. *(n4+1) = xin1;
  453. *(n4+2) = xin2;
  454. xin1 = 0.0;
  455. xin2 = 0.0;
  456. }
  457. }
  458. #endif
  459. #ifdef FIXED_POINT
  460. void lsp_interpolate(spx_lsp_t *old_lsp, spx_lsp_t *new_lsp, spx_lsp_t *lsp, int len, int subframe, int nb_subframes, spx_word16_t margin)
  461. {
  462. int i;
  463. spx_word16_t m = margin;
  464. spx_word16_t m2 = 25736-margin;
  465. spx_word16_t tmp = DIV32_16(SHL32(EXTEND32(1 + subframe),14),nb_subframes);
  466. spx_word16_t tmp2 = 16384-tmp;
  467. for (i=0;i<len;i++)
  468. lsp[i] = MULT16_16_P14(tmp2,old_lsp[i]) + MULT16_16_P14(tmp,new_lsp[i]);
  469. /* Enforce margin to sure the LSPs are stable*/
  470. if (lsp[0]<m)
  471. lsp[0]=m;
  472. if (lsp[len-1]>m2)
  473. lsp[len-1]=m2;
  474. for (i=1;i<len-1;i++)
  475. {
  476. if (lsp[i]<lsp[i-1]+m)
  477. lsp[i]=lsp[i-1]+m;
  478. if (lsp[i]>lsp[i+1]-m)
  479. lsp[i]= SHR16(lsp[i],1) + SHR16(lsp[i+1]-m,1);
  480. }
  481. }
  482. #else
  483. void lsp_interpolate(spx_lsp_t *old_lsp, spx_lsp_t *new_lsp, spx_lsp_t *lsp, int len, int subframe, int nb_subframes, spx_word16_t margin)
  484. {
  485. int i;
  486. float tmp = (1.0f + subframe)/nb_subframes;
  487. for (i=0;i<len;i++)
  488. lsp[i] = (1-tmp)*old_lsp[i] + tmp*new_lsp[i];
  489. /* Enforce margin to sure the LSPs are stable*/
  490. if (lsp[0]<LSP_SCALING*margin)
  491. lsp[0]=LSP_SCALING*margin;
  492. if (lsp[len-1]>LSP_SCALING*(M_PI-margin))
  493. lsp[len-1]=LSP_SCALING*(M_PI-margin);
  494. for (i=1;i<len-1;i++)
  495. {
  496. if (lsp[i]<lsp[i-1]+LSP_SCALING*margin)
  497. lsp[i]=lsp[i-1]+LSP_SCALING*margin;
  498. if (lsp[i]>lsp[i+1]-LSP_SCALING*margin)
  499. lsp[i]= .5f* (lsp[i] + lsp[i+1]-LSP_SCALING*margin);
  500. }
  501. }
  502. #endif