Top Banner
COMP 208 – Computers in Engineering COMP 208 - Lecture 08 1 COMP 208 Computers in Engineering Lecture 08 Jun Wang School of Computer Science McGill University Fall 2007
35

COMP 208 Computers in Engineering - cs.mcgill.ca

Jun 06, 2022

Download

Documents

dariahiddleston
Welcome message from author
This document is posted to help you gain knowledge. Please leave a comment to let me know what you think about it! Share it to your friends and learn new things together.
Transcript
Page 1: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

81

CO

MP

208

Com

pute

rs in E

ngin

eering

Le

ctu

re 0

8

Ju

n W

an

g

Sch

oo

l o

f C

om

pu

ter

Scie

nce

McG

ill U

niv

ers

ity

Fa

ll 2

00

7

Page 2: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

82

Re

vie

w�

Co

unte

r-co

ntr

olle

d loo

p (

definite ite

rato

r)

DOvar= initial, final, step-size

statement block, s

ENDDO

stat

emen

t_af

ter_

loop

loop b

ody

var

<=

fin

al-v

alue

yes

(tr

ue)

no (

fals

e)

var

= i

nit

ial-

val

ue

var

= v

ar+

ste

p-s

ize

chan

ge

<=

to

>=

wh

en s

tep-s

ize

is

neg

ativ

e

Page 3: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

83

Exam

ple

of counte

r-contr

olle

d loop

PROGRAM CountDown

IMPLICIT NONE

INTEGER :: counter

DO counter = 3, 1, -1

WRITE (*,*) “Counter: ”, counter

END DO

WRITE (*,*),“Liftoff!”

WRITE (*,*), “After loop, counter is: ”, counter

END PROGRAM CountDown

Counter: 3

Counter: 2

Counter: 1

Liftoff!

After loop, counter is: 0

Page 4: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

84

Exam

ple

of counte

r-contr

olle

d loop

PROGRAM CountDown

IMPLICIT NONE

INTEGER :: counter

DOcounter = 1, 3, 1

WRITE (*,*) “Counter: ”, 4 -counter

END DO

WRITE (*,*),“Liftoff!”

WRITE (*,*), “After loop, counter is: ”, counter

END PROGRAM CountDown

Counter: 3

Counter: 2

Counter: 1

Liftoff!

After loop, counter is: 4

Page 5: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

85

Exam

ple

of counte

r-contr

olle

d loop

!============================================

! calculates 1 + 2 + 3 + 4 + 5

!============================================

PROGRAM SumOf5

IMPLICIT NONE

INTEGER :: sum, i

sum = 0

DO i = 1, 5

sum = sum + i

END DO

WRITE (*,*), “The result is: ”, sum

END PROGRAM SumOf5

Page 6: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

86

Com

pound D

ata

Str

uctu

res

�W

e o

ften w

ant

to p

rocess g

roups o

f data

valu

es in a

un

iform

way

�D

igits in a

n IS

BN

�G

rades in a

cla

ss

�V

ecto

r of re

al num

bers

�U

sin

g ind

ivid

ua

l vari

able

s is c

um

bers

om

e�

INTEGER :: grade1, grade2, grade3, …, grade100

�T

here

is n

o w

ay t

o u

niform

ly e

xa

min

e o

r pro

cess t

he

valu

es s

tore

d in t

hese

variab

les

sum = sum + grade1

sum = sum + grade2

sum = sum + grade3

...

sum = sum + grade100

! We want something like the

! following. But it’s not

! valid program

DO i=1, 100

sum = sum + gradei

END DO

Page 7: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

87

Arr

ays

�F

OR

TR

AN

pro

vid

es a

n a

rra

y d

ata

type

to

su

pp

ort

gro

up

ing

re

late

d d

ata

to

ge

the

r

�T

his

allo

ws t

he

m t

o b

e p

roce

sse

d in

a u

nifo

rm

wa

y

�A

n a

rra

y is a

co

llectio

n o

f d

ata

of th

e s

am

e

typ

e.

�T

he

en

tire

co

llectio

n h

as a

sin

gle

na

me

�In

div

idu

al va

lue

s in t

he

arr

ay a

re a

ccesse

d b

y

an

IN

TE

GE

R in

de

x

Page 8: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

88

Decla

ring a

n A

rray

Syn

tax f

or

an

arr

ay d

ecla

ratio

n:

type :: name(bound)

Se

ma

ntics

type

is t

he type o

f th

e v

alu

es t

hat

can b

e s

tore

d in

each e

lem

ent

of th

e a

rray

bo

un

dspecifie

s t

he r

ange o

f in

dic

es f

or

the s

ubscri

pt

Inde

x o

f th

