! This file demonstrates the Fortran 90 type and interface features.
! Note that types and interfaces can not have global scope and so must
! be defined in every program unit in which they are used.
! Prepared by Dr. C. S. Tritt
! Last updated 10/18/98
module types
! Use a module to assure types are consistently defined.
type part
real :: v_0 ! Initial velocity in ft/s.
real :: angle ! Angle of departure in radians.
real :: drag ! Aerodynamic drag in ft**0.5.
end type part
end module types
program TypeTest
use types
implicit none
! Types do not scope into Interface blocks so they must be repeated.
interface
real function y(t, junk)
use types
real, intent(in) :: t
type(part), intent(in) :: junk
end function y
end interface
! The following is the main program.
real :: v = 100.0 ! Velocity
real :: a = 1.2 ! Angle
real :: d = 3.0 ! Drag
type(part) :: junk ! The part of interest.
junk%v_0 = v
junk%angle = a
junk%drag = d
write(*,*) 'V_0 = ', junk%v_0, ' Angle = ', junk%angle, &
' Drag = ', junk%drag, ' y(5.0) = ', y(5.0, junk)
stop
end program TypeTest
real function y(t, piece)
! This function calculates the vertical position of an object.
use types
implicit none
real, intent(in) :: t
type(part), intent(in) :: piece
real, parameter :: halfg = 32.2/2.0
y = piece%v_0*t*sin(piece%angle) - halfg*t**2 - &
piece%drag*(piece%v_0*t)**0.5
return
end function y