Εισαγωγή στην Fortran 77

46
ΦΥΣ-151: HΛΕΚΤΡΟΝΙΚΟΙ ΥΠΟΛΟΓΙΣΤΕΣ Ι ΕΣΑΓΩΓΗ ΣΤΗ FORTRAN 77 Νίκος Βουλγαράκης Πανεπιστήμιο Κρήτης Τμήμα Φυσικής

description

Μια σύντομη εισαγωγή στη Fortran 77του Νίκου Βουλγαράκη, Πανεπιστήμιο Κρήτης

Transcript of Εισαγωγή στην Fortran 77

  • -151: H FORTRAN 77

  • 1 .............................................................................................................................. 3

    1.1 FORTRAN 77 .................................................................................... 3 1.1.1 ................................................................................................. 3 1.1.2 ................................................................................................ 4 1.1.3 ............................................................................................... 5

    1.2 ............................................................................................... 5 1.3 ( A)......................................................................................... 6

    1.3.1 .................................................................................................... 6 1.3.2 ................................................................................................ 7 1.3.3 ............................................................................. 7

    1.4 read print................................................................................................. 7 1.4.1 read .............................................................................................................. 7 1.4.2 print.............................................................................................................. 8

    2.4 ............................................................................. 8 2 .............................................................................................................................. 9

    2.1 ( ) ......................................................................................... 9 2.2 parameter ...................................................................................................... 9 2.3 (intrinsic functions) .................................................... 9 ........................................................................................................................... 10 2.4 (external function).................................................... 12 2.5 IF ............................................................................................. 14 ........................................................................................................ 15

    3 ............................................................................................................................ 17 3.1 & ( ) ..................................... 17 3.2 A do .................................................................................... 19 3.3 do while............................................... 25

    4 ............................................................................................................................ 28 4.1 .................................................... 28 4.2 (subroutines)..................................................................................... 32

    5 ............................................................................................................................ 37 5.1 ........................................................................................... 37

    5.1.1 .......................................................................................................... 38

    5.2 ( ) ....................................................................................... 39 5.2.1 (double precision).................................... 39 5.2.2 (complex)................................................................................. 40

    5.3 .............................................................................................. 41 5.3.1 Open........................................................................................................................ 41 5.3.2 Close ....................................................................................................................... 42 5.3.3 Write ....................................................................................................................... 42 5.3.4 Read........................................................................................................................ 43

  • ,, //

    3

    1

    1.1 FORTRAN 77 . , ( ) .

    FORTRAN 77 : 26 ( ) 0,1,2,...,9 : + - * / = ( ) . , _

    1. FORTRAN 77 . , print*,sum PrINt*, Sum pRInt*,suM

    2. . print*, sum pr in t * , Su m

    3. . :

    31 . oi :

    ( ), 0,1,2,...,9 _ (underscore)

    1.1.1 FORTRAN 77 :

  • ,, //

    4

    program name stop end

    1. FORTRAN 77 program end. : .

    2. program (. 1.1)

    3. stop .

    stop end , end.

    program name

    1 2 stop 3 stop end stop , . 3.

    1.1.2 FORTRAN . :

    1. 7 72 . 2. c ( *) 1,

  • ,, //

    5

    3. 6 ( &), . 72.

    4. 2-5 ( ) () .

    1.1.3 123456789.................................................................................................. program circle c c c c c r (input) c perimetros (output) c emvadon (output) real r, perimetros, emvadon print*, read*, r perimetros = 2.*3.14*r emvadon = 3.14*r**2 print*, :, perimetros print*, :, emvadon stop end

    1.2 : + () - () * () / () ** ( )

  • ,, //

    6

    :

    ( ) 2dc

    babac ++++

    FORTRAN 77 c*(a+b) + (a+b)/c + d**2 : :

    1. 2. 3.

    : 2*3+20 = 6+20 = 26 2+100/20 = 2+5 = 7 5+6*3**2 = 5+6*9 = 5+54 = 59 . : (2*3**2 +1)*2-6 = (2*9+1)*2-6 = (18+1)*2-6 = 19*2-6 = 38-6 = 32

    1.3 ( A) H FORTRAN 77 ( ) ( ). -, : 23 -100 2341 10000000001 , 23. 1.0000 .00231 -192. 134.2345 . 23 23. , FORTRAN 77 , .

    1.3.1 FORTRAN 77 :

  • ,, //

    7

    integer () real (, 8 )

    double precision (, 16 ) complex () character () logical (, true false)

    1.3.2

    type .: integer a1, sum, count real energy, sum, r

    A (implicit)

    o FORTRAN 77 . , i, j, k, l, m ,n ( isum, jcount), , . a-h and o-z, (. sum, x, func)

    1.3.3

    =

    : a=0.5*10.**2 energy = 0.5*m*v**2,

    m v . read (. ).

    1.4 read print

    1.4.1 read : read*,

  • ,, //

    8

    . : read*,a1, r, energy : : 1 (,)

    enter. 2 enter .

    1.4.2 print : print*, / / . : print*, , emvadon 1 : ....... 2 .

    2.4 , :

    1. FORTRAN .f (. pogram1.f)

    2. (compile) . g77 program1.f o program1.exe

    3. program1.exe program1.exe 4. ( program1.exe,

    (compiler) a.out) 5. program1.exe

    : .exe . - (executable).

  • ,, //

    9

    2

    2.1 ( ) (. 1.3). , FORTRAN (implicit) . . ; (compiler) ( ) . : implicit none program (implicit none = ). compiler . .

    2.2 parameter , parameter : parameter ( = ) : parameter . . . real pi, f, npi integer N parameter (pi=3.141592, N=100, f=3.2, npi=3.*pi)

    2.3 (intrinsic functions) (+ - * / ) FORTRAN 77 .

  • ,, //

    10

    (intrinsic functions) : ( ) : F77 sqrt(x) : || abs(x) : ex exp(x) : ln(x) log(x) : (x) sin(x) : (x) cos(x) : (x) tan(x) : (x) cotan(x) : ( abs) . abs . : F77

    int(x) Real integer ( . .)

    real(x) Integer real max(x1,x2,) integer

    real x1,x2,

    min(x1,x2,) 1 5 .

    123456789........................... program maxmin c 5

  • ,, //

    11

    c a1,a2,a3,a4,a5 (inputs) c maximum (output): c minimum (output): implicit none real a1,a2,a3,a4,a5, maximum, minimum print*, 5 read*, a1, a2, a3, a4, a5 maximum = max(a1,a2,a3,a4,a5) minimum = min(a1,a2,a3,a4,a5) print*, :,maximum print*, :,minimum stop end 2 :

    ||)]sin()[sin()( 2 xxxexf x +++= 123456789........................... program paradeigma implicit none real x, fx print*, read*, x fx= exp(x) + ( cos(x) + sin(x) )**2 + abs(x) print*, :, fx stop end =f(x1)+f(x2)+f(x3),

    :

  • ,, //

    12

    123456789........................... program paradeigma2 implicit none real x1, x2, x3, print*, 3 o read*, x1, x2, x3 = exp(x1) + ( cos(x1) + sin(x1) )**2 + abs(x1) & + exp(x2) + ( cos(x2) + sin(x2) )**2 + abs(x2) & + exp(x3) + ( cos(x3) + sin(x3) )**2 + abs(x3) print*, :, stop end . f(x) . : fx = f(x1)+f(x2)+f(x3) FORTRAN f(x) ! (external functions). .

    2.4 (external function) : function ( ) ( ) = return end

  • ,, //

    13

    f(x) : 123456789................................... real function f(x) implicit none real x f = exp(x) + ( cos(x) + sin(x) )**2 + abs(x) return end

    1. . , . , prog.f func.f, :

    g77 prog.f func.f o prog.exe : .

    2. , .

    3.

    return.

    4. . :

    )|(|),( yxeyxg += .

    123456789........................... program paradeigma

  • ,, //

    14

    implicit none real x, y, g print*, 2 o read*, x, y print*, :, g(x,y) stop end c real function g(x, y) implicit none real x, y g = exp(- ( abs(x) + y ) ) return end

    2.5 IF . if. H if : if () then 1 endif : , 1. if endif. , if : If () if : if (1 ) then 1

  • ,, //

    15

    else if (2 ) then 2 else if ... else end if : , 1, (elseif) , 2 . , , else. , if endif.

    = ( ): .eq. (equal to) ( ): .ne. ( not equal to) > ( ) .gt. (gteater than) ( ) .ge. (greater than or equal to) < ( ) .lt. (less than) ( ) .le. (less than or equal to) , . and. .or. : : , .and. .or.

  • ,, //

    16

    end if return end

  • ,, //

    17

    3

    3.1 & ( ) . , , , . , x integer, : x=2*3+10-2 =14 14 x. x real, 14 (. x=14.). . , . : real x x=5/2=2. () integer x x=5/2=2 () . x o, . x , 5 2 ( 5. 2.) : real x x=5./2.=2.5 , :

  • ,, //

    18

    , . , real x x=5./2=2.5 ( x=5/2.=2.5 . . 5/2*4.+1. (. 1.2) . , , :

    5/2*4.+1.=2*4.+1.=8.+1.=9. . 4.*5/2+1. = 20./2+1.=10.+1.=11. . . . ...

    o i=2 i=i+1 i 0=1 (). i ( 2) , 1 i , 3 , =12000 y=0.000034 : x=1.2+4 x=0.12E+5

  • ,, //

    19

    y=3.4E-5 y=34E-6 , nE n10

    3.2 A do . do. do : do n=ni, nf, dn enddo n: ni: nf: dn: :

    ) )int(,0 max( dndnninf +

    . max() int() FORTRAN 77 (. 1.2). do do-loop.

    , 0 )int( +

    dndnninf

    , . , ni , ni+dn , . i) do I=1,21,2 (11 ) ii) do I=100,0,-2 (51 ) iii) do I=10,-1,2 (0 ) iv) do I=1,1,1 (1 )

  • ,, //

    20

    1 1 15

    program doloop implicit none integer i do i=1,15,2 print*,i enddo stop end

    1. , , .

    2. (. )

    3. . , 11 , do i=1,11 print*,i,i**2 enddo

    4. do-loop. ,

    do i=1,11

    i=i+1

    enddo .

    ... 2 1 +2 +3 + ...+10

  • ,, //

    21

    program doloop2 implicit none integer I,sum sum=0 do I=1,10 sum=sum+I enddo print*,To 1 10 :, sum stop end

    : . .

    3 1 , . , .

    program doloop3 implicit none integer i,isum print*, read*,N print*,To 1 , N, :, isum(N) stop end

    integer function isum(N)

    implicit none integer I, N isum=0 do i=1,N isum=isum+i enddo

  • ,, //

    22

    return end

    .... 4 Nxxxx +++++ ...1 32 , 5 (=5) x xmin xmax dx. xmin, xmax dx . program polyonymo implicit none real x, pol, xmin, xmax, dx print*, xmin, xmax dx read*, xmin, xmax, dx

    do x=xmin, xmax, dx print*, x, pol(x, 5) enddo stop end real function pol(x, N) implicit none integer N,i real x pol=1. do I=1,N pol=pol+x**I enddo return end

  • ,, //

    23

    5 do-loops.

    2

    1 1][

    = =+

    N

    i

    M

    jji

    program doloop3 implicit none integer N,M,sum print*, read*,N,M sum=0 do i=1,N do j=1,M sum=sum+(i+j)**2 enddo

    enddo print*,To :, sum stop end

    do-loops . do-loop

    do label n=ni, nf, dn label continue label 2 6 do-loop ( label , ).

  • ,, //

    24

    5

    sum=0 do 10 i=1,N do 20 j=1,M sum=sum+(i+j)

    20 continue 10 continue :

    sum=0 do 10 i=1,N do 10 j=1,M sum=sum+(i+j)

    10 continue do, , do-loop. do-loop . if goto label H label . continue . : do i=ni,nf,dn .. If( ) goto 10 . enddo 10 continue

    , , do-loop continue.

  • ,, //

    25

    dowhile .

    3.3 do while H do while : dowhile( ) Enddo : 1: 1 3.2

    program doloop2 implicit none integer I,sum sum=0 i=1 dowhile(i.le.10) sum=sum+i i=i+1 enddo print*,To 1 10 :, sum stop end

    2: 2, 4, 8, 16,.... 100

    program name implicit none

  • ,, //

    26

    integer n n=2 dowhile( n.le.100) print*,n n=2*n enddo stop end

    : dowhile . do,

    ...... ...... n=2 do i=1,10000 print*,n n=2*n if(n.gt.100) go to 10 enddo

    10 continue stop

    end

    do-loop . , dowhile do . do :

    n=2 do print*,n n=2*n if(n.gt.100) go to 10 enddo

    10 continue stop

  • ,, //

    27

    end do-loop n.gt.100 continoue. , do : do-loop. : , do-loop !!!!!!

  • ,, //

    28

    4

    4.1 . . , , . , ( ), . FORTRAN 77 . , integer A(4) real X(5) , (integer real), (A X) ( ). , , A, 4 5 . , . , (1)=3 (2)=5 (3)=0 (4)=123 (1)=4. (2)=9.123

  • ,, //

    29

    (3)=0.01 (4)=2.3 (5)=35. read*,A(1),A(2),A(3),A(4) . ... , , print*,A(1),A(2),A(3),A(4) sum=A(1)+A(2)*A(3)+A(4) : sum=3+0+123=126 , . . , (1) 1 ( ), (2) 2 ( ) . . , program vector implicit none integer A(4),i do i=1,4 read*,A(i) enddo sum=0

    do i=1,4 sum=sum+A(i) enddo print*,To :,sum stop end

  • ,, //

    30

    . do-loop, i=1, , i=2 , 4 . do-loop, . , 4 . 1000 ; , 1000 , . , program experiment implicit none real x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14,...... read*, x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14,...... :-( ????????????!!!!!!!!!!! (;) , .... , . . .

    real X(16)

    , ,

    integer N parameter (N=16) real X(N)

    T ! 5 16 ;

    real A(16), B(16), C(16),D(16), (16)

  • ,, //

    31

    integer N parameter (N=16)

    real A(N), B(N), C(N), D(N), E(N) 30 , 16 30, , =16 =30. ; , , . 0 . . , real Y(0:10) (0). , 11 (0),(1),....,(10) integer P(-2:2) 5 P(-2), P(-1), P(0), P(1) P(2) ( , ). , . : . real function mv(N,A) implicit none integer N,i c N: real A() mv=0. do I=1,N mv=mv+A(i) enddo

  • ,, //

    32

    mv=mv/real(N) return end , program name implicit none integer N,I parameter(N=100) real X(N),mesh_timh do I=1,N print*, , i, read*,X(i) enddo mesh_timh= mv(N,X) print*, , mesh_timh stop end : dimension dimension X(10), M(100) , 10 100 (. 1.3.2).

    4.2 (subroutines) , , . (subroutine) , . , , :

  • ,, //

    33

    1: (inputs) (outputs). 2: inputs outputs. 3: inputs ouput. 4: input output.

    Y , . ... , !!! ! .

    , : subroutine name ( ) implicit none return end subroutine ( ). , , return end. , 1 , mean_value, a, b (inputs) mv (output). subroutine mean_value(a, b, mv) implicit none real a, b, mv mv=(a+b)/2. return

  • ,, //

    34

    end () ( ) call . , : program name implicite none real a, b, c print*, read*, a, b call mean_value(a, b, c) print*, H , c stop end ... 2 . a=1. b=3., a=3. b=1. subroutine switch(a, b) implicite none real a, b, temp temp=a a=b b=temp return end , inputs outputs. 3 :

  • ,, //

    35

    subroutine my_print(a, b) implicite none real a, b print*,a,+,b,=,a+b return end H inputs . output. 4 ---------------------------------------------- subroutine print_line print*,------------------------------------------------- return end inputs outputs. . : , , call, call print_line .... x .

    =

    =N

    iiN xx

    1

    1 ||

    subroutine mvmsd(N,A,mv,msd) implicit none

  • ,, //

    36

    integer N real A(N),mv,msd c : mv mv=0. do i=1,N mv=mv+A(i) enddo mv=mv/real(N) c : msd msd=0. do i=1,N msd=msd+abs(A(i)-mv) enddo msd=msd/real(N) return end

  • ,, //

    37

    5

    5.1 4.1, . FORTRAN 77 , . ,

    =

    121110987654321

    A

    3x4 3 4 . i,j, i j . , 2 3 2,3 7. FORTRAN 77 . : Real A(4,6) , (real, integer ) , (,). , , , Real x(0:4, -1:7) 5 (0,1,2,...,5) 9 (-1,0,1,...,7), 5x9=45 . A 1 . subroutine Min2D(N,M,A,amin,imin,jmin)

  • ,, //

    38

    implicit none real A(N,M), Amin integer imin,jmin Amin=A(1,1) do i=1,N do j=1,M If(A(i,j).lt.Amin) then Amin=A(i,j) imin=i jmin=j endif enddo enddo return end

    5.1.1 do-loop: do i=1,3 do j=1,4 print*, , i,j, read*, A(i,j) enddo enddo . do-loop, do i=1,3 do j=1,4 print*, A(i,j) enddo enddo : 1 2 3

  • ,, //

    39

    11 12 . . do-loop. , do I=1,3 C do-loop print*, (A(i,j), j=1,4) enddo , 1 2 3 4 5 6 7 8 9 10 11 12 . , do-loop . , compiler . compiler, . , format . do-loop . [1] 117

    5.2 ( )

    5.2.1 (double precision) 8 . FORTRAN 77 16 . (double precision) : double precision x,y real*8 x,y

  • ,, //

    40

    , D0. , 1.321 : X=1.321D0 : X=13.21D-1 x= 132.1D-2 =0.1321D+1 x=0.01432D+2 , , . nD n10 : D, . . double precision, , ( ) ( ), D. , . . real x double precision

    Dble(x)

    5.2.2 (complex) w w=a+ib, a b . FORTRAN 77 : Complex w Complex*8 w w, , .

  • ,, //

    41

    , , 2.1+3i : Complex w W=(2.1,3) , . print. w, Real(w) Imag(w) w Abs(w) FORTRAN 77 .

    5.3 . FORTRAN 77 . .

    5.3.1 Open open . . open : open (, file = ) . , ,

  • ,, //

    42

    . write read, . open: Open (1,file=data.in) Open (33,file=outputs) FORTRAN , . , , . .

    5.3.2 Close close , . Close (1) Close (33) , . . . , , .

    5.3.3 Write , write: , Write(*,*) ,emvadon Print*, ,emvadon To * write * print .

  • ,, //

    43

    ( ) (. format). T write . , . , Open (1,file=data.out) Write (1,*) ,emvadon Close (1) data.out

    5.3.4 Read H read(*,*) read*,. write(*,*), format , * . * , . 1 dadta.in 11.0 3. 4. 0.1 8. 14. , : Real a,b,c,d,e,f Open(1,file=data.in) Read(1,*) a,b,c Read(1,*) c, d, f : a=11.0 b= 3. c= 4. d= 0.1 e =8. f=14. , , read, . Read(1,*) a,b Read(1,*) d, f

  • ,, //

    44

    : a=11.0 b= 3. d= 0.1 f=8. c e ( ) 2 input 30 ( ). : Real A(30) Open (1,file=inputs) Do I=1,30 Read(1,*) A(i) Enddo Close(1) 3 . read .

    Real A(1000) Integer I,

    Open(1,file=inputs)

    =0 Do Read(1,*,END=10) A(i) =+1 Enddo

    10 continue continue. . 2 15 3 5 . do-loop Real A(3,5) Integer i,j Open (8,file=D2.in)

    Do I=1,3

  • ,, //

    45

    Read(8,*) (A(i,j),j=1,5) Enddo Close (8) character, format, data, common, intrinsic, external functions

    character [1] . 110 [2] . 242 [3] . 290, 316

    format [2] . 83 [3] . 183

    data [1] . 131 [2] .117 [3] . 53, 124

    common

    [1] . 94 [2] . 175 [3] . 385

    intrinsic, external functions

    [3] . 408

    [1] FORTRAN 77, John Shelley, . . [2] FORTRAN, , [3] FORTRAN 77 programming, T. M. R. Ellis, Addison-Wesley publishing company

    FORTRAN 77 ( A) read print read print ( ) parameter (intrinsic functions) (external function)2.5 IF & ( ) A do do while (subroutines) ( ) (double precision) (complex) OpenCloseWriteRead