对于一个文件(英文文章),找出其中出现频率最高的英文单词。
对于编译器可以选择visual studio系列在加上inter visual Fortran。当然如果简单的学习我们建议simply Fortran。
PROGRAM TASK
!----------------------------------------------------------------------------------------------------
!对于一个文件(英文文章),找出其中出现频率最高的英文单词。
!项目记录:
! 日期 编写者 代码备注
! ===== ========= ===========
! 10.13 朝夕 通过调试
!
!----------------------------------------------------------------------------------------------------
IMPLICIT NONE !关掉隐式声明
CHARACTER(LEN=20)::filename
INTEGER::i,j,m,l,p!控制循环的变量
INTEGER,DIMENSION(:),ALLOCATABLE::flag!flag是记录buff中单词对应出现的次数的动态分配数组
CHARACTER(len=20),DIMENSION(:),ALLOCATABLE::buff!将文本单词读入的数组,动态分配
INTEGER::word_number!读入文本单词数的变量
INTEGER,DIMENSION(10)::result_number!排序算法后输出的出现次数最多单词对应在buff中的位置,若值为0表示未记录
WRITE(*,*)'所处理文本路径:'
READ(*,*)filename
WRITE(*,*)'所读文本单词的个数:'
READ(*,*)word_number
ALLOCATE(flag(word_number))!动态分配数组
ALLOCATE(BUFF(word_number))
i=1 !变量初始化
result_number=(/0,0,0,0,0,0,0,0,0,0/) !变量初始化
DO p=1,word_number
flag(p)=0
END DO
OPEN(unit=1,file=filename,status="old",action="read",iostat=i)!打开文件
IF(i==0)THEN
WRITE(*,*)"OPEN SUCCEED!"
READ(1,*)(BUFF(j),j=1,word_number)
WRITE(*,*)'文本本来数据:'
WRITE(*,*)(BUFF(j),J=1,word_number)
DO j=1,word_number
CALL operate_string(buff(j))
END DO
WRITE(*,*)'文本处理标点后的数据:'
WRITE(*,*)(BUFF(j),j=1,word_number)
DO j=1,word_number
IF(buff(j)/=' ')THEN
flag(j)=1
DO m=j+1,word_number
IF(buff(m)==buff(j))THEN
buff(m)=' '
flag(j)=flag(j)+1
END IF
END DO
END IF
END DO!统计每个单词出现的次数
WRITE(*,*)'统计的结果:'
WRITE(*,*)(flag(j),j=1,word_number)!统计的情况
CALL find_maxv(word_number,flag,result_number)
DO l=1,10
IF (result_number(l)/=0)THEN
WRITE(*,"('出现频率最高的单词是:',A20,'出现的次数是:',I5)")buff(result_number(l)),flag(result_number(l))
END IF
END DO
ELSE
WRITE(*,*)"OPEN FEILD!"
CLOSE(unit=1)
END IF
CLOSE(unit=1)
DEALLOCATE(BUFF)
END PROGRAM
SUBROUTINE operate_string(string)!去除标点符号的子程序
IMPLICIT NONE
CHARACTER(len=20),INTENT(inout)::string
CHARACTER(len=1)::m
CHARACTER(len=len(trim(string)))temp
INTEGER::k
temp=trim(string)
DO k=1,len(temp)
m=temp(k:k)
IF(.NOT.((IACHAR(m)>=65.AND.IACHAR(m)<=90).OR.(IACHAR(m)>=97.AND.IACHAR(m)<=122)))THEN
temp(k:k)=' '
END IF
END DO
string=temp
END SUBROUTINE
SUBROUTINE find_maxv(word_number,int_arr,result_i)!找出出现次数最多的单词
IMPLICIT NONE
INTEGER,INTENT(in)::word_number
INTEGER,DIMENSION(word_number),INTENT(in)::int_arr
INTEGER,DIMENSION(10),INTENT(inout)::result_i
INTEGER::i,temp,j
j=1
result_i=(/0,0,0,0,0,0,0,0,0,0/)
temp=int_arr(1)
DO i=1,word_number
IF(temp
F:\data.txt (当然文件的路径取决于你放在哪里,注意对Fortran而言,有的编译器路径中不允许中文字符)
78
OPEN SUCCEED!
文本本来数据:
Should TV advertisements
for children be
controlled? Nowadays more
and more advertisements
for children spring
up on TVs
which make lots
of parents pay
attention to. There
are also some
specialist criticizing those
advertisements for leading
unhealthy value of
consuming. And they
think it deeply
hurts children’s healthy
development. At the
same it glows
a spirit of
comparison which destroy
children’s pure value.
So I agree
on controlling some
commercial advertisement to
make sure them
a healthy atmosphere.
文本处理标点后的数据:
Should TV advertisements
for children be
controlled Nowadays more
and more advertisements
for children spring
up on TVs
which make lots
of parents pay
attention to There
are also some
specialist criticizing those
advertisements for leading
unhealthy value of
consuming And they
think it deeply
hurts children s healthy
development At the
same it glows
a spirit of
comparison which destroy
children s pure value
So I agree
on controlling some
commercial advertisement to
make sure them
a healthy atmosphere
统计的结果:
1 1 3 3 2 1
1 1 2 1 0 0
0 0 1 1 2 1
2 2 1 3 1 1
1 2 1 1 1 2
1 1 1 0 0 1
1 2 0 1 1 1
1 2 1 1 2 2
1 1 1 1 0 1
2 1 0 1 0 1
0 1 0 1 1 1
0 1 0 1 1 0
0 1 1 0 0 1
出现频率最高的单词是:advertisements 出现的次数是: 3
出现频率最高的单词是:for 出现的次数是: 3
出现频率最高的单词是:of 出现的次数是: 3