使用命令行查找数据文件的行数 [英] Finding number of lines of a data file using command line

查看:244
本文介绍了使用命令行查找数据文件的行数的处理方法,对大家解决问题具有一定的参考价值,需要的朋友们下面随着小编来一起学习吧!

问题描述

有一种传统的方法来逐一读取每行,并在每次读取时检查 iostat 是否为非零值或负值。但是,我想调用 system(command)例程,
使用 wc -l <​​/ code>命令来计数然后想要分配要放置数据的数组的维数。例如,我以两种方式打印行数:

 程序Test_reading_lines 
integer :: count,ios,
字符(LEN = 100):: command
$ b print *,'以标准方式读取行数'
$ b (10,*,iostat = ios)
if(ios / = 0)
read(10,file ='DATA_FILE')
Do
read退出
count = count + 1
完成
关闭(10)


打印*,'行数=',计数



打印*,'使用shell命令读取行数'

command ='cat DATA_FILE | wc -l'
调用系统(命令)

打印*,'行数=','< ? >'


结束程序Test_reading_lines

不幸的是,后者的情况下,我可以像标准情况下那样分配一个像 count 这样的变量吗?也就是说,我想打印一个变量而不是'< ? >'在最后一个打印命令中。

解决方案

如果您想使用Unix命令 $ wc -l <​​/ code>,你可以调用许多Fortran编译器通用的Fortran子程序 execute_command_line gfortran 包括。



这是一个计算行数的工作示例, nlines style.gnuplot 的文件,然后使用 nlines 将一些行附加到 style.gnuplot 通过覆盖最后一个。


$ b

  PROGRAM numLines 

IMPLICIT NONE
integer,parameter :: n = 100
integer :: i,nLines
real,parameter :: x0 = -3.14,xEnd = 3.14
real :: dx
real,dimension(:),allocatable :: x,fun

allocate(x(0:n))!分配x数组
allocate(fun(0:n))!分配有趣的数组

dx = abs(xEnd-x0)/ n
x(0:n)= [(x0 + i * dx,i = 0,n)]!创建x数组
fun(0:n)= [(sin(x0 + i * dx),i = 0,n)]!创建有趣数组

open(unit = 1,file =plotFunction.dat)
DO i = 0,size(x)-1
write(1,* )x(i),'',fun(i)!将函数保存到一个文件中以绘制
END DO
close(unit = 1)

deallocate(x)!取消分配x数组
deallocate(fun)!取消分配有趣数组

open(unit = 7,file =style.gnuplot)
write(7,*)set title'y = sin(x)'font'times ,24''
写入(7,*)set tics font'times,20'
write(7,*)set key font'times,20'
write( 7,*)set grid
write(7,*)set key spacing 1.5
write(7,*)plot'< cat'u 1:2 wl lw 2 linecolor rgb 'orange'notitle
close(unit = 7)

CALL execute_command_line(wc -l style.gnuplot | cut -f1 -d''> nlines.file)!合并行

open(unit = 1,file ='nlines.file')
read(1,*)nlines!这里行数保存到变量
close(unit = 1)

CALL execute_command_line(rm nlines.file)!删除nlines.file

CALL execute_command_line(cat plotFunction.dat | gnuplot -p style.gnuplot)!在可执行文件中显示绘图
$ b $ open(unit = 7,file =style.gnuplot)
DO i = 1,nLines-1
read(7,*) !倒数第二行读取文件untile,
END DO!然后追加其他行
write(7,*)在-3.14,0大小char 1,char 1处设置对象矩形,&
fillcolor rgb'blue'fillstyle solid border lt 2 lw 1.5
write(7,*)set 0,0 size char 1,char 1,&
fillcolor rgb'blue'fillstyle solid border lt 2 lw 1.5
write(7,*)set 3.14,0 size char 1,char 1,&
fillcolor rgb'blue'fillstyle solid border lt 2 lw 1.5
write(7,*)plot'plotFunction.dat'u 1:2 wl lw 2 linecolor rgb'orange'notitle
close(unit = 7)

CALL execute_command_line(gnuplot -p'style.gnuplot')!用附加行重新载入style.gnulot

END PROGRAM numLines

我的代码可能不够优雅,但它似乎有效!


