Lecture 4

advertisement
Review of lecture 3

Data type and declaration

INTEGER


REAL





E.g., a, b, c
E.g., x, y, z, w
LOGICAL
COMPLEX
CHARACTER
Examples:
 INTEGER::a=1,b=-5,c=5
 REAL::x=2.0
Review of lecture 3 (cont.)

Arithmetic expressions



E.g., 5 + 2 *3
E.g., b**2 – 4*a*c
It has a value by itself

E.g. expression: 5 + 2*3 has a value of 11
Review of lecture 3 (cont.)

Evaluating Complex Expressions


Precedence
Associativity (For expressions having operators with the
same precedence).
operators
Precedence
associativity
()
1
Left to right
**
2
Right to left
*, /
3
Left to right
+, -
4
Left to right
Review of lecture 3 (cont.)
Mixed Mode Expressions

If one operand of an arithmetic operator is INTEGER and the other is
REAL
 the INTEGER value is converted to REAL
 the operation is performed
 the result is REAL
1 + 2.5  3.5
1/2.0  0.5
2.0/8  0.25
-3**2.0  -9.0
4.0**(1/2)  1.0 (since 1/2  0)
3/5 * 5.0  0.0 (since 3/5 0)
Review of lecture 3 (cont.)
Statements

Assignment statement:
Variable = expression
e.g., b = -5
(never the other way around, 5=b is not valid!)

General statement:
INTEGER a, b, c
write (*,*) ‘Hello world!’
Selection in FORTRAN
Lecture 4
By Nathan Friedman and Yi Lin
Jan 16, 2007
Roots of a Quadratic (again)
! -------------------------------------------------! Solve Ax^2 + Bx + C = 0 given B*B-4*A*C >= 0
! -------------------------------------------------PROGRAM QuadraticEquation
IMPLICIT NONE
REAL :: a, b, c, d, root1, root2
! read in the coefficients a, b and c
WRITE(*,*) "A, B, C Please : "
READ(*,*) a, b, c
! compute the square root of discriminant d
d = SQRT(b*b - 4.0*a*c)
! solve the equation
root1 = (-b + d)/(2.0*a) ! first root
root2 = (-b - d)/(2.0*a) ! second root
! display the results
WRITE(*,*) "Roots are ", root1, " and ", root2
END PROGRAM QuadraticEquation
Run Time Error
We assumed that the discriminant was positive
What if it wasn’t?
We would get an error when we run the program and
attempt to compute the square root and the program
would abort
What should we do?
Avoid trying to perform an illegal operation by branching
around it -- use a selection control structure
Quadratics example
d=b*b – 4.0*a*c
.TRUE.
D>=0.0
.FALSE.
Ouput “no
real roots!”
Calc root1,
root2
end
IF-THEN-ELSE-END IF
Used to select between two alternative sequences of
statements.
They keywords delineate the statement blocks.
Syntax:
IF (logical-expression) THEN
first statement block, s_1
ELSE
second statement block, s_2
END IF
IF-THEN-ELSE-END IF
Semantics:
•
•
•
•
Evaluate the logical expression. It can have
value .TRUE. or value .FALSE.
If the value is .TRUE., evaluate s_1, the first block of
statements
If the value is .FALSE., evlaluate s_2, the second block
of statements
After finishing either s_1 or s_2, execute the statement
following the END IF
Roots of Quadratic – v.2
! ---------------------------------------------------------------!
Solve Ax^2 + Bx + C = 0 given B*B-4*A*C >= 0
! ---------------------------------------------------------------PROGRAM QuadraticEquation
IMPLICIT NONE
REAL :: a, b, c, d, root, root2
! read in the coefficients a, b and c
WRITE(*,*) "A, B, C Please : "
READ(*,*)
a, b, c
!compute the square root of discriminant d
d = b*b - 4.0*a*c
IF (d >= 0.0) THEN
! is it solvable?
d
= SQRT(d)
root1 = (-b + d)/(2.0*a)
! first root
root2 = (-b - d)/(2.0*a)
! second root
WRITE(*,*) "Roots are ", root1, " and ", root2
ELSE
! complex roots
WRITE(*,*) "There is no real roots!"
WRITE(*,*) "Discriminant = ", d
END IF
END PROGRAM
QuadraticEquation
Logical Expressions

