quiver Subroutine

public subroutine quiver(x, y, u, v, s, c, scaling, lineColor, lineStyle, lineWidth)

Arguments

Type IntentOptional AttributesName
real(kind=wp), intent(in), dimension(:):: x

x-positions of vectors

real(kind=wp), intent(in), dimension(:):: y

y-positions of vectors

real(kind=wp), intent(in), dimension(:,:):: u

u-components of vectors

real(kind=wp), intent(in), dimension(:,:):: v

v-components of vectors

real(kind=wp), intent(in), optional dimension(:,:):: s

Scale of vectors

real(kind=wp), intent(in), optional dimension(:,:):: c

Color values for vectors

real(kind=wp), intent(in), optional :: scaling

Scaling of vectors < 0 = Automatic, then scaled 0 = Automatic

0 = Directly scaled

character(len=*), intent(in), optional :: lineColor

Color of vectors

character(len=*), intent(in), optional :: lineStyle

Style of vectors' lines

real(kind=wp) , optional :: lineWidth

Width of vectors' lines

Description

Plot vectors

Calls

proc~~quiver~~CallsGraph proc~quiver quiver plcol1 plcol1 proc~quiver->plcol1 interface~mixval mixval proc~quiver->interface~mixval plvect plvect proc~quiver->plvect
Help

Called By

proc~~quiver~~CalledByGraph proc~quiver quiver proc~doquiver doQuiver proc~doquiver->proc~quiver program~examples_prg examples_prg program~examples_prg->proc~doquiver
Help

Variables

TypeVisibility AttributesNameInitial
real(kind=pp), public, dimension(:), allocatable:: xl
real(kind=pp), public, dimension(:), allocatable:: yl
real(kind=pp), public, dimension(:,:), allocatable:: ul
real(kind=pp), public, dimension(:,:), allocatable:: vl
real(kind=pp), public, dimension(:,:), allocatable:: sl
real(kind=pp), public, dimension(2):: xb
real(kind=pp), public, dimension(2):: yb
real(kind=pp), public, dimension(2):: sb
real(kind=pp), public, dimension(2):: cb
real(kind=pp), public, dimension(2):: d
real(kind=pp), public :: scalingl
real(kind=pp), public :: scl
real(kind=pp), public :: mag
real(kind=pp), public :: clr
integer, public :: i
integer, public :: j

Source Code

	subroutine quiver(x,y,u,v,s,c,scaling,lineColor,lineStyle,lineWidth)
		!! Plot vectors
		real(wp),dimension(:),intent(in)::x
			!! x-positions of vectors
		real(wp),dimension(:),intent(in)::y
			!! y-positions of vectors
		real(wp),dimension(:,:),intent(in)::u
			!! u-components of vectors
		real(wp),dimension(:,:),intent(in)::v
			!! v-components of vectors
		real(wp),dimension(:,:),intent(in),optional::s
			!! Scale of vectors
		real(wp),dimension(:,:),intent(in),optional::c
			!! Color values for vectors
		real(wp),intent(in),optional::scaling
			!! Scaling of vectors
			!! < 0 = Automatic, then scaled
			!!   0 = Automatic
			!! > 0 = Directly scaled
		character(*),intent(in),optional::lineColor
			!! Color of vectors
		character(*),intent(in),optional::lineStyle
			!! Style of vectors' lines
		real(wp),optional::lineWidth
			!! Width of vectors' lines
		
		real(pp),dimension(:),allocatable::xl,yl
		real(pp),dimension(:,:),allocatable::ul,vl,sl
		real(pp),dimension(2)::xb,yb,sb,cb,d
		real(pp)::scalingl,scl,mag,clr
		integer::i,j
		
		xl = localize(x)
		yl = localize(y)
		ul = localize(u)
		vl = localize(v)
		
		d = real([x(2)-x(1),y(2)-y(1)],pp)
		
		xb = real(mixval(x),pp)
		yb = real(mixval(y),pp)
		if(present(s)) then
			sl = localize(s)
			sl = sl/maxval(sl)
		else
			sl = localize(u**2+v**2)
			sl = sqrt(sl)
			sl = sl/maxval(sl)
		end if
		sb = [minval(sl),maxval(sl)]
		cb = 0.0_wp
		if(present(c)) cb = real([minval(c),maxval(c)],pp)
		
		scalingl = 1.0_pp
		if(present(scaling)) scalingl = real(scaling,pp)
		
		if(present(lineColor)) call setColor(lineColor)
		if(present(lineStyle)) call setLineStyle(lineStyle)
		if(present(lineWidth)) call setLineWidth(lineWidth)
		
		do i=1,size(u,1)
			do j=1,size(u,2)
				mag = norm2([ul(i,j),vl(i,j)])
				scl = scalingl*norm2(d)*sl(i,j)
				if(abs(scl)<1.0E-5_wp) cycle
				if(present(c)) then
					clr = real( (c(i,j)-cb(1))/(cb(2)-cb(1)) ,pp)
					clr = max(clr,0.0_pp)
					clr = min(clr,1.0_pp)
					call plcol1( clr )
				end if
				call plvect(ul(i:i,j:j)/mag,vl(i:i,j:j)/mag,scl,xl(i:i),yl(j:j))
			end do
		end do
		
		call resetPen()
	end subroutine quiver