There is a conventional way to read each line one by one and check iostat hits nonzero or negative value at every reading. However, I would like to call system(command) routine and use wc -l command to count the number of and then want to allocate the dimension of the array where I want to put the data. For the example, I am printing the number of lines in both ways:

Program Test_reading_lines
    integer:: count,ios, whatever
    character(LEN=100):: command

    Print*,'Reading number of lines in a standard way'

    count=0
    open (10, file='DATA_FILE')
     Do
           read (10,*,iostat=ios) whatever
           if (ios/=0) exit     
         count=count+1
      End Do
    close(10)


    Print*,'Number of lines =', count



    Print*,'Reading number of lines using shell command'

    command='cat DATA_FILE | wc -l'
    call system(command)

    Print*,'Number of lines =','< ? >' 


    End Program Test_reading_lines

Unfortunately, in the latter case, can I assign a variable like count as in the standard case? That is, I want to print a variable instead of '< ? >' in the last print command.

解决方案

If you want to use the Unix command $ wc -l, you could call the Fortran subroutine execute_command_line which is common to many Fortran compilers, gfortran included.

Here is a working example which computes the number of lines, nlines, of a file called style.gnuplot and then uses nlines to append some rows to style.gnuplot by overwriting the last one.

PROGRAM numLines

    IMPLICIT NONE
    integer, parameter :: n = 100
    integer :: i, nLines
    real, parameter :: x0 = -3.14, xEnd = 3.14
    real :: dx
    real, dimension (:), allocatable :: x, fun

    allocate(x(0:n)) ! Allocate the x array
    allocate(fun(0:n)) ! Allocate the fun array

    dx = abs(xEnd-x0)/n
    x(0:n) = [(x0+i*dx, i = 0,n)] ! Create the x array
    fun(0:n) = [(sin(x0+i*dx), i = 0,n)] ! Create the fun array

    open(unit=1,file="plotFunction.dat")
        DO i=0,size(x)-1
            write(1,*) x(i), ' ', fun(i) ! Save the function to a file to plot
        END DO
    close(unit=1)

    deallocate(x) ! Deallocate the x array
    deallocate(fun) ! Deallocate the fun array

    open(unit=7, file="style.gnuplot")
        write(7,*) "set title 'y = sin(x)' font 'times, 24'"
        write(7,*) "set tics font 'times, 20'"
        write(7,*) "set key font 'times,20'"
        write(7,*) "set grid"
        write(7,*) "set key spacing 1.5"
        write(7,*) "plot '<cat' u 1:2 w l lw 2  linecolor rgb 'orange' notitle "
    close(unit=7)

    CALL execute_command_line("wc -l style.gnuplot | cut -f1 -d' ' > nlines.file") ! COunt the lines

    open(unit=1,file='nlines.file')
        read(1,*) nlines ! Here the number of lines is saved to a variable
    close(unit=1)

    CALL execute_command_line("rm nlines.file") ! Remove nlines.file

    CALL execute_command_line("cat plotFunction.dat | gnuplot -p style.gnuplot") ! Show the plot within the executable

    open(unit=7,file="style.gnuplot")
        DO i = 1,nLines-1 
            read(7,*) ! Read the file untile the penultimate row,
        END DO        ! then append the other rows
        write(7,*) "set object rectangle at -3.14,0 size char 1, char 1", & 
                                                                    " fillcolor rgb 'blue' fillstyle solid border lt 2 lw 1.5"
        write(7,*) "set object rectangle at 0,0 size char 1, char 1", & 
                                                                    " fillcolor rgb 'blue' fillstyle solid border lt 2 lw 1.5"
        write(7,*) "set object rectangle at 3.14,0 size char 1, char 1", & 
                                                                    " fillcolor rgb 'blue' fillstyle solid border lt 2 lw 1.5"
        write(7,*) "plot 'plotFunction.dat' u 1:2 w l lw 2  linecolor rgb 'orange' notitle"
    close(unit=7)

    CALL execute_command_line("gnuplot -p 'style.gnuplot'") ! Load again style.gnulot with the appended lines

END PROGRAM numLines

My code might not be elegant, but it seems to work!

这篇关于使用命令行查找数据文件的行数的文章就介绍到这了,希望我们推荐的答案对大家有所帮助,也希望大家多多支持IT屋!

查看全文
登录 关闭
扫码关注1秒登录
发送“验证码”获取 | 15天全站免登陆