Relational operators return result of .TRUE. or .FALSE
<, <=, >, >=,

==, /=
Relational operators are of lower precedence than all
arithmetic operators
2 + 7 >= 3 * 3  .TRUE.

There is no associativity
a < b < c  illegal

Note that == means “is equal to” but = means “assign
the value on the right”
Data Type Logical



Where do .TRUE. and .FALSE. come from?
FORTRAN has a LOGICAL data type, just like
it has INTEGER and REAL types
We can declare variables to be of this type and
assign values to them
LOGICAL :: positive_x, condition
condition = .TRUE.
positive_x = x > 0
Is Number Even or Odd?
IF (MOD(number, 2) == 0) THEN
WRITE(*,*) number, " is even"
ELSE
WRITE(*,*) number, " is odd"
END IF
MOD(a, b): Intrinsic function, returning the remainder of a/b
Find Absolute Value
REAL :: x, absolute_x
x = .....
IF (x >= 0.0) THEN
absolute_x = x
ELSE
absolute_x = -x
END IF
WRITE(*,*) “The absolute value of “,&
x, “ is “, absolute_x
Note the use of & to indicate “continue on next line”
Which value is smaller?
INTEGER :: a, b, min
READ(*,*) a, b
IF (a <= b) THEN
min = a
ELSE
min = b
END IF
Write(*,*) “The smaller of “, a, &
“ and “, b, “ is “, min
IF-THEN-END IF
The IF-THEN-ELSE-END IF form allows us to
choose between two alternatives
There is another simpler selection mechanism that
allows us to choose whether or not to perform a
single block of actions
We either perform the actions and go on, or skip
them and go on
IF-THEN-END IF
Syntax:
IF (logical expression) THEN
block of statements
END IF
Semantics:
1.
2.
3.
Evaluate the logical expression
If it evaluates to .TRUE. execute the block of statements and
then continue with the statement following the END IF
If the result is .FALSE. skip the block and continue with the
statement following the END IF
Examples of IF-THEN-END IF
absolute_x = x
IF (x < 0.0) THEN
absolute_x = -x
END IF
WRITE(*,*) "The absolute value of ", x, " is ", absolute_x
------------------------------------------------INTEGER :: a, b, min
READ(*,*) a, b
min = a
IF (a > b) THEN
min = b
END IF
Write(*,*) "The smaller of ", a, " and ", b, " is ", min
Logical IF
An even simpler form is sometimes useful
Syntax:
IF (logical expression) singlestatement
Semantics: equivalent to
IF (logical expression) THEN
single-statement
END IF
Examples of Logical IF
absolute_x = x
IF (x < 0.0) absolute_x = -x
WRITE(*,*) "The absolute value of ", x, &
" is" ,"absolute_x
------------------------------------------------INTEGER :: a, b, min
READ(*,*) a, b
min = a
IF (a > b) min = b
Write(*,*) "The smaller of ", a, " and ", b, &
" is ", min
IF-THEN-ELSE IF-END IF
IF-THEN-ELSE-ENDIF can only handle processes
which have two options.
Sometimes we have more than 2 options for one
process.
For example, in the quadratic equation problem, there
may be two equivalent roots. We want to detect this
and complex roots at the same time.
Solution: put another IF-THEN-ELSE-ENDIF in the
ELSE block
IF-THEN-ELSE IF-END IF

Syntax
IF (logical-expression1) THEN
first statement block, s_1
ELSE
IF (logical-expression2) THEN
second statement block, s_2
ELSE
third statement block, s_3
END IF
END IF
IF-THEN-ELSE IF-END IF
Semantics:
•
•
•
•
Evaluate the logical expression 1. It can have value .TRUE. or
value .FALSE.
If the value is .TRUE., evaluate s_1, the first block of statements
If the value is .FALSE.,
 evaluate the logical expression 2. It can have value .TRUE. Or
