mirror of
https://github.com/saitohirga/WSJT-X.git
synced 2025-09-03 05:38:01 -04:00
Changes necessary to build ldpcsim174_91.f90.
This commit is contained in:
parent
87f5510999
commit
358081f280
@ -421,6 +421,7 @@ set (wsjt_FSRCS
|
|||||||
lib/extractmessage144.f90
|
lib/extractmessage144.f90
|
||||||
lib/fsk4hf/extractmessage168.f90
|
lib/fsk4hf/extractmessage168.f90
|
||||||
lib/ft8/extractmessage174.f90
|
lib/ft8/extractmessage174.f90
|
||||||
|
lib/fsk4hf/extractmessage174_91.f90
|
||||||
lib/fano232.f90
|
lib/fano232.f90
|
||||||
lib/fast9.f90
|
lib/fast9.f90
|
||||||
lib/fast_decode.f90
|
lib/fast_decode.f90
|
||||||
@ -530,6 +531,7 @@ set (wsjt_FSRCS
|
|||||||
lib/fsk4hf/msksoftsym.f90
|
lib/fsk4hf/msksoftsym.f90
|
||||||
lib/fsk4hf/msksoftsymw.f90
|
lib/fsk4hf/msksoftsymw.f90
|
||||||
lib/ft8/osd174.f90
|
lib/ft8/osd174.f90
|
||||||
|
lib/fsk4hf/osd174_91.f90
|
||||||
lib/fsk4hf/osd300.f90
|
lib/fsk4hf/osd300.f90
|
||||||
lib/fsk4hf/osd204.f90
|
lib/fsk4hf/osd204.f90
|
||||||
lib/pctile.f90
|
lib/pctile.f90
|
||||||
|
@ -374,7 +374,7 @@ do iter=0,maxiterations
|
|||||||
|
|
||||||
! send messages from check nodes to variable nodes
|
! send messages from check nodes to variable nodes
|
||||||
do i=1,M
|
do i=1,M
|
||||||
tanhtoc(1:6,i)=tanh(-toc(1:6,i)/2)
|
tanhtoc(1:7,i)=tanh(-toc(1:7,i)/2)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
do j=1,N
|
do j=1,N
|
||||||
|
@ -1,5 +1,5 @@
|
|||||||
integer, parameter:: N=174, K=91, M=N-K
|
integer, parameter:: N=174, K=91, M=N-K
|
||||||
character*22 g(83)
|
character*23 g(83)
|
||||||
integer colorder(N)
|
integer colorder(N)
|
||||||
|
|
||||||
data g/ &
|
data g/ &
|
||||||
|
@ -1,5 +1,5 @@
|
|||||||
program ldpcsim174_91
|
program ldpcsim174_91
|
||||||
! End to end test of the (174,77)/crc14 encoder and decoder.
|
! End to end test of the (174,91)/crc14 encoder and decoder.
|
||||||
use crc
|
use crc
|
||||||
use packjt
|
use packjt
|
||||||
|
|
||||||
@ -7,14 +7,14 @@ character*22 msg,msgsent,msgreceived
|
|||||||
character*8 arg
|
character*8 arg
|
||||||
character*6 grid
|
character*6 grid
|
||||||
integer*1, allocatable :: codeword(:), decoded(:), message(:)
|
integer*1, allocatable :: codeword(:), decoded(:), message(:)
|
||||||
integer*1, target:: i1Msg8BitBytes(11)
|
integer*1, target:: i1Msg8BitBytes(12)
|
||||||
integer*1 msgbits(91)
|
integer*1 msgbits(91)
|
||||||
integer*1 apmask(174), cw(174)
|
integer*1 apmask(174), cw(174)
|
||||||
integer*2 checksum
|
integer*2 checksum
|
||||||
integer*4 i4Msg6BitWords(13)
|
integer*4 i4Msg6BitWords(13)
|
||||||
integer colorder(174)
|
integer colorder(174)
|
||||||
integer nerrtot(174),nerrdec(174),nmpcbad(91)
|
integer nerrtot(174),nerrdec(174),nmpcbad(91)
|
||||||
logical checksumok,fsk,bpsk
|
logical checksumok
|
||||||
real*8, allocatable :: rxdata(:)
|
real*8, allocatable :: rxdata(:)
|
||||||
real, allocatable :: llr(:)
|
real, allocatable :: llr(:)
|
||||||
|
|
||||||
@ -50,9 +50,6 @@ read(arg,*) ntrials
|
|||||||
call getarg(4,arg)
|
call getarg(4,arg)
|
||||||
read(arg,*) s
|
read(arg,*) s
|
||||||
|
|
||||||
fsk=.false.
|
|
||||||
bpsk=.true.
|
|
||||||
|
|
||||||
! don't count crc bits as data bits
|
! don't count crc bits as data bits
|
||||||
N=174
|
N=174
|
||||||
K=91
|
K=91
|
||||||
@ -89,18 +86,18 @@ allocate ( rxdata(N), llr(N) )
|
|||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
i1Msg8BitBytes(10:11)=0
|
i1Msg8BitBytes(10:12)=0
|
||||||
checksum = crc14 (c_loc (i1Msg8BitBytes), 11)
|
checksum = crc14 (c_loc (i1Msg8BitBytes), 12)
|
||||||
! For reference, the next 3 lines show how to check the CRC
|
! For reference, the next 3 lines show how to check the CRC
|
||||||
i1Msg8BitBytes(10)=checksum/256
|
i1Msg8BitBytes(11)=checksum/256
|
||||||
i1Msg8BitBytes(11)=iand (checksum,255)
|
i1Msg8BitBytes(12)=iand (checksum,255)
|
||||||
checksumok = crc14_check(c_loc (i1Msg8BitBytes), 11)
|
checksumok = crc14_check(c_loc (i1Msg8BitBytes), 12)
|
||||||
if( checksumok ) write(*,*) 'Good checksum'
|
if( checksumok ) write(*,*) 'Good checksum'
|
||||||
|
|
||||||
! K=87, For now:
|
! K=91, For now:
|
||||||
! msgbits(1:72) JT message bits
|
! msgbits(1:72) JT message bits
|
||||||
! msgbits(73:75) 3 free message bits (set to 0)
|
! msgbits(73:77) 5 free message bits (set to 0)
|
||||||
! msgbits(76:87) CRC12
|
! msgbits(78:91) CRC14
|
||||||
mbit=0
|
mbit=0
|
||||||
do i=1, 9
|
do i=1, 9
|
||||||
i1=i1Msg8BitBytes(i)
|
i1=i1Msg8BitBytes(i)
|
||||||
@ -109,20 +106,20 @@ allocate ( rxdata(N), llr(N) )
|
|||||||
msgbits(mbit)=iand(1,ishft(i1,ibit-8))
|
msgbits(mbit)=iand(1,ishft(i1,ibit-8))
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
msgbits(73:75)=0 ! the three extra message bits go here
|
msgbits(73:77)=0 ! the five extra message bits go here
|
||||||
i1=i1Msg8BitBytes(10) ! First 4 bits of crc12 are LSB of this byte
|
i1=i1Msg8BitBytes(11) ! First 6 bits of crc12 are LSB of this byte
|
||||||
do ibit=1,4
|
do ibit=1,6
|
||||||
msgbits(75+ibit)=iand(1,ishft(i1,ibit-4))
|
msgbits(77+ibit)=iand(1,ishft(i1,ibit-6))
|
||||||
enddo
|
enddo
|
||||||
i1=i1Msg8BitBytes(11) ! Now shift in last 8 bits of the CRC
|
i1=i1Msg8BitBytes(12) ! Now shift in last 8 bits of the CRC
|
||||||
do ibit=1,8
|
do ibit=1,8
|
||||||
msgbits(79+ibit)=iand(1,ishft(i1,ibit-8))
|
msgbits(83+ibit)=iand(1,ishft(i1,ibit-8))
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
write(*,*) 'message'
|
write(*,*) 'message'
|
||||||
write(*,'(11(8i1,1x))') msgbits
|
write(*,'(12(8i1,1x))') msgbits
|
||||||
|
|
||||||
call encode174(msgbits,codeword)
|
call encode174_91(msgbits,codeword)
|
||||||
call init_random_seed()
|
call init_random_seed()
|
||||||
! call sgran()
|
! call sgran()
|
||||||
|
|
||||||
@ -131,7 +128,7 @@ allocate ( rxdata(N), llr(N) )
|
|||||||
|
|
||||||
write(*,*) "Es/N0 SNR2500 ngood nundetected nbadcrc sigma"
|
write(*,*) "Es/N0 SNR2500 ngood nundetected nbadcrc sigma"
|
||||||
do idb = 20,-10,-1
|
do idb = 20,-10,-1
|
||||||
!do idb = -3,-3,-1
|
!do idb = 0,0,-1
|
||||||
db=idb/2.0-1.0
|
db=idb/2.0-1.0
|
||||||
sigma=1/sqrt( 2*(10**(db/10.0)) )
|
sigma=1/sqrt( 2*(10**(db/10.0)) )
|
||||||
ngood=0
|
ngood=0
|
||||||
@ -141,20 +138,7 @@ do idb = 20,-10,-1
|
|||||||
do itrial=1, ntrials
|
do itrial=1, ntrials
|
||||||
! Create a realization of a noisy received word
|
! Create a realization of a noisy received word
|
||||||
do i=1,N
|
do i=1,N
|
||||||
if( bpsk ) then
|
|
||||||
rxdata(i) = 2.0*codeword(i)-1.0 + sigma*gran()
|
rxdata(i) = 2.0*codeword(i)-1.0 + sigma*gran()
|
||||||
elseif( fsk ) then
|
|
||||||
if( codeword(i) .eq. 1 ) then
|
|
||||||
r1=(1.0 + sigma*gran())**2 + (sigma*gran())**2
|
|
||||||
r2=(sigma*gran())**2 + (sigma*gran())**2
|
|
||||||
elseif( codeword(i) .eq. 0 ) then
|
|
||||||
r2=(1.0 + sigma*gran())**2 + (sigma*gran())**2
|
|
||||||
r1=(sigma*gran())**2 + (sigma*gran())**2
|
|
||||||
endif
|
|
||||||
! rxdata(i)=0.35*(sqrt(r1)-sqrt(r2))
|
|
||||||
! rxdata(i)=0.35*(exp(r1)-exp(r2))
|
|
||||||
rxdata(i)=0.12*(log(r1)-log(r2))
|
|
||||||
endif
|
|
||||||
enddo
|
enddo
|
||||||
nerr=0
|
nerr=0
|
||||||
do i=1,N
|
do i=1,N
|
||||||
@ -163,15 +147,10 @@ do idb = 20,-10,-1
|
|||||||
if(nerr.ge.1) nerrtot(nerr)=nerrtot(nerr)+1
|
if(nerr.ge.1) nerrtot(nerr)=nerrtot(nerr)+1
|
||||||
nberr=nberr+nerr
|
nberr=nberr+nerr
|
||||||
|
|
||||||
! Correct signal normalization is important for this decoder.
|
|
||||||
rxav=sum(rxdata)/N
|
rxav=sum(rxdata)/N
|
||||||
rx2av=sum(rxdata*rxdata)/N
|
rx2av=sum(rxdata*rxdata)/N
|
||||||
rxsig=sqrt(rx2av-rxav*rxav)
|
rxsig=sqrt(rx2av-rxav*rxav)
|
||||||
rxdata=rxdata/rxsig
|
rxdata=rxdata/rxsig
|
||||||
! To match the metric to the channel, s should be set to the noise standard deviation.
|
|
||||||
! For now, set s to the value that optimizes decode probability near threshold.
|
|
||||||
! The s parameter can be tuned to trade a few tenth's dB of threshold for an order of
|
|
||||||
! magnitude in UER
|
|
||||||
if( s .lt. 0 ) then
|
if( s .lt. 0 ) then
|
||||||
ss=sigma
|
ss=sigma
|
||||||
else
|
else
|
||||||
@ -180,16 +159,16 @@ do idb = 20,-10,-1
|
|||||||
|
|
||||||
llr=2.0*rxdata/(ss*ss)
|
llr=2.0*rxdata/(ss*ss)
|
||||||
nap=0 ! number of AP bits
|
nap=0 ! number of AP bits
|
||||||
llr(colorder(174-87+1:174-87+nap)+1)=5*(2.0*msgbits(1:nap)-1.0)
|
llr(colorder(174-91+1:174-91+nap)+1)=5*(2.0*msgbits(1:nap)-1.0)
|
||||||
apmask=0
|
apmask=0
|
||||||
apmask(colorder(174-87+1:174-87+nap)+1)=1
|
apmask(colorder(174-91+1:174-91+nap)+1)=1
|
||||||
|
|
||||||
! max_iterations is max number of belief propagation iterations
|
! max_iterations is max number of belief propagation iterations
|
||||||
call bpdecode174(llr, apmask, max_iterations, decoded, cw, nharderrors,niterations)
|
call bpdecode174_91(llr, apmask, max_iterations, decoded, cw, nharderrors,niterations)
|
||||||
if( ndepth .ge. 0 .and. nharderrors .lt. 0 ) call osd174(llr, apmask, ndepth, decoded, cw, nharderrors, dmin)
|
if( ndepth .ge. 0 .and. nharderrors .lt. 0 ) call osd174_91(llr, apmask, ndepth, decoded, cw, nharderrors, dmin)
|
||||||
! If the decoder finds a valid codeword, nharderrors will be .ge. 0.
|
! If the decoder finds a valid codeword, nharderrors will be .ge. 0.
|
||||||
if( nharderrors .ge. 0 ) then
|
if( nharderrors .ge. 0 ) then
|
||||||
call extractmessage174(decoded,msgreceived,ncrcflag)
|
call extractmessage174_91(decoded,msgreceived,ncrcflag)
|
||||||
if( ncrcflag .ne. 1 ) then
|
if( ncrcflag .ne. 1 ) then
|
||||||
nbadcrc=nbadcrc+1
|
nbadcrc=nbadcrc+1
|
||||||
endif
|
endif
|
||||||
|
@ -21,9 +21,11 @@ save first,gen
|
|||||||
if( first ) then ! fill the generator matrix
|
if( first ) then ! fill the generator matrix
|
||||||
gen=0
|
gen=0
|
||||||
do i=1,M
|
do i=1,M
|
||||||
do j=1,22
|
do j=1,23
|
||||||
read(g(i)(j:j),"(Z1)") istr
|
read(g(i)(j:j),"(Z1)") istr
|
||||||
do jj=1, 4
|
ibmax=4
|
||||||
|
if(j.eq.23) ibmax=3
|
||||||
|
do jj=1, ibmax
|
||||||
irow=(j-1)*4+jj
|
irow=(j-1)*4+jj
|
||||||
if( btest(istr,4-jj) ) gen(irow,i)=1
|
if( btest(istr,4-jj) ) gen(irow,i)=1
|
||||||
enddo
|
enddo
|
||||||
@ -246,7 +248,7 @@ hdec(indices)=hdec
|
|||||||
decoded=cw(M+1:N)
|
decoded=cw(M+1:N)
|
||||||
cw(colorder+1)=cw ! put the codeword back into received-word order
|
cw(colorder+1)=cw ! put the codeword back into received-word order
|
||||||
return
|
return
|
||||||
end subroutine osd174
|
end subroutine osd174_91
|
||||||
|
|
||||||
subroutine mrbencode(me,codeword,g2,N,K)
|
subroutine mrbencode(me,codeword,g2,N,K)
|
||||||
integer*1 me(K),codeword(N),g2(N,K)
|
integer*1 me(K),codeword(N),g2(N,K)
|
||||||
@ -291,7 +293,7 @@ end subroutine nextpat
|
|||||||
|
|
||||||
subroutine boxit(reset,e2,ntau,npindex,i1,i2)
|
subroutine boxit(reset,e2,ntau,npindex,i1,i2)
|
||||||
integer*1 e2(1:ntau)
|
integer*1 e2(1:ntau)
|
||||||
integer indexes(4000,2),fp(0:525000),np(4000)
|
integer indexes(5000,2),fp(0:525000),np(5000)
|
||||||
logical reset
|
logical reset
|
||||||
common/boxes/indexes,fp,np
|
common/boxes/indexes,fp,np
|
||||||
|
|
||||||
@ -326,7 +328,7 @@ subroutine boxit(reset,e2,ntau,npindex,i1,i2)
|
|||||||
end subroutine boxit
|
end subroutine boxit
|
||||||
|
|
||||||
subroutine fetchit(reset,e2,ntau,i1,i2)
|
subroutine fetchit(reset,e2,ntau,i1,i2)
|
||||||
integer indexes(4000,2),fp(0:525000),np(4000)
|
integer indexes(5000,2),fp(0:525000),np(5000)
|
||||||
integer lastpat
|
integer lastpat
|
||||||
integer*1 e2(ntau)
|
integer*1 e2(ntau)
|
||||||
logical reset
|
logical reset
|
||||||
|
Loading…
x
Reference in New Issue
Block a user