computer programming samples- mingqindai

6
1 Program 1 It is a program to simulate the outcome as one randomly and evenly distribute 52 poker cards to 4 players. Output the cards (both the symbols and the numbers/characters) that each player has. (1) I generate a series of random and distinct numbers between 1 and 52, divide the range into four groups corresponding to spade, heart, diamond, and club, respectively. (2) I sort the cards in each player’s hands. I use a subroutine to do so. (3) Then, I print out these symbols. (4) The output of the program looks like the following. PROGRAM 1 IMPLICIT NONE INTEGER::a,b,m,n,ix,i,j,k REAL::temp INTEGER,DIMENSION(52)::c CHARACTER(LEN=3),DIMENSION(4,4,13)::player INTEGER,DIMENSION(4,4)::n_play=0 INTEGER,DIMENSION(4,13)::pla INTEGER,DIMENSION(4,4,13)::play=0 n=1 call RANDOM_SEED() CALL RANDOM_NUMBER(temp) a=temp*100 c(1)=MOD(a,53) DO CALL RANDOM_NUMBER(temp) a=temp*100 a=MOD(a,53) IF(a==0)THEN CYCLE END IF ix=0 1 / 6

Upload: mingqin-dai

Post on 25-Jul-2016

223 views

Category:

Documents


0 download

DESCRIPTION

Two Computer Programming Samples

TRANSCRIPT

Page 1: Computer Programming Samples- MingqinDai

1 Program 1It is a program to simulate the outcome as one randomly and evenly distribute 52 poker cards to 4 players. Output the cards (both the symbols and the numbers/characters) that each player has.

(1) I generate a series of random and distinct numbers between 1 and 52, divide the range into four groups corresponding to spade, heart, diamond, and club, respectively.

(2) I sort the cards in each player’s hands. I use a subroutine to do so.

(3) Then, I print out these symbols.

(4) The output of the program looks like the following.

PROGRAM 1IMPLICIT NONEINTEGER::a,b,m,n,ix,i,j,kREAL::tempINTEGER,DIMENSION(52)::cCHARACTER(LEN=3),DIMENSION(4,4,13)::playerINTEGER,DIMENSION(4,4)::n_play=0INTEGER,DIMENSION(4,13)::plaINTEGER,DIMENSION(4,4,13)::play=0n=1call RANDOM_SEED()CALL RANDOM_NUMBER(temp)a=temp*100c(1)=MOD(a,53)DO

CALL RANDOM_NUMBER(temp)a=temp*100a=MOD(a,53)IF(a==0)THEN

CYCLEEND IFix=0DO j=1,n

IF(a==c(j))THENix=1EXIT

END IFEND DOIF(ix==0)THEN

1 / 5

Page 2: Computer Programming Samples- MingqinDai

n=n+1c(n)=a

END IFIF(n==52)EXIT

END DOCALL subplay(c,pla)CALL shorting (pla)

DO i=1,4DO K=1,13

m=pla(i,k)SELECT CASE(m)CASE(1:13)

play(i,1,k)=mn_play(i,1)=k

CASE(14:26)play(i,2,(k-n_play(i,1)))=m-13n_play(i,2)=k-n_play(i,1)

CASE(27:39)play(i,3,(k-n_play(i,2)-n_play(i,1)))=m-26n_play(i,3)=k-n_play(i,2)-n_play(i,1)

CASE(40:53)play(i,4,(k-n_play(i,3)-n_play(i,2)-n_play(i,1)))=m-39n_play(i,4)=k-n_play(i,3)-n_play(i,2)-n_play(i,1)

END SELECTEND DO

END DO

CALL player_after_shorting (play,player)DO i=1,4

WRITE(*,*)"Player",iDO j=1,4

WRITE(*,*)" ",char(7-j)," ",player(i,j,1:n_play(i,j))END DO

END DO

END

SUBROUTINE player_after_shorting (play,player)INTEGER,DIMENSION(4,4,13),INTENT(IN)::playCHARACTER(LEN=3),DIMENSION(4,4,13),INTENT(OUT)::playerCHARACTER(LEN=3)::tempINTEGER::i,j,k,nDO i=1,4

DO j=1,4DO K=1,13

SELECT CASE(play(i,j,k))CASE(1)

temp="A"CASE(2)

temp="2"

2 / 5

Page 3: Computer Programming Samples- MingqinDai

CASE(3)temp="3"

CASE(4)temp="4"

CASE(5)temp="5"

CASE(6)temp="6"

CASE(7)temp="7"

CASE(8)temp="8"

CASE(9)temp="9"

CASE(10)temp="10"

CASE(11)temp="J"

CASE(12)temp="Q"

CASE(13)temp="K"

END SELECTplayer(i,j,k)=temp

END DOEND DO

END DOEND SUBROUTINESUBROUTINE subplay(c,p)INTEGER,DIMENSION(52),INTENT(IN)::cINTEGER,DIMENSION(4,13),INTENT(OUT)::pINTEGER::j,k,nDO j=1,4

n=0DO k=j,52,4

n=n+1p(j,n)=c(k)

END DOEND DOEND SUBROUTINE

SUBROUTINE shorting(a)INTEGER,DIMENSION(4,13),INTENT(INOUT)::aINTEGER,DIMENSION(13)::bINTEGER::n,i,j,k,tempDO i=1,4

DO j=1,12n=jDO k=(j+1),13

IF(a(i,n)>a(i,k))THEN

3 / 5

Page 4: Computer Programming Samples- MingqinDai

n=kEND IF

END DOIF(j/=n)THEN

temp=a(i,j)a(i,j)=a(i,n)a(i,n)=temp

END IFEND DOEND DOEND SUBROUTINE

4 / 5

Page 5: Computer Programming Samples- MingqinDai

2 Program 2I write a program to use the bisection method to find an approximate root of the equation,

The tolerance of error is 10-5, and the final interval is less than 2 x 10-5.

The program is prepared as:

(1) Input the upper and lower limits of the initial interval, [A, B]. A is greater than 1. process is repeated until A>1 and f(A)f(B)<0.

(2) Declare the tolerance as a constant at the beginning of the program.

(3) Output the value of the upper and lower limit of the interval [A, B] at the end of each iteration.

(4) Output the approximate root C, the value of the function at x=C, and the number of iteration to reach this approximate answer.

PROGRAM Bisection_methodIMPLICIT NONEREAL::a,b,c,x,fun_x,fun_a,fun_b,i=1REAL,PARAMETER::error=0.1**(5)WRITE(*,*)"please input the upper ad lower limits A and B,where A >1"

READ(*,*)a,b fun_b=sqrt(b-1)-cos(b) fun_a=sqrt(a-1)-cos(a) if (fun_b*fun_a>0) then WRITE(*,*)"please input another A and B" else

DO x=(a+b)/2 fun_x=sqrt(x-1)-cos(x) fun_a=sqrt(a-1)-cos(a) IF(fun_x*fun_a<0)THEN b=x ELSE a=x END IF IF(ABS(a-b)<error)EXIT i=i+1 WRITE(*,*)i," [A,B] = ","[",a,b,"]"END DOend if

WRITE(*,*)"the approximate root x=",a," f(c)=",fun_a," error=",ABS(a-b)END PROGRAM

5 / 5