mirror of
https://github.com/saitohirga/WSJT-X.git
synced 2024-11-04 16:31:17 -05:00
Use Joe's sync vector.
This commit is contained in:
parent
2f7afbc34e
commit
1044342245
@ -8,7 +8,8 @@ subroutine genwsprcpm(msg,msgsent,itone)
|
||||
character*22 msg,msgsent
|
||||
character*64 cbits
|
||||
character*32 sbits
|
||||
integer iuniqueword0
|
||||
character c1*1,c4*4
|
||||
character*31 cseq
|
||||
integer*1,target :: idat(9)
|
||||
integer*1 msgbits(68),codeword(ND)
|
||||
logical first
|
||||
@ -18,20 +19,25 @@ subroutine genwsprcpm(msg,msgsent,itone)
|
||||
integer ipreamble(16) !Freq estimation preamble
|
||||
integer isync(200) !Long sync vector
|
||||
integer itone(NN)
|
||||
data cseq /'9D9F C48B 797A DD60 58CB 2EBC 6'/
|
||||
data ipreamble/1,1,1,1,0,0,0,0,0,0,0,0,1,1,1,1/
|
||||
data first/.true./
|
||||
data iuniqueword0/z'30C9E8AD'/
|
||||
save first,isync,ipreamble
|
||||
|
||||
if(first) then
|
||||
write(sbits,'(b32.32)') iuniqueword0
|
||||
read(sbits,'(32i1)') isync(1:32)
|
||||
read(sbits,'(32i1)') isync(33:64)
|
||||
read(sbits,'(32i1)') isync(65:96)
|
||||
read(sbits,'(32i1)') isync(97:128)
|
||||
read(sbits,'(32i1)') isync(129:160)
|
||||
read(sbits,'(32i1)') isync(161:192)
|
||||
read(sbits,'(8i1)') isync(193:200)
|
||||
k=0
|
||||
do i=1,31
|
||||
c1=cseq(i:i)
|
||||
if(c1.eq.' ') cycle
|
||||
read(c1,'(z1)') n
|
||||
write(c4,'(b4.4)') n
|
||||
do j=1,4
|
||||
k=k+1
|
||||
isync(k)=0
|
||||
if(c4(j:j).eq.'1') isync(k)=1
|
||||
enddo
|
||||
isync(101:200)=isync(1:100)
|
||||
enddo
|
||||
first=.false.
|
||||
endif
|
||||
|
||||
@ -62,9 +68,6 @@ subroutine genwsprcpm(msg,msgsent,itone)
|
||||
itone(101:116)=ipreamble+1
|
||||
itone(117:216)=isync(101:200)+2*codeword(101:200)
|
||||
itone=2*itone-3
|
||||
do i=1,216
|
||||
write(*,*) i,itone(i)
|
||||
enddo
|
||||
|
||||
return
|
||||
end subroutine genwsprcpm
|
||||
|
@ -16,6 +16,7 @@ program wsprcpmd
|
||||
include 'wsprcpm_params.f90'
|
||||
parameter(NMAX=120*12000)
|
||||
character arg*8,message*22,cbits*50,infile*80,fname*16,datetime*11
|
||||
character ch1*1,ch4*4,cseq*31
|
||||
character*22 decodes(100)
|
||||
character*120 data_dir
|
||||
character*32 uwbits
|
||||
@ -42,16 +43,22 @@ program wsprcpmd
|
||||
integer*1 decoded(68),apmask(204),cw(204)
|
||||
integer*1 hbits(216),hbits1(216),hbits3(216)
|
||||
data ipreamble/1,1,1,1,0,0,0,0,0,0,0,0,1,1,1,1/
|
||||
data cseq /'9D9F C48B 797A DD60 58CB 2EBC 6'/
|
||||
data iuniqueword0/z'30C9E8AD'/
|
||||
|
||||
write(uwbits,'(b32.32)') iuniqueword0
|
||||
read(uwbits,'(32i1)') isync(1:32)
|
||||
read(uwbits,'(32i1)') isync(33:64)
|
||||
read(uwbits,'(32i1)') isync(65:96)
|
||||
read(uwbits,'(32i1)') isync(97:128)
|
||||
read(uwbits,'(32i1)') isync(129:160)
|
||||
read(uwbits,'(32i1)') isync(161:192)
|
||||
read(uwbits,'(8i1)') isync(193:200)
|
||||
k=0
|
||||
do i=1,31
|
||||
ch1=cseq(i:i)
|
||||
if(ch1.eq.' ') cycle
|
||||
read(ch1,'(z1)') n
|
||||
write(ch4,'(b4.4)') n
|
||||
do j=1,4
|
||||
k=k+1
|
||||
isync(k)=0
|
||||
if(ch4(j:j).eq.'1') isync(k)=1
|
||||
enddo
|
||||
enddo
|
||||
isync(101:200)=isync(1:100)
|
||||
|
||||
fs=12000.0/NDOWN !Sample rate
|
||||
dt=1.0/fs !Sample interval (s)
|
||||
@ -93,6 +100,7 @@ program wsprcpmd
|
||||
isync2(113:116)=0
|
||||
isync2(117:216)=isync(101:200)
|
||||
|
||||
! data MSB
|
||||
! data sync tone
|
||||
! 0 0 0
|
||||
! 0 1 1
|
||||
@ -104,8 +112,10 @@ program wsprcpmd
|
||||
if(j.eq.0) then
|
||||
dphi0=-3*dphi
|
||||
dphi1=+1*dphi
|
||||
! dphi1=-1*dphi data LSB
|
||||
else
|
||||
dphi0=-1*dphi
|
||||
! dphi0=+1*dphi data LSB
|
||||
dphi1=+3*dphi
|
||||
endif
|
||||
phi0=0.0
|
||||
@ -247,7 +257,7 @@ program wsprcpmd
|
||||
sbits=sbits3
|
||||
hbits=hbits3
|
||||
endif
|
||||
if( count(hbits(101:116).ne.ipreamble) .gt.7 ) cycle
|
||||
! if( count(hbits(101:116).ne.ipreamble) .gt.7 ) cycle
|
||||
|
||||
rxdata(1:100)=sbits(1:100)
|
||||
rxdata(101:200)=sbits(117:216);
|
||||
@ -343,7 +353,6 @@ subroutine coherent_preamble_fsync(c2,h,ipreamble,nsync,nsps,istart,fc,imode,xma
|
||||
enddo
|
||||
first=.false.
|
||||
endif
|
||||
|
||||
dphi=twopi*fc*dt
|
||||
ctwkp=cmplx(0.0,0.0)
|
||||
phi=0
|
||||
@ -355,12 +364,13 @@ subroutine coherent_preamble_fsync(c2,h,ipreamble,nsync,nsps,istart,fc,imode,xma
|
||||
ctmp1=0.0
|
||||
xmax=0.0
|
||||
if(imode.eq.1) then !refine DT with given fc
|
||||
do iii=-40,40,5
|
||||
do iii=-50,50,5
|
||||
ctmp1(0:16*200-1)=c2(ipstart+iii:ipstart+iii+16*200-1)*conjg(ctwkp)
|
||||
xx=abs(sum(ctmp1))
|
||||
if(xx.gt.xmax) then
|
||||
xnorm=sqrt(sum(abs(ctmp1(0:16*200-1))**2))*sqrt(16.0*200.0)
|
||||
xc=abs(sum(ctmp1))/xnorm
|
||||
if(xc.gt.xmax) then
|
||||
iiibest=iii
|
||||
xmax=xx
|
||||
xmax=xc
|
||||
endif
|
||||
enddo
|
||||
istart=istart+iiibest
|
||||
@ -368,6 +378,8 @@ subroutine coherent_preamble_fsync(c2,h,ipreamble,nsync,nsps,istart,fc,imode,xma
|
||||
endif
|
||||
! else refine fc with given DT
|
||||
ctmp1(0:16*200-1)=c2(ipstart:ipstart+16*200-1)*conjg(ctwkp)
|
||||
xnorm=sqrt(sum(abs(ctmp1(0:16*200-1))**2))*sqrt(16.0*200.0)
|
||||
ctmp1=ctmp1/xnorm
|
||||
call four2a(ctmp1,4*16*200,1,-1,1) !c2c FFT to freq domain
|
||||
xmax=0.0
|
||||
ctmp1=cshift(ctmp1,-200)
|
||||
@ -421,7 +433,6 @@ subroutine noncoherent_frame_sync(c2,h,fc,isync2,istart,ssmax)
|
||||
th3=mod(th3+dp3,twopi)
|
||||
enddo
|
||||
ss=0.0
|
||||
totp=0.0
|
||||
avp=0.0
|
||||
xc=0.0
|
||||
do is=1,216
|
||||
@ -435,21 +446,27 @@ subroutine noncoherent_frame_sync(c2,h,fc,isync2,istart,ssmax)
|
||||
p2=sqrt(p2)
|
||||
p3=sqrt(p3)
|
||||
|
||||
totp=totp+p0+p1+p2+p3
|
||||
avp=avp+(p0+p1+p2+p3)/4.0
|
||||
! cmet=(p1+p3)-(p0+p2)
|
||||
cmet=max(p1,p3)-max(p0,p2) ! This works better near threshold SNR
|
||||
if(isync2(is).eq.0) ss=ss-cmet
|
||||
if(isync2(is).eq.1) ss=ss+cmet
|
||||
if(isync2(is).eq.0) xc=xc+max(p0,p2)
|
||||
if(isync2(is).eq.1) xc=xc+max(p1,p3)
|
||||
if(is.le.100 .or. is.ge.117) then
|
||||
if(isync2(is).eq.0) then
|
||||
xc=xc+max(p0,p2)
|
||||
avp=avp+(p1+p3)/2.0
|
||||
elseif(isync2(is).eq.1) then
|
||||
xc=xc+max(p1,p3)
|
||||
avp=avp+(p2+p4)/2.0
|
||||
endif
|
||||
else
|
||||
if(isync2(is).eq.0) then
|
||||
xc=xc+p2
|
||||
avp=avp+(p0+p1+p3)/3.0
|
||||
elseif(isync2(is).eq.1) then
|
||||
xc=xc+p1
|
||||
avp=avp+(p0+p2+p4)/3.0
|
||||
endif
|
||||
endif
|
||||
enddo
|
||||
ss=ss/totp
|
||||
sy=xc/avp
|
||||
! if(ss.gt.ssmax) then
|
||||
if(sy.gt.ssmax) then
|
||||
ioffset=it
|
||||
! ssmax=ss
|
||||
ssmax=sy
|
||||
endif
|
||||
enddo
|
||||
@ -544,7 +561,7 @@ subroutine getcandidate2(c,npts,fs,fa,fb,ncand,candidates)
|
||||
(bigspec(i).gt.1.15).and.ncand.lt.100) then
|
||||
ncand=ncand+1
|
||||
candidates(ncand,1)=df*(i-NH2)
|
||||
candidates(ncand,2)=10*log10(bigspec(i)-1)-30.0
|
||||
candidates(ncand,2)=10*log10(bigspec(i)-1)-26.0
|
||||
endif
|
||||
enddo
|
||||
return
|
||||
|
@ -19,7 +19,7 @@ program wsprcpmsim
|
||||
nargs=iargc()
|
||||
if(nargs.ne.9) then
|
||||
print*,'Usage: wsprcpmsim "message" f0 DT fsp del nwav nfiles snr h'
|
||||
print*,'Example: wsprcpmsim "K1ABC FN42 30" 50 0.0 0.1 1.0 1 10 -33 1.0'
|
||||
print*,'Example: wsprcpmsim "K1ABC FN42 30" 50 1.0 0.1 1.0 1 10 -32 1.0'
|
||||
go to 999
|
||||
endif
|
||||
call getarg(1,msg) !Message to be transmitted
|
||||
@ -59,6 +59,7 @@ program wsprcpmsim
|
||||
c0=0.
|
||||
k=-1 + nint(xdt/dt)
|
||||
do j=1,NN
|
||||
write(*,*) j,itone(j)
|
||||
dp=twopi*(f0+itone(j)*(h/2.0)*baud)*dt
|
||||
do i=1,NSPS
|
||||
k=k+1
|
||||
|
Loading…
Reference in New Issue
Block a user