e a

rray e

lem

ents

is b

etw

een 1

an

d b

oun

d

In C

, ar

ray i

ndex

sta

rts

wit

h 0

Page 9: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

89

What

hap

pe

ns w

hen w

e d

ecla

re

an a

rray?

�W

hen a

n a

rray is d

ecla

red,

the c

om

pute

r allo

cate

s

sto

rage f

or

a c

ontigu

ous b

lock o

f m

em

ory

cells

�T

his

blo

ck h

as t

he n

am

e w

e s

pe

cify

�E

ach e

lem

ent

in t

he b

lock h

as t

he r

ight

siz

e f

or

hold

ing

valu

es o

f th

e t

ype that w

as s

pecifie

d

�T

he in

div

idua

l ele

men

ts in t

he b

lock c

an b

e r

efe

rence

d

by a

n ind

ex

�T

he in

de

x s

tart

s a

t 1

�T

he in

de

x r

ang

es u

p to t

he s

ize w

e s

pecify

�E

ach e

lem

ent

can b

e t

reate

d a

s a

sim

ple

variab

le o

f th

e

specifie

d t

ype.

Page 10: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

81

0

Decla

ring a

n A

rray

Exam

ple

: INTEGER :: DIGITS(10)

Vis

ualiz

ing a

n a

rray:

078729

12

43

65

390

789

3 10

DIGITS

contents

indices

name

Page 11: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

81

1

How

Do W

e A

ccess the

Ele

ments

?

To a

ccess ind

ivid

ua

l ele

ments

in the a

rray,

we u

se t

he

nam

e o

f th

e a

rray a

nd the s

ubscri

pt

(inde

x)

of th

e

ele

ment

SUM = SUM + (11-POS)*DIGITS(POS)

Synta

x:

array-name ( integer-expression )

Sem

antics:

array-name

is the n

am

e o

f th

e a

rray,

and

integer-expression

is a

n e

xpre

ssio

n t

hat

eva

luate

s to a

n inte

ge

r. T

he v

alu

e o

f th

is inte

ger

must

be b

etw

een 1

an

d t

he d

ecla

red a

rray s

ize

Page 12: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

81

2

Exam

ple

INTEGER :: grades(100)

...

DO i=1, 100

sum = sum + grades(i)

END DO

INTEGER :: arr(3)

...

arr(1) = 3

arr(2) = 2

arr(3) = 1

WRITE (*,*) arr(1)

WRITE (*,*) arr(2)

WRITE (*,*) arr(3)

3 2 1

Page 13: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

81

3

Out of

Bounds?

�W

ha

t h

ap

pe

ns if

the

in

de

x e

xp

ressio

n

eva

lua

tes t

o 0

? A

ne

ga

tive

nu

mb

er?

A v

alu

e

gre

ate

r th

an

th

e a

rra

y s

ize

?

�W

ho

kn

ow

s?

�W

ha

t m

igh

t h

ap

pe

n:

–P

rocessor

gen

era

tes a

run t

ime e

rror

and s

tops

(expensiv

e to c

heck)

–P

rocessor

mig

ht

just re

fere

nce a

mem

ory

cell

near

the a

rray (

dang

ero

us)

Page 14: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

81

4

Out of

Bounds?

�W

hat do I d

o?

–M

ost

co

mp

ilers

ha

ve

a b

ou

nd

s c

he

ckin

g

op

tio

n

–T

urn

it

on

du

rin

g t

estin

g

–T

urn

it

off w

he

n p

rog

ram

fu

lly d

eve

lop

ed

to

ma

ke

exe

cu

tio

n m

ore

eff

icie

nt

Page 15: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

81

5

Usin

g A

rrays

�A

na

tura

l m

ech

an

ism

fo

r p

roce

ssin

g a

rra

ys

is t

he

DO

-lo

op

�It

allo

ws u

s t

o g

o th

rou

gh

an

d p

roce

ss e

ach

ele

me

nt

in t

he

arr

ay

–e.g

. in

cre

ase a

ll gra

des b

y 5

%

�It

als

o a

llow

s u

s t

o p

ut

va

lue

s in

to th

e a

rra

y

to b

eg

in w

ith

Page 16: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

81

6

Initia

lize a

n A

rray to Z

ero

INTEGER :: UPPER = 100

INTEGER :: a(UPPER)

INTEGER :: i

DO i = 1, UPPER

a(i) = 0

END DO

Page 17: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

More

on A

rrays a

nd L

oops

Nath

an F

riedm

an

Fall,

2007

Page 18: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

81

8

Input

Valu

es into

an A

rray

(DO

–LO

OP

)

REAL :: A(1000)

INTEGER :: I, SIZE