value .FALSE.
 If the value is .TRUE., evaluate s_2, the second block of
statements
 If the value is .FALSE., evaluate s_3, the third block of
statements
 After finishing either s_2 or s_3, execute the statement following
ENDIF
After finishing either s_1 or s_2 or s_3, execute the statement
following the END IF
Roots of Quadratic v.3
! --------------------------------------------------!
Solve Ax^2 + Bx + C = 0 given B*B-4*A*C >= 0
!
Detect complex roots and repeated roots.
! --------------------------------------------------PROGRAM QuadraticEquation
IMPLICIT NONE
!
!
REAL :: a, b, c, d, root1, root2
read in the coefficients a, b and c
READ(*,*) a, b, c
comute the discriminant d
d = b*b - 4.0*a*c
IF (d > 0.0) THEN
! distinct roots?
d
= SQRT(d)
root1 = (-b + d)/(2.0*a)
! first root
root2 = (-b - d)/(2.0*a)
! second root
WRITE(*,*) 'Roots are ', root1, ' and ', root2
ELSE
IF (d == 0.0) THEN
! repeated roots?
WRITE(*,*) 'The repeated root is ', -b/(2.0*a)
ELSE
! complex roots
WRITE(*,*) 'There is no real roots!‘
WRITE(*,*) 'Discriminant = ', d
END IF
END IF
END PROGRAM
QuadraticEquation
IF-THEN-ELSE IF-END IF


You can put IF-THEN-ELSE IF-ENDIF within ELSE block
repeatedly.
IF (logical-expression1) THEN
first statement block, s_1
ELSE
IF (logical-expression2) THEN
second statement block, s_2
ELSE
IF-THEN-ELSE IF-ENDIF
END IF
END IF
There is a concise way to do this.
IF-ELSEIF-ELSE-ENDIF

syntax
IF (logical expression 1) THEN
block 1
ELSEIF (logical expression 2) THEN
block 2
...
ELSEIF (logical expression N-1) THEN
block N-1
[ELSE
block N]
ENDIF
IF-ELSEIF-ELSE-ENDIF

Semantics
 First evaluate the logical expression 1. It can have value .TRUE. or
value .FALSE.
 If the value is .TRUE., evaluate the first block of statements.
 If the value is .FALSE., evaluate the logical expression 2. It can have
value .TRUE. or value .FALSE.
 If the value is .TRUE., evaluate the second block of statements.
 Repeat this until all logical expressions have been evaluated.
 If none of them are .TRUE., evaluate block N within ELSE and ENDIF.
After that, execute the statement following the ENDIF
Roots of Quadratic v.4
--------------------------------------------------!
Solve Ax^2 + Bx + C = 0 given B*B-4*A*C >= 0
!
Detect complex roots and repeated roots.
! --------------------------------------------------PROGRAM QuadraticEquation
IMPLICIT NONE
!
!
REAL :: a, b, c, d, root1,root2
read in the coefficients a, b and c
READ(*,*) a, b, c
compute the discriminant d
d = b*b - 4.0*a*c
IF (d > 0.0) THEN
! distinct roots?
d
= SQRT(d)
root1 = (-b + d)/(2.0*a)
! first root
root2 = (-b - d)/(2.0*a)
! second root
WRITE(*,*) 'Roots are ', root1, ' and ', root2
ELSEIF (d == 0.0) THEN
! repeated roots?
WRITE(*,*) 'The repeated root is ', -b/(2.0*a)
ELSE
! complex roots
WRITE(*,*) 'There is no real roots!‘
WRITE(*,*) 'Discriminant = ', d
END IF
END PROGRAM
QuadraticEquation
Example in previous midterms
PROGRAM X
IMPLICIT NONE
LOGICAL :: A,B,C
INTEGER :: I,J,K
I = 5/2+2.5
J= 13.0/3.0 + 0.66
K=5
A = (I==J)
B = (K > J)
C = (K==I)
WRITE (*,*) A, B, C
END PROGRAM
12345-
TTT
TFT
TFF
FTF
None of the above
Complex Logical Expressions
In addition to relational operators, more complex logical
expressions can be formed using logical operators
The Logical Operators listed in order of decreasing
precedence are:
.NOT.
.AND.
.OR.
.EQV., .NEQV.
High
Low
The precedence of all logical operators is lower than all
relational operators
They all associate from left to right except .NOT.
Logical operator: .AND. (&&)

