Examples

The following Visual Fortran example program illustrates the use of the Fortran routine APIs (faglxxxx routines). This is a Sample program that can be found in the folder  ...\ArrayVisualizer\Samples\Fortran\Simple2\:


program MAIN

	! AVDef is the Array Visualizer module file
        use AVDef
	use DFLib

	IMPLICIT NONE
	! Define a 2D array of reals
	integer, parameter :: lbc=1, ubc=40, lbr=1, ubr=50
	real, parameter :: pi=3.14159
	! Using allocatable array M for array viewing
	! The array_visualizer attribute will result in better performance
	! when using the aview lib with allocatable arrays.
	real(4), allocatable :: M(:, :)
	!DEC$ATTRIBUTES array_visualizer :: M
	integer :: lbnd(2) = 0
	real x, y, z, rval
	integer status, i, j, arrayData
	character(1) :: key

	! allocate memory for the array
	allocate(M(lbc:ubc, lbr:ubr))

	print *, "Initializing array data"
	do i=lbr,ubr
		x = i/(ubr-lbr+1.0)
		do j=lbc,ubc
			y = j/(ubc-lbc+1.0)
			z = sin(x*pi) + cos(y*pi);
			M(j, i) = z
		end do
	end do

	! Call StartWatch since we are interested in viewing M
	call faglStartWatch(M, status)

	! Set lbnd to the lower bound values of M
	! (This is not really needed if we are using the default Fortran array
	! indexing value of 1)
	lbnd(1:size(shape(M))) = lbound(M)
	call faglLBound(M, lbnd, status)


	print *, "Starting Array Viewer"
	call faglShow(M, status)

	! Set the title bar on ArrayViewer
	call faglName(M, "sin(x) + cos(y)", status)

	print *, "press any key to continue"
	key = GETCHARQQ()

	print *,  "Adding some random fluctuations to the array data"
	do i=lbr,ubr
		do j=lbc,ubc
			call RANDOM(rval)
			rval = rval * 0.2 - 0.1
			M(j, i) = M(j, i) + rval
		end do
	end do

	print *, "Informing the viewer that the array data has been changed."
	call faglUpdate(M, status)

	! Change the title to reflect the changes in the data set
	call faglName(M, "sin(x) + cos(y) + noise", status)

	print *, "press any key to continue"
	key = GETCHARQQ()

	! Uncomment the following line to have the ArrayViewer
	! closed automatically.
	! call faglClose(M, status)

	! Remove M from the watch list
	call faglEndWatch(M, status)

	! Free the memory allocation
	deallocate(M)

	print *, "Done!"

  end program MAIN

This example illustrates most of the Fortran API calls. The program displays the initial values of allocatable array M, and then, after calling faglUpdate, displays the new values.

The following example also shows the use of the cDEC$ ATTRIBUTES option ARRAY_VISUALIZER:


real(4), allocatable :: MyArray(:, :)
!DEC$ ATTRIBUTES array_visualizer :: MyArray

When this option is used, array memory can be shared between the Array Viewer and your application. Otherwise, the array data will need to be copied during each faglUpdate call.

Array Visualizer Sample programs are installed on your hard disk if you selected a Complete installation. You can also copy Samples folders from the Array Visualizer CD-ROM to your hard disk.