READ(*,*) SIZE

DO I = 1, SIZE

READ (*,*) A(I)

END DO

Sin

ce t

he R

EA

D s

tate

ment

has o

nly

1 v

ariab

le,

A(I

), it

reads o

nly

one v

alu

e. T

here

fore

, th

e 1

000 v

alu

es m

ust be

ente

red in 1

00

0 lin

es.

Page 19: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

81

9

Input

Valu

es into

an A

rray

(DO

–LO

OP

)In

our

ISB

N e

xam

ple

, w

e c

ould

input th

e

dig

its a

s follo

ws:

DO I = 1, 10

READ (*,*) digits(i)

END DO

We w

ould

have to input 10 lin

es.

The first valu

e o

n e

ach lin

e w

ould

be r

ead

Page 20: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

82

0

Input

Valu

es into

an A

rray

(Im

plie

d D

O –

LO

OP

)

REAL :: A(1000)

INTEGER :: I, SIZE

READ(*,*) SIZE

READ (*,*) (A(I), I=1,SIZE)

Re

ad

s v

alu

es s

eq

ue

ntia

lly f

rom

a lin

e

If th

ere

are

no

t e

no

ug

h v

alu

es o

n t

he

lin

e it

wa

its

for

mo

re v

alu

es o

n a

ne

w lin

e

Th

is is c

alle

d a

n in

line

or

imp

lied

DO

lo

op

Page 21: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

82

1

Input

Valu

es into

an A

rray

(Im

plie

d D

O –

LO

OP

)

In o

ur

ISB

N e

xa

mp

le,

we

co

uld

in

pu

t th

e d

igits a

s

follo

ws:

READ (*,*) (digits(I), I=1,10)

We

co

uld

in

pu

t a

ll o

f th

e d

igits o

n o

ne o

r m

ore

lin

es s

ep

ara

ted

by b

lan

ks

Th

e f

irst 1

0 d

igits w

ou

ld b

e r

ea

d a

nd

sto

red

in

th

e

dig

its a

rra

y

Page 22: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

82

2

Input

Valu

es into

an A

rray

(Im

plic

it Im

plie

d D

O –

LO

OP

)REAL :: A(1000)

INTEGER :: I, SIZE

READ(*,*) SIZE

READ (*,*) A

Re

ad

s v

alu

es s

eq

ue

ntia

lly lik

e a

n im

plie

d d

o lo

op

It m

ust fill

the

en

tire

arr

ay,

no

t ju

st th

e f

irst S

IZE

va

lue

s

Page 23: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

82

3

Com

pute

Sum

of A

rray

Ele

ments

REAL :: Data(100)

REAL :: Sum

. . .

Sum = 0.0

DO k = 1, 100

Sum = Sum + Data(k)

END DO

Page 24: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

82

4

Inner

Pro

duct of V

ecto

rs

Th

e in

ne

r p

rod

uct o

f tw

o v

ecto

rs is t

he

su

m o

f th

e

pro

du

cts

of

co

rre

sp

on

din

g e

lem

en

ts.

REAL :: V1(50), V2(50)

REAL :: InnerProduct

INTEGER :: dim, n

READ(*,*) dim !actual dimension of vector

InnerProduct= 0.0

DO n = 1, dim

InnerProduct= InnerProduct+ V1(n)*V2(n)

END DO

Page 25: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

82

5

Fin

d M

axim

um

Valu

e

How

do w

e fin

d the larg

est valu

e in a

n a

rray?

Imagin

e a

deck o

f card

s that w

e look

thro

ugh o

ne a

t a tim

e

Keep tra

ck o

f th

e larg

est valu

e

Sta

rt w

ith the o

ne o

n the first card

Keep lookin

g a

nd n

ote

whenever

a larg

er

valu

e is found

Page 26: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

82

6

Fin

d M

axim

um

Valu

e

PROGRAM FINDMAX

IMPLICIT NONE

INTEGER :: MARKS(210)

INTEGER :: MAX, I

READ(*,*) MARKS

MAX = MARKS(1)

DO I = 2, 210

IF (MARKS(I) > MAX) MAX = MARKS(I)

END DO

WRITE (*,*) “THE HIGHEST MARK IS: “, MAX

END PROGRAM FINDMAX

Page 27: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

82

7

Indefinite Ite

rato

rs(logic

al

expre

ssio

n-c

ontr

olle

d loops)

�F

or

som

e a

pplic

ations, w

e d

o n

ot know

in

advance h

ow

many tim

es to r

epeat th

e

com

puta

tion

�T

he loop c

ontinues u

ntil som

e c

onditio

n is

met and then it te

rmin

ate

s

Page 28: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

82

8

