Files
Fortran-95-2003-Program-3rd…/第2章习题.f90
2025-09-25 16:33:13 +08:00

302 lines
10 KiB
Fortran

! 2021:04:14 20:02:17 标准程序格式
! program name
! !
! ! 目的:
! !
! !
! ! 修订记录:
! ! 日期 编程者 改动描述
! ! =================== ============= ======================
! !
! !
! ! 程序结构:
! !
! implicit none
! ! 数据字典
! ! 声明常量
! REAL, PARAMETER :: PI=3.14159265 ! PI值
! REAL, PARAMETER :: e=2.718281828459 ! 自然对数
! INTEGER, PARAMETER :: arrayLength=20 ! 数组基准长度
! ! 声明变量
! ! 变量初始化
! ! 数据输入
! ! 运算过程
! ! 结果输出
! end program name
! 2021:04:14 17:31:01 一个用于读取文件中所有数值的程序案例
! program name
! ! =============================================================
! ! 目的:
! ! 遍历一个文件内的所有变量(需要全部是实数或整数)
! ! 修订记录:
! ! 日期 编程者 改动描述
! ! =================== ============= ======================
! ! 2021-04-14 17:46:57 Sola 编写源代码并校正格式
! ! =============================================================
! implicit none
! ! 数据字典
! ! 结构需要
! integer :: i ! 控制读取字符所在位置
! integer :: errorLevel ! 检查错误信息
! integer :: valueStart ! 读取数值开始位置
! integer :: valueEnd ! 读取数值结束位置
! real :: value ! 读取的数值内容
! character(len=128) :: allValue ! 所在行字符内容
! character(len=128) :: selectValue ! 读取所在行第i个字符内容
! character(len=128) :: readValue ! 读取的字符内容
! ! 使用者自定义
! ! 声明常量
! REAL, PARAMETER :: PI=3.14159265 ! PI值
! REAL, PARAMETER :: e=2.718281828459 ! 自然对数
! ! 声明变量
! ! 变量初始化
! valueStart=1
! ! 打开文件
! open (unit=1, file='content', status='old', action='read', iostat=errorLevel)
! if (errorLevel > 0) stop "读取文件出错"
! ! 遍历数值
! do
! read(1, '(A128)', iostat=errorLevel) allValue ! 读取行内容
! if (errorLevel < 0) exit ! 如果到达最后一行, 退出循环
! if (errorLevel > 0) stop "读取行出错" ! 读取行内容出错, 退出程序
! ! 遍历行内字符
! do i=1, len_trim(allValue), 1
! selectValue=allValue(i:i) ! 读取第i个字符
! if ( .not. ( trim(selectValue) == ',' .or. i == len_trim(allValue)) ) then
! cycle ! 如果不是逗号或到达末尾, 则跳过此次循环
! else ! 如果是逗号或到达末尾
! if ( i == len_trim(allValue) ) then
! valueEnd=i ! 如果是到达末尾, 则数值结束位置为i
! else
! valueEnd=i-1 ! 如果并未达到末尾, 则数值结束位置为i-1
! end if
! readValue=allValue(valueStart:valueEnd) ! 读取当前数值
! read(readValue, '(F5.1)', iostat=errorLevel) value ! 将当前数值赋值给一个实数
! if (errorLevel > 0) stop "存在非合法数值,请检查" ! 赋值存在错误, 退出程序
! valueStart=i+1 ! 下一次数值的开始位置为i+1
! end if
! end do
! valueStart=1 ! 开始新一行, 并将数值开始位置重置
! end do
! close (unit=1) ! 关闭文件
! end program name
! program example
! implicit none
! end program example
! 2021:04:08 19:23:29 2-9
! PROGRAM triangle
! IMPLICIT NONE
! REAL :: a, b, c, theta
! REAL, PARAMETER :: PI=3.14159265
! WRITE (*,*) 'Enter the length of the hypotenuse C:'
! READ (*,*) c
! WRITE (*,*) 'Enter the angle THETA in degrees:'
! READ (*,*) theta
! a = c * COS(theta)
! b = c * SIN(theta)
! WRITE (*,*) 'The length of the adjacent side is ', a
! WRITE (*,*) 'The length of the opppsite side is ', b
! END PROGRAM triangle
! 2021:04:08 19:44:56 2-10
! program example
! implicit none
! real :: a, b, c
! integer :: k, l, m
! read (*,*) a, b, c, k
! read (*,*) l, m
! write (*,*) a, b, c, k, l, m
! end program example
! 2021:04:09 19:44:46 2-11
! program example
! implicit none
! real :: hourWages, workTime, allWages
! write (*,*) 'How many wages per hour?'
! read (*,*) hourWages
! write (*,*) 'How much time work a week?'
! read (*,*) workTime
! allWages = hourWages * workTime
! write (*,*) 'You can get the wages of $', allWages, ' a week'
! end program example
! 2021:04:09 20:31:02 2-12
! program example
! implicit none
! real :: m, h, v, PE, KE, E
! real, PARAMETER :: g=10.0
! write (*,*) 'Please enter the m h v for coculate the energy of the item above the ground.'
! read (*,*) m, h, v
! PE=m*g*h
! KE=1./2.*m*v**2
! E=PE + KE
! write (*,*) 'The energy of the item is:', E, 'J'
! end program example
! 2021:04:09 20:37:44 2-13
! program example
! implicit none
! real, parameter :: g=10.0
! real :: v, h
! write (*,*) 'Please enter the highte of the item.'
! read (*,*) h
! v=sqrt(2.*g*h)
! write (*,*) 'The speed is', v, 'm/s'
! end program example
! 2021:04:09 20:42:37 2-14
! program example
! implicit none
! real, parameter :: c=2.9979E8
! real :: E, m, t, P
! write (*,*) 'Please enter the days of reactor run a year.'
! read (*,*) t
! write (*,*) 'Please enter the power(mW) of the reactor.'
! read (*,*) P
! E=P*t*24.*60*60
! m=E*1E6/c**2
! write (*,*) m, 'kg of consumed material per year.'
! end program example
! 2021:04:09 21:03:57 2-17
! program example
! implicit none
! real, parameter :: g=10.0, PI=3.14159265
! real :: L, T
! write (*,*) 'Please input pendulum length(m).'
! read (*,*) L
! T = 2*PI*sqrt(L/g)
! write(unit=*, fmt=*) 'The oscillation period of the pendulum is', T, 's'
! end program example
! 2021:04:09 21:12:01 2-18
! program example
! implicit none
! real :: a, b, c
! write(unit=*, fmt=*) 'Please enter the length(cm) of the two right angle sides.'
! read (*,*) a, b
! c = sqrt(a**2+b**2)
! write(unit=*, fmt=*) 'The length of the hypotenuse of the right triangle is', c, 'cm.'
! end program example
! 2021:04:09 21:18:48 2-19
! program example
! implicit none
! real :: b, x, calculationResult, calculationCheck
! write(unit=*, fmt=*) 'Please enter logarithm x and base b respectively'
! read (*,*) x, b
! calculationResult = log10(x)/log10(b)
! calculationCheck = log(x)/log(b)
! write(unit=*, fmt=*) 'The calculation result is', calculationResult, 'and the check result is', calculationCheck
! end program example
! 2021:04:09 21:27:29 2-20
! program example
! implicit none
! a = 1
! end program example
! 2021:04:09 21:29:00 2-21
! program example
! implicit none
! real :: d, x1, x2, y1, y2
! write(unit=*, fmt=*) 'Please enter the coordinates of the first point.'
! read (*,*) x1, y1
! write(unit=*, fmt=*) 'Please enter the coordinates of the second point.'
! read (*,*) x2, y2
! d = sqrt((x1-x2)**2+(y1-y2)**2)
! write(unit=*, fmt=*) 'The distance between the two points is', d
! end program example
! 2021:04:09 21:33:10 2-22
! program example
! implicit none
! real :: dB, P2
! real, parameter :: P1=1
! write(unit=*, fmt=*) '请输入接受输入能源的级别'
! read (*,*) P2
! dB = 10*log10(P2/P1)
! write(unit=*, fmt=*) '该输入的分贝值为:', dB, 'dB'
! end program example
! 2021:04:09 21:37:13 2-23
! program example
! implicit none
! real :: x, calculationResult, calculationCheck
! real, parameter :: e=2.718281828459
! write(unit=*, fmt=*) '请输入需要计算的双曲余弦值的x值'
! read (*,*) x
! calculationResult = (e**x+e**(-x))/2.
! calculationCheck = COSH(x)
! write(unit=*, fmt=*) '计算结果为:', calculationResult, '核对结果为:', calculationCheck
! end program example
! 2021:04:09 21:42:29 2-24
! program example
! implicit none
! real :: P, F, APR
! integer :: m, n
! write(unit=*, fmt=*) '请输入每年计算复利的次数以及储存年数'
! read (*,*) m, n
! P = 1000.00
! APR = 5
! F = P*(1.+APR/(100.*m))**(m*n)
! write(unit=*, fmt=*) '该账户', n, '年后存款将达到$', F
! end program example
! 2021:04:09 22:07:57 2-25
! program example
! implicit none
! real :: f0, L, C
! real, parameter :: PI=3.14159265
! write(unit=*, fmt=*) '请输入电感值(mH)与电容值(nF)'
! read (*,*) L, C
! f0 = 1/(2*PI*sqrt(L*C))
! write(unit=*, fmt=*) '该无线电的频率为:', f0, 'hz'
! end program example
! 2021:04:09 22:12:51 2-26
! program example
! implicit none
! real :: a, v, r
! real, parameter :: g=9.81, machToMeter=340
! v=0.8*machToMeter
! a=2.5*g
! r = v**2/a
! write(unit=*, fmt=*) '(a) 飞机的飞行半径为', r, 'm'
! v = 1.5*machToMeter
! r = v**2/a
! write(unit=*, fmt=*) '(b) 飞机的飞行半径为', r, 'm'
! a = 7*g
! r = v**2/a
! write(unit=*, fmt=*) '(c) 飞机的飞行最小半径为', r, 'm'
! end program example
! 2021:04:09 22:21:16 2-27
! program example
! implicit none
! real, parameter :: G=6.673E-11
! real :: vescEarth, vescMoon, vescGu, vescJuipter, M, R
! M = 6.0E24
! R = 6.4E6
! vescEarth = sqrt(2*G*M/R)
! M = 7.4E22
! R = 1.7E6
! vescMoon = sqrt(2*G*M/R)
! M = 8.7E20
! R = 4.7E5
! vescGu = sqrt(2*G*M/R)
! M = 1.9E27
! R = 7.1E7
! vescJuipter = sqrt(2*G*M/R)
! write(unit=*, fmt=*) '地球上物体的逃逸速度为', vescEarth, 'm/s'
! write(unit=*, fmt=*) '月球上物体的逃逸速度为', vescMoon, 'm/s'
! write(unit=*, fmt=*) '谷神星上物体的逃逸速度为', vescGu, 'm/s'
! write(unit=*, fmt=*) '木星上物体的逃逸速度为', vescJuipter, 'm/s'
! end program example