Document 7860410

Download Report

Transcript Document 7860410

CS1001 Lecture 8
• Working with LOGICAL Data Type
• Examples
• Q&A Project
28 March, 2000
LOGICAL Variables
• LOGICAL type statement
LOGICAL :: list
e.g., LOGICAL :: RootExists, Error
• Assignment statement
variable = logical-expression or logical-constant (.TRUE.,
.FALSE.
e.g., Error = .TRUE.
Error = iTemp < -100 .OR. iTemp > 1000
28 March, 2000
LOGICAL Variables
• I/O
Print *, error, RootExists, .TRUE., .FALSE.
Suppose error is .TRUE. And RootExists is .FALSE., then
out put is: T F T F
LOGICAL :: A,B,C
Read *, A,B,C
Input could be .T., .FALSE., T
or T, .F,
28 March, 2000
From yesterday:
IF (cScale /= “F” .AND. cScale /= “C”) THEN
bError = .TRUE.
ELSE IF (iTemp < -100 .OR. iTemp > 1000)
THEN
bError = .TRUE.
ELSE
bError = .FALSE.
ENDIF
END IF
28 March, 2000
Operations with LOGICALs
LOGICAL:: OutRange, CorrectLetter
:
CorrectLetter = (cScale = “F”) .OR. (cScale = “C”)
OutRange = iTemp < -100 .OR. iTemp > 1000
Integer:: N
LOGICAL:: Even, Odd
Even = (N-N/2*N) .EQ. 0
Odd = (N-N/2*N) /= 0
28 March, 2000
Problem 1 (Chap 3, #14)
Program Sides_of_Triangle
! Check if 3 lengths can be the sides of a triangle, of an
! equilateral triangle, of an isosceles triangle, of a scalene
! triangle.
IMPLICIT NONE
REAL :: side1, side2,side3
LOGICAL :: Triangle, Equilateral, Isosceles, Scalene
! Read three sides and make determination
PRINT *, “Enter 3 lengths:”
READ *, side1, side2, side3
28 March, 2000
Problem 1 (Cont’d)
Triangle = (side1+side2 > side3) .AND. (side1+side3 >side2) &
(side2+side3 > side1)
Equilateral = Triangle .AND. (side1 = = side2) .AND. &
(side3 = = side2)
Isosceles = Triangle .AND. ((side1 = = side2) .OR (side2= =side3) &
. OR. (side1 = = side 3))
Scalene = Triangle .AND. .NOT. Isosceles
Print *, “Triangle is: “ , Triangle
Print *, “Equilateral is:”, Equilateral
Print *, “Isosceles is:”, Isosceles
Print *, “Scalene is: “ , Scalene
END PROGRAM Sides_of_Triangle
28 March, 2000
.NOT. Operator
• The logical operator .NOT. is used to form the
complement (or opposite) of a condition.
E.g.: Even = (N-N/2*N) .EQ. 0
Odd = .NOT. Even
E.g.: (Age .GT. 25) .AND. (Status .EQ. ‘single’)
.NOT. ( (Age .GT. 25) .AND. (Status .EQ. ‘single’))
28 March, 2000
DeMorgan’s Theorem
• Used to form Complements of a logical expression
• Theorem:
Complement of Expr1 .AND. Expr2 is Comp1 .OR. Comp2
Complement of Expr1 .OR. Expr2 is Comp1 .AND. Comp2
where Comp1 is Complement of Expr1 (.NOT. Expr1) and
Comp2 is Complement of Expr2 (.NOT. Expr2)
E.g.: .NOT. ( (Age .GT. 25) .AND. (Status .EQ. ‘single’))
may be written as using DeMorgan’s Law
.NOT. (Age .GT.25) .OR. .NOT. (Status .EQ. ‘single’)
Then simplifying to (Age .LE. 25) .OR. (Status .NE. ‘single’)
E.g.: .NOT. ((A > 5) .OR. (C < (A+B))) may be written as
using DeMorgan’s Law .NOT. (A>5) .AND. .NOT. C<(A+B)
simplifying to (A<=5) .AND. (C >=(A+B))
28 March, 2000
Program Pointers 1
• With Multialternative selection: IF-ELSE IF can
be more efficient than a sequence of IFs.
IF (Score >= 90) Grade = “A”
IF ((Score >= 80) .AND. (Score < 90) Grade = “B”
IF ((Score >= 70) .AND. (Score < 80) Grade = “C”
IF ((Score >= 60) .AND. (Score < 70) Grade = “D”
IF ((Score < 60) Grade = “F”
IF (Score >= 90) THEN Grade = “A”
ELSE IF (Score >= 80) Grade = “B”
ELSE IF (Score >= 70) Grade = “C”
ELSE IF (Score >= 60) Grade = “D”
ELSE Grade = “F”
28 March, 2000
Program Pointer 2
• Because most real values are not stored exactly,
real qualities that are algebraically equal may yield
a false logical construct when compare with = =.
E.g.: algebraically x*(1.0/x) = 1.0
but, x*(1.0/x) == 1.0 is usually .FALSE.
See example Figure 3.3 Pages 135-136.
Use IF(ABS(real_values1 - real_values2) < Tolerance)
THEN ….
Tolerance is some small positive real value e.g., 1E-10
28 March, 2000
Example Program
• Page 183 #6
• Gas Company charges gas used bas on the following
table
Gas Used
Rate
First 70 Cubic meters
$5 minimum
Next 100 Cubic meters
$0.05 per cubic meter
Next 230 cubic meters
$0.025 per cubic meter
Above 400 cubic meter
$0.015 per cubic meter
28 March, 2000
If gas used is 60 cubic meters, then the charge is $5.00.
If gas used is greater than 70 cubic meters;
for example, 130 cubic meters, then the
charge = (130-70)*(rate2) + Minimum rate
= 60* $0.05 + $5.00 =$8.00.
If the gas used is 250 cubic meters, then the
charge = (250-170)* (rate3)+ (170-70)*(rate2) + minimum cost
If the gas used is 500 cubic meters, then the
charge = (500-400)*(rate4) + (400-170)*(rate3) +
(170-70)*(rate2)+minimum cost
28 March, 2000
Program Design
Ask the user for two 4-digit numbers, i.e.,
meter reading for the previous month and the current meter reading.
Calculate the gas used. Handle the special case
Calculate charges (how to do this?)
Check and do for the higher usage first.
Print out charges
28 March, 2000