Indefinite Ite

rato

r�

Synta

x

�T

he b

lock, s, is

evalu

ate

d r

epeate

dly

an

indete

rmin

ate

num

ber

of tim

es

�T

he loop is term

inate

d w

ith a

n EXIT

sta

tem

ent, u

sually

when c

ert

ain

conditio

n is tru

e.

DO

statement-block, s

END DO

Page 29: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

82

9

GC

D

�T

he

gre

ate

st

co

mm

on

div

iso

r o

f tw

o in

teg

ers

is

the

la

rge

st

nu

mb

er

tha

t d

ivid

es b

oth

of

the

m

�T

he

re a

re n

um

ero

us a

pp

lica

tio

ns t

ha

t re

qu

ire

co

mp

utin

g G

CD’s

�F

or

exa

mp

le,

red

ucin

g r

atio

na

l n

um

be

rs t

o t

heir

sim

ple

st

form

in

se

min

um

eri

cco

mp

uta

tio

ns

�W

e p

rese

nt

a v

ery

sim

ple

(slo

w)

alg

ori

thm

Page 30: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

83

0

A G

CD

Alg

orith

m

�T

he

GC

D is o

bvio

usly

le

ss th

an

or

eq

ua

l to

eith

er

of

the

giv

en

nu

mb

ers

, x a

nd

y

�W

e ju

st

ha

ve

to

wo

rk b

ackw

ard

s a

nd

te

st

eve

ry

nu

mb

er

less t

ha

n x

or

y u

ntil w

e f

ind

on

e t

ha

t

div

ide

s b

oth

�W

e s

top

wh

en

we

fin

d a

com

mo

n d

ivis

or

or

wh

en

we

ge

t to

1

Page 31: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

83

1

A S

imple

GC

D C

om

puta

tion

PROGRAM gcd

INTEGER :: x, y, g

READ (*,*) x, y

!! Ensure both x, y are greater than 1

IF (x < y) THEN

g = x

ELSE

g = y

END IF

DO

IF (mod(x,g)==0 .AND. mod(y,g)==0) exit

g = g -1

END DO

WRITE (*,*) "GCD of ", x, " and ", y, " = ", g

END PROGRAM gcd

Page 32: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

83

2

Fin

din

g S

quare

Roots

�N

ew

ton p

resente

d a

n a

lgorith

m for

appro

xim

ating the s

quare

root of a

num

ber

in 1

669

�T

he m

eth

od s

tart

s w

ith a

n initia

l guess a

t th

e r

oot and k

eeps r

efinin

g the g

uess

�It s

tops r

efinin

g w

hen the g

uess is c

lose

to the r

oot, that is

when it’s s

quare

is

clo

se to the g

iven n

um

ber

Page 33: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

83

3

New

ton’s

alg

orith

m for

square

root

calc

ula

te t

he

squar

e ro

ot

of

2

...

...

...

1.4

142

(1.4

167 +

1.4

118)/

2 =

1.4

142

2/1

.4167=

1.4

118

0.0

07

1.4

167

(1.5

+1.3

333)/

2=

1.4

167

2/1

.5 =

1.3

333

0.2

51.5

(1+

2)/

2=

1.5

2/1

=2

11

avera

ge

(R +

x/R

) / 2

qu

oti

en

t

(x / R

)

dif

fere

nce

(R2

–x)

esti

mate

(R)

x =

2

Page 34: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

83

4

New

ton’s

Square

Root A

lgorith

m! ---------------------------------------------------------

! Newton's method to find the square root of a positive number.

! ---------------------------------------------------------

PROGRAM SquareRoot

IMPLICIT NONE

REAL :: Tolerance = 0.001, A, R

DO

WRITE (*,*) "Enter a positive number:"

READ (*,*) A

IF (A >= 0.0) EXIT

END DO

R = A ! Initial approximation

DO

IF (ABS(R*R -

A) < Tolerance) EXIT

! If close enough, exit

R = 0.5 * (R + A/R) ! Update approximation

END DO

WRITE (*,*) "The estimated square root of ", A, " is ", R

WRITE (*,*) "The square root from SQRT() is ", SQRT(A)

WRITE (*,*) "Absolute error= ", ABS(SQRT(A) -

R)

END PROGRAM SquareRoot

Page 35: COMP 208 Computers in Engineering - cs.mcgill.ca

COMP 208 – Computers in Engineering

CO

MP

208

-L

ectu

re 0

83

5

A L

am

e J

oke

The instr

uctions o

n the s

ham

poo label said

:

1.

Rin

se

2.

La

the

r

3.

Re

pe

at

Why d

id the C

om

pute

r S

cie

ntist die

in the

Show

er?