I am trying to use the code below to read a formatted file and write it into another. However, on running it shows the following error
Fortran runtime error: Bad real number in item 1 of list input
$ ./conv.sac.farm < i_conv.farm
# stn comp Delta Tr-time Start in record
At line 54 of file Main/conv.sac.farm.f (unit = 5, file = 'stdin')
Fortran runtime error: Bad real number in item 1 of list input
The source code is as follows
PARAMETER (nd0=100000,pi=3.1415926)
IMPLICIT COMPLEX*8 (Z)
CHARACTER name*6,comp*6,fname*60,event*20
- ,cmp(0:3)*5,fname0*60,charac*15,scode*60
REAL*8 GFACT(500),PP0(500),depth0
integer hr0,mnu0,yr,month,day,hr,mnu
REAL x(nd0),y(nd0)
DIMENSION Z(nd0),zpole(50),zero(50)
data np,cmp/8,'disp.','vel. ','acc. ','orig.'/
common /tbl/ip(110,14),is(110,14),secp(110,14),secs(110,14)
read(5,'(a)') event
read(5,*) alats,alons,depth,hr0,mnu0,sec0,id,delmin,delmax
depth0=depth
write(22,'(a,a5,3f7.2,2i3,f6.2)')
# event,cmp(id),alats,alons,depth,hr0,mnu0,sec0
* << J-B travel time table >>
OPEN(11,FILE='jb.ptime')
OPEN(12,FILE='jb.stime')
1000 read(11,*,end=1001) n,(ip(n,i),secp(n,i),i=1,14)
goto 1000
1001 read(12,*,end=1002) n,(is(n,i),secs(n,i),i=1,14)
goto 1001
1002 continue
close(11)
close(12)
* << Geometrical factor >>
OPEN(15,FILE='jb.table')
CALL GEOM(GFACT,PP0,depth0)
close(15)
nstn=0
print *,' # stn comp Delta Tr-time Start in record'
5 read(5,'(a)') fname
read(5,'(a)') scode
* ta=advance of start-time relative the standard P/S arrival
* du=duration
c
if(fname.eq.'dummy') goto 90
read(5,*) ta,du,dt,f1,f2,iph,nr,iuni
open(1,file=fname)
READ(1,'(g15.7)') dt0
read(1,'(/////5g15.7)') dum, alat, alon, elev
read(1,'(///////5i10)') yr, nday, hr,mnu, nsec
read(1,'(5i10)') nmsec,ndum,ndum,ndum,nd
read(1,'(/////)')
read(1,'(a6,2x,a13)') name,charac
read(1,'(////)')
And so on..
Line 54 is
read(5,*) ta,du,dt,f1,f2,iph,nr,iuni
and my i_conv.farm file is
1604151625 Japan
32.79 130.58 10 16 25 06 1 30 100
II.BORG.00.BH1.A
II.BORG.00
II.BORG.00.BH2.A
II.BORG.00
II.BORG.00.BHZ.A
II.BORG.00
20 120 1
0.002 1 1 1 1
II.DGAR.00.BH1.A
II.DGAR.00
II.DGAR.00.BH2.A
II.DGAR.00
II.DGAR.00.BHZ.A
II.DGAR.00
20 120 1
0.002 1 1 1 1
II.TAU.00.BH1.A
II.TAU.00
II.TAU.00.BH2.A
II.TAU.00
II.TAU.00.BHZ.A
II.TAU.00
20 120 1
0.002 1 1 1 1
II.UOSS.00.BH1.A
II.UOSS.00
II.UOSS.00.BH2.A
II.UOSS.00
II.UOSS.00.BHZ.A
II.UOSS.00
20 120 1
0.002 1 1 1 1
II.WRAB.00.BH1.A
II.WRAB.00
II.WRAB.00.BH2.A
II.WRAB.00
II.WRAB.00.BHZ.A
II.WRAB.00
20 120 1
0.002 1 1 1 1
IU.AFI.00.BH1.A
IU.AFI.00
IU.AFI.00.BH2.A
IU.AFI.00
IU.AFI.00.BHZ.A
IU.AFI.00
20 120 1
0.002 1 1 1 1
I really don’t know where the formatted data is not right?
I put «Real» MATC before I even opened my project and restart two twice, but still the same error message:
ELMER SOLVER (v 7.0) STARTED AT: 2014/08/11 10:31:01
MAIN:
MAIN: =============================================================
MAIN: ElmerSolver finite element software, Welcome!
MAIN: This program is free software licensed under (L)GPL
MAIN: Copyright 1st April 1995 — , CSC — IT Center for Science Ltd.
MAIN: Webpage http://www.csc.fi/elmer, Email elmeradm@csc.fi
MAIN: Library version: 7.0 (Rev: exported)
MAIN: =============================================================
MAIN:
MAIN:
MAIN: ————————————-
MAIN: Reading Model: case.sif
Loading user function library: [HeatSolve]…[HeatSolver_Init0]
LoadMesh: Scaling coordinates: 1.000E-03 1.000E-03 1.000E-03
MAIN: ————————————-
Loading user function library: [HeatSolve]…[HeatSolver_Init]
Loading user function library: [HeatSolve]…[HeatSolver]
OptimizeBandwidth: ———————————————————
OptimizeBandwidth: Computing matrix structure for: heat equation…done.
OptimizeBandwidth: Half bandwidth without optimization: 8575
OptimizeBandwidth:
OptimizeBandwidth: Bandwidth Optimization …done.
OptimizeBandwidth: Half bandwidth after optimization: 1478
OptimizeBandwidth: ———————————————————
MAIN:
MAIN: ————————————-
MAIN: Time: 1/14 86400.000000000000
MAIN: ————————————-
MAIN:
HeatSolve:
HeatSolve:
HeatSolve: ————————————-
HeatSolve: TEMPERATURE ITERATION 1
HeatSolve: ————————————-
HeatSolve:
HeatSolve: Starting Assembly…
HeatSolve: Assembly:
: …..Assembly done
DefUtils::DefaultDirichletBCs: Setting Dirichlet boundary conditions
DefUtils::DefaultDirichletBCs: Dirichlet boundary conditions set
CRS_IncompleteLU: ILU(0) (Real), Starting Factorization:
CRS_IncompleteLU: ILU(0) (Real), NOF nonzeros: 120074
CRS_IncompleteLU: ILU(0) (Real), filling (%) : 100
CRS_IncompleteLU: ILU(0) (Real), Factorization ready at (s): 0.02
1 0.3895E-02
2 0.1909E-03
3 0.2327E-04
4 0.1216E-04
5 0.5040E-05
6 0.5204E-04
7 0.1487E-05
8 0.1616E-05
9 0.2218E-06
10 0.1219E-06
11 0.2561E-06
12 0.3507E-07
13 0.7409E-07
14 0.7608E-08
15 0.8945E-08
16 0.1223E-08
17 0.1234E-08
18 0.1603E-09
19 0.2121E-09
20 0.3031E-10
20 0.3031E-10
ComputeChange: NS (ITER=1) (NRM,RELC): ( 24.900009 2.0000000 ) :: heat equation
HeatSolve: iter: 1 Assembly: (s) 5.53 5.53
HeatSolve: iter: 1 Solve: (s) 0.16 0.16
HeatSolve: Result Norm : 24.900008502275778
HeatSolve: Relative Change : 2.0000000000000000
HeatSolve:
HeatSolve:
HeatSolve: ————————————-
HeatSolve: TEMPERATURE ITERATION 2
HeatSolve: ————————————-
HeatSolve:
HeatSolve: Starting Assembly…
HeatSolve: Assembly:
At line 2841 of file Lists.f90
Fortran runtime error: Bad real number in item 1 of list input
You should upgrade or use an alternative browser.
-
Forums
-
Other Sciences
-
Programming and Computer Science
Runtime Error in Fortran 95
- Fortran
-
Thread starter
ngendler -
Start date
Jun 17, 2013
- Jun 17, 2013
- #1
function f(x)
implicit none
real :: x,f,p
print *,’Type a probability density function’
read *, p
!It doesn’t like line 34…
f = p
end function f
It compiles fine, but then when I run the program and enter a function (say, x**2), it gives me the error:
Fortran runtime error: Bad real number in item 1 of list input
Help, please!
Answers and Replies
- Jun 17, 2013
- #2
is the wrong approach for achieving
B)
I’m trying to write a function that will integrate a user given function
To achieve B you need to parse the user provided string and either
1) compile that parsed expression during run-time and execute the code in your integration function
2) or sample it by other means over a given Riemann-partition
Unfortunately, writing parsers is generally one of the most challenging programming tasks; and Fortran is not exactly well suited for parser development; it’s a language for numerical programming and that’s it.
Fortunately in your case, almost every parsing solution (e.g. lex/yacc resp. flex/bison) has a calculator as standard example, so you can take such a sample and refine that according to your needs.
- Jun 17, 2013
- #3
- Jun 17, 2013
-
- #4
- Jun 17, 2013
- #5
1. The function f will be expected to return a numerical value. If you want f to return a CHARACTER string, then f must be declared accordingly.
2. Ditto for reading in the variable ‘p’. How is the program supposed to know that ‘p’ should be reading a CHARACTER string rather than a floating point or integer value? This is why you get a run-time error when you type in the string ‘x**2’.
3. FORTRAN is very poor at deciphering user intent and then self-writing code to fill in the blanks. Most programming languages are.
4. The response by Solkar is very apt. In order for a user-input function to be integrated, the character string must first be parsed so that the program can decipher the input string. The logic for doing this can be implemented with FORTRAN code, but that will require much more programming than you have shown so far. Instead of using a FUNCTION to do this, a SUBROUTINE would be more appropriate.
- Jun 18, 2013
- #6
I want the user to be able to say «x**2» and have the program read it and integrate it.
And how to achieve that was what I explained.
- Jun 18, 2013
- #7
A)
is the wrong approach for achieving
B)To achieve B you need to parse the user provided string and either
1) compile that parsed expression during run-time and execute the code in your integration function
2) or sample it by other means over a given Riemann-partitionUnfortunately, writing parsers is generally one of the most challenging programming tasks; and Fortran is not exactly well suited for parser development; it’s a language for numerical programming and that’s it.
Fortunately in your case, almost every parsing solution (e.g. lex/yacc resp. flex/bison) has a calculator as standard example, so you can take such a sample and refine that according to your needs.
I don’t think you will need an elaborate parser for the OP’s purpose; he is not trying to have a general purpose parser which would be needed for implementing a programming language. The OP, I think, could use a restricted set of functions, like polynomials, basic trig functions, hyperbolics, etc., to which the user would be constrained.
FORTRAN possesses basic string manipulation intrinsic functions, so it is possible to search for substrings, manipulate characters, etc. The idea that FORTRAN is restricted to numerical programming solely is an old wives’ tale, and has been since at least FORTRAN77.
I think the OP assumed that because the mathematical term ‘x^2’ is written as ‘x**2’ in FORTRAN code, his program would read that string and interpret it to mean x*x, not realizing that some extra steps were required to accomplish his desired goal.
- Jun 18, 2013
- #8
have a general purpose parser which would be needed for implementing a programming language.
We do neither discuss «general purpose parsers» nor «implementing a programming language»
The complexity of the parsing task at hand is above the complexity of implementing a calculator, which a the standard example for parser generators and lexers; that’s what we discuss.
So lex/yacc (flex/bison) or a similar toolset it is; Fortran having some string processing feats does not imply it’d be suited for any up-from-scratch parser development.
- Jun 18, 2013
- #9
In a FORTRAN program like the OP envisioned, the user could type in ‘SIN(X)’ in response to the question ‘Which Function do you wish to integrate?’
The program could then scan the input string to determine if the substring ‘SIN» was present. The various functions which are in the permitted list of functions, e.g. ‘SIN’, ‘COS’, ‘TAN’, etc., could be programmed already in several separate FUNCTION statements. Based on its analysis of the input string, the program then branches to calculating using the proper function.
Tools like lex/yacc work in a similar fashion. Based on the description of the programming language, they analyze the source file to strip out white space, and figure out what are keywords, data, variable names, commands, etc. so that the code generator can do its thing.
IMO, the OP is trying to write a simple calculation tool, something which doesn’t quite have the capability of a computer-aided algebra system.
All I am trying to say to the OP is that his program can be written if the list of functions is kept restricted in some fashion, otherwise, it becomes more the development of a parser than the development of a calculation routine. (What folks in other times and other places called ‘Mission Creep’.)
- Jun 18, 2013
- #10
We do neither discuss «general purpose parsers» nor «implementing a programming language»
Actually we have no idea what we are discussing, as OP didn’t tell what exact kind of input is the program expected to work with. So everyone answers not the OP question, but their own guess of what the original question is.
- Jun 18, 2013
-
- #11
print *,'Type a probability density function'
the program must at least be capable to deal with
[tex]frac{1}{sqrt{2pisigma^2}}expleft(-frac{left(x-muright)^2}{2sigma^2}right)[/tex]
given in at least one (whichever) ascii or unicode repr; and even just that consists of e.g.
unary «-«, binary «-«, «/», «*», «(«, «)», «exp «, «sqrt», «²», «π»
and actual floats provided for σ and μ
And all that must be handled by the parser.
- Jun 18, 2013
- #12
Actually we have no idea what we are discussing
The snippet the OP provided together with his explanations was sufficient for determining the problem domain, and it is obvious that we’re neither discussing a «general purpose parser» nor a parser for a «programming language».
- Jun 18, 2013
-
- #13
For dealing with prob. densities the program requests hereprint *,'Type a probability density function'
the program must at least be capable to deal with
[tex]frac{1}{sqrt{2pisigma^2}}expleft(-frac{left(x-muright)^2}{2sigma^2}right)[/tex]given in at least one (whichever) ascii or unicode repr; and even just that consists of e.g.
unary «-«, binary «-«, «/», «*», «(«, «)», «exp «, «sqrt», «²», «π»
and actual floats provided for σ and μAnd all that must be handled by the parser.
Why must all that be handled by the parser? That the program must at least be capable of handling an expression of that level of complexity is your requirement. It might well be that what is wanted is a simple parser that can handle polynomials and nothing else. We don’t know.
The OP has yet to come back and say what his/her requirements are, and why they are this way. We don’t know if this is an undergrad assignment, something that needs to be done for work or a grad school project, or a self-imposed problem. We don’t know is the operative phrase.
- Jun 18, 2013
- #14
Why must all that be handled by the parser?
Because that’s the normal distribution,
but even
It might well be that what is wanted is a simple parser that can handle polynomials
just handling polynomials would imply having to deal with
unary «-«, binary «+», «*», «x^i»
operator associativity and precedence rules.
Suggested for: Runtime Error in Fortran 95
- Last Post
- Jan 18, 2020
- Last Post
- Jul 5, 2021
- Last Post
- Apr 1, 2019
- Last Post
- Jan 10, 2023
- Last Post
- Today, 12:16 AM
- Last Post
- Aug 7, 2018
- Last Post
- Aug 27, 2020
- Last Post
- Jan 31, 2019
- Last Post
- Jun 16, 2021
- Last Post
- Jun 27, 2022
-
Forums
-
Other Sciences
-
Programming and Computer Science
-
Hachi-ait
- Posts: 5
- Joined: 2020/06/14 18:18:10
Fortran runtime error: Bad integer for item 1 in list input
Dear CentOS users,
I run a program (named wrfcamx) writen by fortran language,
The example job file wrote like this
- Capture1.PNG (14.14 KiB) Viewed 1682 times
Then I change to my day
set DAY (160101 160102 160103)
set DAYM1 (151231 160101 160102
foreach i (1 2 3)
and the rest keep the same
But I faced to this message: set: Variable name must begin with a letter.
I think with centOS, it should be in another syntax. But I can’t find what is correct. I try with set DAY = (160101 160102 160103)
it appear this error: «Fortran runtime error: Bad integer for item 1 in list input»
Please guide me how to solve it.
Sorry if I ask a very basic question, I have very few knowledge in programing.
thanks!
Ha Chi
-
MartinR
- Posts: 714
- Joined: 2015/05/11 07:53:27
- Location: UK
Re: Fortran runtime error: Bad integer for item 1 in list input
Post
by MartinR » 2020/06/15 09:13:04
You’ve missed out the «=» sign when setting DAY and DAYM1:
Code: Select all
bash-4.2$ cat Y
#!/bin/csh -vx
set DAY = (050601 050602 050603 050604 050605)
foreach i (1 2 3 4 5)
if ( $DAY[$i] == "050601" ) then
set START = $DAY[$i]"12"
else
set START = $DAY[$i]"00"
endif
echo $START
this snippet then runs fine:
Code: Select all
bash-4.2$ ./Y
set DAY = ( 050601 050602 050603 050604 050605 )
set DAY = ( 050601 050602 050603 050604 050605 )
echo $DAY
echo 050601 050602 050603 050604 050605
050601 050602 050603 050604 050605
foreach i ( 1 2 3 4 5 )
foreach i ( 1 2 3 4 5 )
if ( $DAY[$i] == "050601" ) then
if ( 050601 == 050601 ) then
set START = $DAY[$i]"12"
set START = 05060112
else
else
echo $START
echo 05060112
05060112
Notes:
- Please use cut-and-paste into code blocks (see the </> icon). It means that anyone trying to help you can reproduce the error instead of having to type it in.
- Note the use of «-vx» on the first line. The «-v» tells the interpreter to echo the line as it is read, so you know where you’ve got to. The «-x» causes the interpreter to echo the line after all substitutions have been done. The last line appears as: -v => «echo $START», -x => «echo 05060112» and the command output is «05060112».
- As it stands, the loop is not closed and so only one pass occurs.
- In examples, please remove all extraneous lines
- There is not one scrap of FORTRAN here, so it is not a «Fortran runtime error».
-
Hachi-ait
- Posts: 5
- Joined: 2020/06/14 18:18:10
Re: Fortran runtime error: Bad integer for item 1 in list input
Post
by Hachi-ait » 2020/06/16 08:31:52
Thank you very much
Your notes are very clear and valuable.
I found out that the fortran runtime error is caused by the software not by the set command. I am contacting the software developer directly for this error.
Thanks
As an exercise, I put together a postfix calculator using modern Fortran. Language apart, I am interested in knowing your take on the algorithm. As far as I remember from my freshman year (chemistry — long ago), the problem has a standard solution in C, which I imagine is optimal in some sense. However, I did not look it up, and wrote something that is probably different in some respects. The program runs and passes the tests.
I am interested in knowing whether the present solution is acceptable, or if it has any major hidden flaws / inefficiencies. For folks not familiar with the simple syntax of modern Fortran, I suggest the following quick modern Fortran tutorial.
Thanks!
module mod_postfix
implicit none
private
integer, parameter :: TOKEN_MAX_LEN = 50
public :: EvalPostfix
contains
real(kind(1d0)) function EvalPostfix( CmdStrn ) result(res)
character(len=*), intent(in) :: CmdStrn
integer :: iToken, nTokens, shift
character(len=:) , allocatable :: Token
character(len=TOKEN_MAX_LEN), allocatable :: stack(:)
nTokens = GetNTokens(CmdStrn)
allocate(stack(nTokens))
do iToken = 1, nTokens
call GetToken(CmdStrn,iToken,Token)
stack(iToken) = Token
enddo
shift=0
call simplify_stack(nTokens,Stack,shift)
read(Stack(nTokens),*)res
end function EvalPostfix
recursive subroutine simplify_stack(n,Stack,shift)
integer , intent(in) :: n
character(len=TOKEN_MAX_LEN), intent(inout) :: Stack(:)
integer , intent(inout) :: shift
character(len=:), allocatable :: sOp
integer :: i
real(kind(1d0)) :: v1, v2, res
logical :: IsBinary, IsUnary, IsNonary, IsOperator
if(n==0)return
sOp = trim(Stack(n))
!.. Case Binary Operators
IsBinary = index( "+ - * / max min mod **", sOp ) > 0
IsUnary = index( " sin cos tan asin acos atan exp log int sqrt abs", sOp ) > 0
IsNonary = index( " random_number PI", sOp ) > 0
IsOperator = IsBinary .or. IsUnary .or. IsNonary
if( ( .not. IsOperator ) .and. n == shift + 1 )return
call simplify_stack(n-1,stack,shift)
if( IsBinary )then
read(Stack(n-1),*)v2
read(Stack(n-2),*)v1
if( sOp == "+" ) res = v1+v2
if( sOp == "-" ) res = v1-v2
if( sOp == "*" ) res = v1*v2
if( sOp == "/" ) res = v1/v2
if( sOp == "max" ) res = max(v1,v2)
if( sOp == "min" ) res = min(v1,v2)
if( sOp == "mod" ) res = mod(v1,v2)
if( sOp == "**" ) res = v1**v2
write(Stack(n),"(e24.16)")res
shift=shift+2
do i=n-3,1,-1
Stack(i+2)=Stack(i)
enddo
elseif( IsUnary )then
read(Stack(n-1),*)v1
if( sOp == "sin" ) res = sin (v1)
if( sOp == "cos" ) res = cos (v1)
if( sOp == "tan" ) res = tan (v1)
if( sOp == "asin") res = asin(v1)
if( sOp == "acos") res = acos(v1)
if( sOp == "atan") res = atan(v1)
if( sOp == "exp" ) res = exp (v1)
if( sOp == "log" ) res = log (v1)
if( sOp == "sqrt") res = sqrt(v1)
if( sOp == "abs" ) res = abs (v1)
if( sOp == "int" ) res = dble(int(v1))
write(Stack(n),"(e24.16)")res
shift=shift+1
do i=n-2,1,-1
Stack(i+1)=Stack(i)
enddo
elseif( IsNonary )then
if( sOp == "random_number")call random_number(res)
if( sOp == "PI" )res=4.d0*atan(1.d0)
write(Stack(n),"(e24.16)")res
if(n == shift + 1)return
call simplify_stack(n-1,stack,shift)
end if
end subroutine simplify_stack
!> Counts the number of tokens
integer function GetNTokens( strn, separator_list_ ) result( n )
implicit none
character(len=*) , intent(in) :: strn
character(len=*), optional, intent(in) :: separator_list_
!
character , parameter :: SEPARATOR_LIST_DEFAULT = " "
character(len=:), allocatable :: separator_list
integer :: i,j
n=0
if(len_trim( strn ) == 0)return
if(present(separator_list_))then
allocate(separator_list,source=separator_list_)
else
allocate(separator_list,source=SEPARATOR_LIST_DEFAULT)
endif
i=1
do
j=verify(strn(i:),separator_list)
if(j<=0)exit
n=n+1
j=i-1+j
i=scan(strn(j:),separator_list)
if(i<=0)exit
i=j-1+i
if(i>len(strn))exit
enddo
if(allocated(separator_list))deallocate(separator_list)
end function GetNTokens
subroutine GetToken( strn, iToken, token, separator_list_ )
implicit none
character(len=*), intent(in) :: strn
integer , intent(in) :: iToken
character(len=:), allocatable, intent(out):: token
character(len=*), optional , intent(in) :: separator_list_
!
character , parameter :: SEPARATOR_LIST_DEFAULT = " "
character(len=:), allocatable :: separator_list
integer :: i,j,n
if(present(separator_list_))then
allocate(separator_list,source=separator_list_)
else
allocate(separator_list,source=SEPARATOR_LIST_DEFAULT)
endif
if(iToken<1)return
if(iToken>GetNTokens(strn,separator_list))return
if(allocated(token))deallocate(token)
i=1
n=0
do
j=verify(strn(i:),separator_list)
if(j<=0)exit
n=n+1
j=i-1+j
i=scan(strn(j:),separator_list)
if(i<=0)then
i=len_trim(strn)+1
else
i=j-1+i
endif
if(n==iToken)then
allocate(token,source=strn(j:i-1))
exit
endif
enddo
end subroutine GetToken
end module Mod_Postfix
program TestPostfixCalculator
use mod_postfix
implicit none
real(kind(1d0)) , parameter :: THRESHOLD = 1.d-10
real(kind(1d0)) :: res
character(len=:), allocatable :: sPostfix
call assert("+" , abs( EvalPostfix(" 3 4 +") - 7 ) < THRESHOLD )
call assert("-" , abs( EvalPostfix(" 3 4 -") + 1 ) < THRESHOLD )
call assert("*" , abs( EvalPostfix(" 3 4 *") - 12 ) < THRESHOLD )
call assert("/" , abs( EvalPostfix(" 3 4 /") - 0.75 ) < THRESHOLD )
call assert("max", abs( EvalPostfix(" 3 4 max") - 4 ) < THRESHOLD )
call assert("min", abs( EvalPostfix(" 3 4 min") - 3 ) < THRESHOLD )
call assert("mod", abs( EvalPostfix("13 5 mod") - 3 ) < THRESHOLD )
call assert("**" , abs( EvalPostfix(" 2 5 **" ) - 32 ) < THRESHOLD )
call assert("cos", abs( EvalPostfix(" PI 3 / cos" ) - 0.5 ) < THRESHOLD )
res = sqrt( (log(10.d0)-atan(2.d0))/max(cos(6.d0),exp(3.d0)) )
sPostfix ="10 log 2 atan - 6 cos 3 exp max / sqrt"
call assert("expression1", abs( EvalPostfix(sPostfix) - res ) < THRESHOLD )
!.. etc. etc.
contains
subroutine assert(msg,cond)
use, intrinsic :: iso_fortran_env, only : OUTPUT_UNIT
character(len=*), intent(in) :: msg
logical , intent(in) :: cond
write(OUTPUT_UNIT,"(a)",advance="no") "["//msg//"] "
if( cond )then
write(OUTPUT_UNIT,"(a)") "passed"
else
write(OUTPUT_UNIT,"(a)") "FAILED"
endif
end subroutine assert
end program TestPostfixCalculator