@Phorce is right here. I don't think there is any reson to reinvent the wheel. However, if you want to do this so that you understand the methodology and to have the joy of coding it yourself I can provide a FORTRAN FFT code that I developed some years ago. Of course this is not C++ and will require a translation; this should not be too difficult and should enable you to learn a lot in doing so...
Below is a Radix 4 based algorithm; this radix-4 FFT recursively partitions a DFT into four quarter-length DFTs of groups of every fourth time sample. The outputs of these shorter FFTs are reused to compute many outputs, thus greatly reducing the total computational cost. The radix-4 decimation-in-frequency FFT groups every fourth output sample into shorter-length DFTs to save computations. The radix-4 FFTs require only 75% as many complex multiplies as the radix-2 FFTs. See here for more information.
!+ FILE: RADIX4.FOR ! =================================================================== ! Discription: Radix 4 is a descreet complex Fourier transform algorithim. It ! is to be supplied with two real arrays, one for real parts of function ! one for imaginary parts: It can also unscramble transformed arrays. ! Usage: calling FASTF(XREAL,XIMAG,ISIZE,ITYPE,IFAULT); we supply the ! following: ! ! XREAL - array containing real parts of transform sequence ! XIMAG - array containing imagianry parts of transformation sequence ! ISIZE - size of transform (ISIZE = 4*2*M) ! ITYPE - +1 forward transform ! -1 reverse transform ! IFAULT - 1 if error ! - 0 otherwise ! =================================================================== ! ! Forward transform computes: ! X(k) = sum_{j=0}^{isize-1} x(j)*exp(-2ijk*pi/isize) ! Backward computes: ! x(j) = (1/isize) sum_{k=0}^{isize-1} X(k)*exp(ijk*pi/isize) ! ! Forward followed by backwards will result in the origonal sequence! ! ! =================================================================== SUBROUTINE FASTF(XREAL,XIMAG,ISIZE,ITYPE,IFAULT) REAL*8 XREAL(*),XIMAG(*) INTEGER MAX2,II,IPOW PARAMETER (MAX2 = 20) ! Check for valid transform size upto 2**(max2): IFAULT = 1 IF(ISIZE.LT.4) THEN print*,'FFT: Error: Data array < 4 - Too small!' return ENDIF II = 4 IPOW = 2 ! Prepare mod 2: 1 IF((II-ISIZE).NE.0) THEN II = II*2 IPOW = IPOW + 1 IF(IPOW.GT.MAX2) THEN print*,'FFT: Error: FFT1!' return ENDIF GOTO 1 ENDIF ! Check for correct type: IF(IABS(ITYPE).NE.1) THEN print*,'FFT: Error: Wrong type of transformation!' return ENDIF ! No entry errors - continue: IFAULT = 0 ! call FASTG to preform transformation: CALL FASTG(XREAL,XIMAG,ISIZE,ITYPE) ! Due to Radix 4 factorisation results are not in the same order ! after transformation as they were when the data was submitted: ! We now call SCRAM, to unscramble the reults: CALL SCRAM(XREAL,XIMAG,ISIZE,IPOW) return END !-END: RADIX4.FOR ! =============================================================== ! Discription: This is the radix 4 complex descreet fast Fourier ! transform with out unscrabling. Suitable for convolutions or other ! applications that do not require unscrambling. Designed for use ! with FASTF.FOR. ! SUBROUTINE FASTG(XREAL,XIMAG,N,ITYPE) INTEGER N,IFACA,IFCAB,LITLA INTEGER I0,I1,I2,I3 REAL*8 XREAL(*),XIMAG(*),BCOS,BSIN,CW1,CW2,PI REAL*8 SW1,SW2,SW3,TEMPR,X1,X2,X3,XS0,XS1,XS2,XS3 REAL*8 Y1,Y2,Y3,YS0,YS1,YS2,YS3,Z,ZATAN,ZFLOAT,ZSIN ZATAN(Z) = ATAN(Z) ZFLOAT(K) = FLOAT(K) ! Real equivalent of K. ZSIN(Z) = SIN(Z) PI = (4.0)*ZATAN(1.0) IFACA = N/4 ! Forward transform: IF(ITYPE.GT.0) THEN GOTO 5 ENDIF ! If this is for an inverse transform - conjugate the data: DO 4, K = 1,N XIMAG(K) = -XIMAG(K) 4 CONTINUE 5 IFCAB = IFACA*4 ! Proform appropriate transformations: Z = PI/ZFLOAT(IFCAB) BCOS = -2.0*ZSIN(Z)**2 BSIN = ZSIN(2.0*Z) CW1 = 1.0 SW1 = 0.0 ! This is the main body of radix 4 calculations: DO 10, LITLA = 1,IFACA DO 8, I0 = LITLA,N,IFCAB I1 = I0 + IFACA I2 = I1 + IFACA I3 = I2 + IFACA XS0 = XREAL(I0) + XREAL(I2) XS1 = XREAL(I0) - XREAL(I2) YS0 = XIMAG(I0) + XIMAG(I2) YS1 = XIMAG(I0) - XIMAG(I2) XS2 = XREAL(I1) + XREAL(I3) XS3 = XREAL(I1) - XREAL(I3) YS2 = XIMAG(I1) + XIMAG(I3) YS3 = XIMAG(I1) - XIMAG(I3) XREAL(I0) = XS0 + XS2 XIMAG(I0) = YS0 + YS2 X1 = XS1 + YS3 Y1 = YS1 - XS3 X2 = XS0 - XS2 Y2 = YS0 - YS2 X3 = XS1 - YS3 Y3 = YS1 + XS3 IF(LITLA.GT.1) THEN GOTO 7 ENDIF XREAL(I2) = X1 XIMAG(I2) = Y1 XREAL(I1) = X2 XIMAG(I1) = Y2 XREAL(I3) = X3 XIMAG(I3) = Y3 GOTO 8 ! Now IF required - we multiply by twiddle factors: 7 XREAL(I2) = X1*CW1 + Y1*SW1 XIMAG(I2) = Y1*CW1 - X1*SW1 XREAL(I1) = X2*CW2 + Y2*SW2 XIMAG(I1) = Y2*CW2 - X2*SW2 XREAL(I3) = X3*CW3 + Y3*SW3 XIMAG(I3) = Y3*CW3 - X3*SW3 8 CONTINUE IF(LITLA.EQ.IFACA) THEN GOTO 10 ENDIF ! Calculate a new set of twiddle factors: Z = CW1*BCOS - SW1*BSIN + CW1 SW1 = BCOS*SW1 + BSIN*CW1 + SW1 TEMPR = 1.5 - 0.5*(Z*Z + SW1*SW1) CW1 = Z*TEMPR SW1 = SW1*TEMPR CW2 = CW1*CW1 - SW1*SW1 SW2 = 2.0*CW1*SW1 CW3 = CW1*CW2 - SW1*SW2 SW3 = CW1*SW2 + CW2*SW1 10 CONTINUE IF(IFACA.LE.1) THEN GOTO 14 ENDIF ! Set up tranform split for next stage: IFACA = IFACA/4 IF(IFACA.GT.0) THEN GOTO 5 ENDIF ! This is the calculation of a radix two-stage: DO 13, K = 1,N,2 TEMPR = XREAL(K) + XREAL(K + 1) XREAL(K + 1) = XREAL(K) - XREAL(K + 1) XREAL(K) = TEMPR TEMPR = XIMAG(K) + XIMAG(K + 1) XIMAG(K + 1) = XIMAG(K) - XIMAG(K + 1) XIMAG(K) = TEMPR 13 CONTINUE 14 IF(ITYPE.GT.0) THEN GOTO 17 ENDIF ! For the inverse case, cojugate and scale the transform: Z = 1.0/ZFLOAT(N) DO 16, K = 1,N XIMAG(K) = -XIMAG(K)*Z XREAL(K) = XREAL(K)*Z 16 CONTINUE 17 return END ! ---------------------------------------------------------- !-END of subroutine FASTG.FOR. ! ---------------------------------------------------------- !+ FILE: SCRAM.FOR ! ========================================================== ! Discription: Subroutine for unscrambiling FFT data: ! ========================================================== SUBROUTINE SCRAM(XREAL,XIMAG,N,IPOW) INTEGER L(19),II,J1,J2,J3,J4,J5,J6,J7,J8,J9,J10,J11,J12 INTEGER J13,J14,J15,J16,J17,J18,J19,J20,ITOP,I REAL*8 XREAL(*),XIMAG(*),TEMPR EQUIVALENCE (L1,L(1)),(L2,L(2)),(L3,L(3)),(L4,L(4)) EQUIVALENCE (L5,L(5)),(L6,L(6)),(L7,L(7)),(L8,L(8)) EQUIVALENCE (L9,L(9)),(L10,L(10)),(L11,L(11)),(L12,L(12)) EQUIVALENCE (L13,L(13)),(L14,L(14)),(L15,L(15)),(L16,L(16)) EQUIVALENCE (L17,L(17)),(L18,L(18)),(L19,L(19)) II = 1 ITOP = 2**(IPOW - 1) I = 20 - IPOW DO 5, K = 1,I L(K) = II 5 CONTINUE L0 = II I = I + 1 DO 6, K = I,19 II = II*2 L(K) = II 6 CONTINUE II = 0 DO 9, J1 = 1,L1,L0 DO 9, J2 = J1,L2,L1 DO 9, J3 = J2,L3,L2 DO 9, J4 = J3,L4,L3 DO 9, J5 = J4,L5,L4 DO 9, J6 = J5,L6,L5 DO 9, J7 = J6,L7,L6 DO 9, J8 = J7,L8,L7 DO 9, J9 = J8,L9,L8 DO 9, J10 = J9,L10,L9 DO 9, J11 = J10,L11,L10 DO 9, J12 = J11,L12,L11 DO 9, J13 = J12,L13,L12 DO 9, J14 = J13,L14,L13 DO 9, J15 = J14,L15,L14 DO 9, J16 = J15,L16,L15 DO 9, J17 = J16,L17,L16 DO 9, J18 = J17,L18,L17 DO 9, J19 = J18,L19,L18 J20 = J19 DO 9, I = 1,2 II = II +1 IF(II.GE.J20) THEN GOTO 8 ENDIF ! J20 is the bit reverse of II! ! Pairwise exchange: TEMPR = XREAL(II) XREAL(II) = XREAL(J20) XREAL(J20) = TEMPR TEMPR = XIMAG(II) XIMAG(II) = XIMAG(J20) XIMAG(J20) = TEMPR 8 J20 = J20 + ITOP 9 CONTINUE return END ! ------------------------------------------------------------------- !-END: ! -------------------------------------------------------------------
Going through this and understanding it will take time! I wrote this using a CalTech paper I found years ago, I cannot recall the reference I am afraid. Good luck.
I hope this helps.
PIto 7 figures. (Ignoring performance of course; for a large input, this will be enormously slower than the equivalent FFT).