Examples




<exp1> && <exp2>
<exp1> .AND. <exp2>
(2>1) .and. (3<4) .TRUE.
exp2 .TRUE.
(2>1) .and. (3>4) .FALSE.
.FALSE.
exp1
(2<1) .and. (3<4) .FALSE.
.TRUE.
.TRUE.
.FALSE.
.FALSE.
.TRUE.
(2<1) .and. (3>4) .FALSE.
.FALSE.
.FALSE.
.FALSE.
.FALSE.
.FALSE.
Logical operator: .OR. (||)

Examples




(2>1) .OR. (3<4) .TRUE.
(2>1) .OR. (3>4) .TRUE.
(2<1) .OR. (3<4) .TRUE.
(2<1) .OR. (3>4) .FALSE.
<exp1> || <exp2>
<exp1> .OR. <exp2>
exp2 .TRUE.
exp1
.FALSE.
.TRUE.
.TRUE.
.TRUE.
.FALSE.
.TRUE.
.FALSE.
Logical operator: .EQV.

Examples




<exp1> .EQV. <exp2>
(2>1) .EQV. (3<4) .TRUE.
exp2 .TRUE.
(2>1) .EQV. (3>4) .FALSE.
exp1
(2<1) .EQV. (3<4) .FALSE.
.TRUE.
.TRUE.
(2<1) .EQV. (3>4) .TRUE.
.FALSE.
.FALSE.
.FALSE.
.FALSE.
.TRUE.
Logical operator: .NEQV.

Examples




(2>1) .NEQV. (3<4) .FALSE.
(2>1) . NEQV. (3>4) . TRUE.
(2<1) . NEQV. (3<4) .TRUE.
(2<1) . NEQV. (3>4) .FALSE.
<exp1> .NEQV. <exp2>
exp2 .TRUE.
exp1
.FALSE.
.TRUE.
.FALSE.
.TRUE.
.FALSE.
.TRUE.
.FALSE.
Logical operator: .NOT.

Examples


.NOT. (2<1) .TRUE.
.NOT. (2>1) .FALSE.
.NOT. <exp>
exp
.TRUE.
.FALSE.
.FALSE.
.TRUE.
Examples
Suppose we have the declaration:
INTEGER :: age=34, old=92, young=16
What is the value of the following expressions?
age /= old
age >= young
age == 62
age==56 .and. old/=92
age==56 .or. old/=92
age==56 .or. .not.(old/=92)
.not. (age==56 .or. old/=92)
Another Example
Suppose the integer variable, n has value 4.
n**2 + 1 > 10 .AND. .NOT. n < 3
 4**2 + 1 > 10 .AND. .NOT. 4 < 3
 [4**2] + 1 > 10 .AND. .NOT. 4 < 3
 16 + 1 > 10 .AND. .NOT. 4 < 3
 [16 + 1] > 10 .AND. .NOT. 4 < 3
 17 > 10 .AND. .NOT. 4 < 3
 [17 > 10] .AND. .NOT. 4 < 3
 .TRUE. .AND. .NOT. 4 < 3
 .TRUE. .AND. .NOT. [4 < 3]
 .TRUE. .AND. .NOT. .FALSE.
 .TRUE. .AND. [.NOT. .FALSE.]
 .TRUE. .AND. .TRUE.
 .TRUE.
Example in the final of
Fall 2006
What is the output of the following
Fortran program?
PROGRAM exam
IMPLICIT NONE
LOGICAL :: X,Y
INTEGER :: I=2, J=3
REAL :: A=5.0,B=9.0
X = (A/I) < (B/J)
Y = (J/I) == (B/A)
X = X .AND. Y
Y = X .OR. Y
WRITE (*,*) X, Y
END PROGRAM exam
a). T F
b). T T
c). F T
d). F F
e). The program does not
compile
Download