马上注册,结交更多好友,享用更多功能,让你轻松玩转社区。
您需要 登录 才可以下载或查看,没有账号?我要加入
x
<P>下面的这些用法您用过吗?</P>
<P><STRONG>Where</STRONG> Arrays allow a more compact notation for conditional assignment </P><PRE><CODE> real, dimension(100,100) :: a, b<br>
...
where(a>0.0)
b = a
elsewhere
b = 0.0
end where
</CODE></PRE>
<P><STRONG>Mask operations</STRONG> There are also many conditional tests and masked intrinsics </P><PRE><p>
if (all(a==0.0)) write(*,*) 'a is zero'
if (any(a==0.0)) write(*,*) 'a has at least 1 zero element'
write(*,*) 'a has', count(a==1.0), ' elements equal to 1'
a = merge(0.000001, a, a==0.0)
b = sum(a, a>0.0)
c = product(a+1.0, a>=-1.0)
</PRE>
<P><STRONG>Assumed shape and automatic</STRONG> With array notation comes the possibility of assumed shape </P><PRE><p>
subroutine foo(a,b)
real, dimension(:,:) :: a
real, dimension(0:,-5:) :: b
...
end subroutine foo
and automatic arrays
subroutine foo(a)
real, dimension(:,:) :: a
real, dimension(size(a,1), size(a,2)) :: b
...
end subroutine foo
</PRE>
<P><STRONG>Case</STRONG> Often want to test for more than one condition. An if-then-elseif-else-endif tree is not suitable. Fortran 90 provides a case statement </P><PRE>select case(ch)<p>
case('a','c','d')
x = sin(y)
case('w':)
x = cos(y)
case default
x = y
end select
</PRE>
<P><STRONG>Intent</STRONG> Fortran90 provides a mechanism to tell the compiler about how variables are used within a sub program. This allows the compiler to provide additional checking and optimisation. </P><PRE><p>
subroutine foo(a, b, c)
real, intent(in) :: a
real, intent(inout) :: b
integer, intent(out) :: c
...
end subroutine foo
</PRE>now, something like a=1.0 inside foo will generate a compiler error. Also, c will be undefined on entry into foo
<P><STRONG>Optional arguments</STRONG> Subroutines and fuction can have optional arguments in Fortran90 </P><PRE><p>
function foo(a, b)
real :: foo
real, intent(in) :: a
integer, intent(in), optional :: b
if (present(b)) then
foo = a**b
else
foo = a
end if
end function foo
</PRE>
<P><STRONG>Interfaces</STRONG> F77 did not have type checking for arguments to subroutines and functions. F90 allows the declaration of an interface to a sub program which the compiler will then enforce. </P><PRE><p>
program main
interface
real function fun(x)
real :: x
end function fun
end interface
real :: y
y = fun(10.0) ! Calling y=fun(1) will produce a compiler error.
end program main
</PRE>
<P><STRONG>Modules</STRONG> Modules provide a mechanism to package data types, derived types, function, subroutines and interfaces together. Including a module gains access to all public components within that module and automatically defines interfaces to all functions and subroutines within. </P><PRE> <p>
module foobar
real :: a
integer :: b
contains
subroutine foo(c, d)
integer :: c
real :: d
d = d * a**c + b
end subroutine foo
end module foobar
</PRE>
<P><STRONG>Using modules</STRONG> A module can then be used to gain access to its components </P><PRE><p>
program main
use foobar
real :: x
x = 10.0
b = 3
call foo(5, x)
end program main
</PRE>Since the subroutine foo is within a module its interface is automatic and enforced by the compiler.
<P><STRONG>Modules cascade</STRONG> Modules can be cascaded. </P><PRE> <p>
module aaa
...
end module aaa
module bbb
use module aaa
...
end module bbb
module ccc
use module bbb
...
end module ccc
</PRE>Module ccc now has access to all public objects within module bbb and module aaa
<P>Being more specific, You can elect to <STRONG>use only certain objects from a module</STRONG> </P><PRE><p>
module bbb
use aaa, only: foo, bar
...
end module bbb
</PRE>which only gains access to foo and bar within module aaa
<P><STRONG>Public and private</STRONG> You can state which objects within a module are publically available or private </P><PRE><p>
module foobar
private
public :: foo
real :: a
real, public :: b
contains
subroutine foo(...)
...
end subroutine foo
subroutine bar(...)
...
end subroutine bar
end module foobar
</PRE>
<P><STRONG>Derived types</STRONG> Ofter more complex data types are required. Fortran90 allows this through derived types. </P><PRE><p>
type particle
real, dimension(3) :: pos, vel, acc
real :: mass
integer :: n
end type particle
type(particle) :: p
p%mass = 1.0
p%n = 1
p%pos = (/ 1.0, 2.0, 4.0 /)
p%vel = 0.0
p%acc = 0.0
</PRE>
<P><STRONG>Derived types may be extremely complex</STRONG> </P><PRE><p>
type particlebox
type(particle), dimension(:), pointer :: particles
real :: lx, ly, lz
end type particlebox
type(particlebox) :: box
allocate(box%particles(100))
box%particles(10)%mass = 1.0d0
</PRE>
<P><STRONG>Operators</STRONG> You can define your own operators with an interface block </P><PRE><p>
module a
type point
real :: x, y
end type point
interface operator(.dist.)
module procedure calcdist
end interface
contains
function calcdist(p1, p2)
type(point) :: p1, p2
real :: calcdist
calcdist = sqrt((p1%x-p2%x)*<strong>2 + (p1%y-p2%y)</strong>*2)
end function calcdist
</PRE>
<P><STRONG>Dynamic memory</STRONG> Fortran90 introduced the concept of dynamic memory allocation and pointers. To dynamically allocate memory, an array must be declared allocatable </P><PRE> <p>
real, dimension(:,:), allocatable :: a
allocate(a(100,100))
...
deallocate(a)
</PRE>Allocatable arrays can not be used within a derived data type. You need to use a pointer.
<P><STRONG>Pointers</STRONG> Unlike C style pointers, Fortran pointers point to a specific object. That object must be another pointer of the same type or a target. </P><PRE><p>
real, dimension(100,100), target :: a
real, dimension(:,:), pointer :: b
b=>a
</PRE>Now, both a and b refer to the same piece of memory. NOTE: b is NOT an array of pointers. It is a pointer to an array
<P><STRONG>More pointers</STRONG> You can allocate memory directly to a pointer as with an allocatable array </P><PRE><p>
real, dimension(:,:), pointer :: a
nullify(a)
allocate(a(100,100))
...
deallocate(a)
</PRE>A call to nullify(a) after an allocate will cause a memory leak.
<P><STRONG>Pointers to subsections</STRONG> You can use pointers to reference a subsection of an array. Be aware that this may have a serious performance impact. </P><PRE> real, dimension(100,100), target :: a
real, dimension(:,:), pointer :: b
b=>a(20:30,40:50)
</PRE>
<P><STRONG>The linked list</STRONG> One of the most useful features of derived types and pointers is the ability to create a dynamic structure called a link list. </P><PRE><p>
type node
type(node), pointer :: next, prev
real, dimension(100,100) :: a
end type node
type(node), pointer :: ll, cur
integer :: i
allocate(ll)
ll%next => ll
ll%prev => ll
cur => ll
do i = 1, 10
allocate(cur%next)
cur%next%prev => cur
cur%next%next => ll
cur => cur%next
end do
</PRE>This creates a dynamic list of arrays. Now, indexing b effectively strides through the array a
<P><STRONG>Linked list operations</STRONG></P>Link lists can be grown <PRE> allocate(newnode)
newnode%prev => cur
newnode%next => cur%next
cur%next%prev => newnode
cur%%next => newnode<BR>
</PRE>and shrunk <PRE> oldnode => cur
cur%prev%next => cur%next
cur%next%prev => cur%prev
cur => cur%next
deallocate(oldnode)
</PRE> |