|
NAME
userl - subroutine frame for the definition of a bilinear form L.
SYNOPSIS
- SUBROUTINE USERL (
-
T, GROUP, CLASS, COMPV, COMPW, LAST,
NELIS, L, DIM, X, TAU, NK, U, DUDX,
LT, UT, DUTDX, NOP, NOPARM, DNOPDX,
NRSP, RSPARM, NRVP, RVP1, RVPARM,
NISP, ISPARM, NIVP, IVP1, IVPARM,
L3, L2, L1, L0)
- INTEGER
-
GROUP, CLASS, COMPV, COMPW, LAST, NELIS, L, DIM, NK, LT, NOP,
NRSP, NRVP, RVP1, NISP, NIVP, IVP1
- INTEGER
-
ISPARM(NISP), IVPARM(IVP1,NIVP)
- DOUBLE PRECISION
-
T, X(L,DIM), TAU(L,DIM,CLASS),
U(L,NK), DUDX(L,NK,CLASS), UT(LT,NK), DUTDX(LT,NK,CLASS),
NOPARM(L,NOP), DNOPDX(L,NOP,CLASS), RSPARM(NRSP), RVPARM(RVP1,NRVP),
L3(L,CLASS,CLASS), L2(L,CLASS), L1(L,CLASS), L0(L)
PURPOSE
userl is the subroutine which defines the bilinear form L. L
depends linearly on two arguments called first and second test function.
L is a sum over the product of component COMPV of the first
test function and component COMPW of the second test function
(COMPV,COMPW=1,... ,NK) and over
the manifolds M(CLASS) (CLASS=0,1,... ,DIM).
The terms of the sum are
integrals with M(CLASS) as domain of integration and the product of
the test functions and their derivatives with respect to the space
directions/tangential directions multiplied by coefficients L3, L2,
L1 and L0 as the kernels of integration. The routine userl
defines the values of the coefficients L3, L2, L1
and L0. They may depend on the location, the integer and real
parameter sets of the elements, the node parameter set and
its derivative with respect to space. Additionally the coefficient
may depend on the time, a given input solution and its derivatives
with respect to space. Keep in mind that for the solution
this dependency is not considered by the calling programs
veme00. If you want to
do this, you have to use the general tools veme02 and vemp02.
You have to
enter the statements which define the coefficients into a subroutine
with the argument list of userl. The name of the routine may
be changed. The name has to be declared by the EXTERNAL statement and
has to be entered instead of USERL (and USERK) into the argument
list of veme00.
By one call, the coefficients for the coupling of the component COMPV of
the first test functions and component COMPW of the second test
function and the manifold M(CLASS) have to be set
for a set (called stripe) of NELIS points which are in different elements
of the group GROUP. Since normally NELIS<>NE,
userl is called several times for one group, and so it is very
important that the vector parameters are selected with the offset
LAST. For a pair (COMPV, COMPW, GROUP)
userl is called, if MASKL(COMPV, COMPW,
GROUP)=true and NELTYP>0
for component COMPV and COMPW in group
GROUP. In the other case the coefficients L3, L2,
L1 and L0 are set to zero by the calling program.
The bilinear form L is called symmetrical if the first test function
and the second test function can be exchanged without any change
of the value, i.e. for all test functions V and W
L(V,W)=L(W,V)
holds. This can be expressed by the coupling coefficients of
the test functions:
L3(.,j1,j2) for (COMPV,COMPW) = L3(.,j2,j1) for (COMPW,COMPV)
L2(.,j1) for (COMPV,COMPW) = L1(.,j1) for (COMPW,COMPV)
L0(.) for (COMPV,COMPW) = L0(.) for (COMPW,COMPV)
for all j1,j2=1,...,CLASS, COMPV,COMPW=1,...,NK
and all groups. Use of the symmetry reduces the CPU time and the storage
amount during the solution, so you should carefully check whether
your bilinear form is symmetrical.
ARGUMENTS
- T double precision, scalar, input
-
Current time (not used).
- GROUP integer, scalar, input
-
Current group.
- CLASS integer, scalar, input
-
Dimension of the elements in the current group.
- COMPV integer, scalar, input
-
The component of the first test function whose coefficients have to be set.
- COMPW integer, scalar, input
-
The component of the second test function whose coefficients have to be set.
- LAST integer, scalar, input
-
Number of elements in the preceding stripes.
- NELIS integer, scalar, input
-
Number of elements in the current stripe.
- L integer, scalar, input
-
Leading dimension.
- DIM integer, scalar, input
-
Space dimension.
- X double precision, array: X(L,DIM), input
-
Coordinates of the points where the coefficients are evaluated. X(z,.)
lies in the z-th element in the current stripe.
- TAU double precision, array: TAU(L,DIM,CLASS), input
-
Normalized tangential directions of the elements, only defined for
0<CLASS<DIM. The vectors TAU(z,.,1), ....,
TAU(z,.,CLASS) span the tangential space on the element z
at point X(z,.). TAU(z,j,i) is the j-th
component of the i-th tangential direction at the element z at point
X(z,.). The vectors TAU(.,.,1) point from the local geometrical
node 1 to the local geometrical node 2 of the element. In the case of
CLASS=2 the vectors TAU(.,.,2) point from the local geometrical
node 1 to the local geometrical node 4/3 of the quadrilateral/triangle
element. If TAU is used, these have to be considered in the mesh
generation. In the case CLASS=DIM, TAU is undefined.
- NK integer, scalar, input
-
Number of components of the input solution = number of components of
the test functions.
- U double precision, array: U(L,NK), input
-
The values of the solution. U(z,j) is the j-th component of
the solution at the point X(z,.). U has undefined values for
the components with NELTYP=0 in the current group. If userl
is called by veme00 with STARTU=false, U is undefined.
- DUDX double precision, array: DUDX(L,NK,DIM), input
-
The values of the derivatives of the solution with respect to
the space direction in the case of CLASS=DIM and
with respect to the tangential directions
in the case of CLASS<DIM. DUDX(z,j,i) is
the derivative of the j-th component of
the solution at the point X(z,.) with respect to the
i-th space direction/with respect to TAU(z,.,i). DUDX has
undefined values for the components with NELTYP=0 in the current
group. If userl is called by veme00 with
STARTU=false, DUDX is undefined.
- LT integer, scalar, input
-
Not used.
- UT double precision, array: UT(LT,NK), input
-
Not used.
- DUTDX double precision, array: DUTDX(LT,NK,DIM), input
-
Not used.
- NOP integer, scalar, input
-
Number of node parameters.
- NOPARM double precision, array: NOPARM(L,NOP), input
-
Interpolation of the node parameters. NOPARM(z,i)
is the i-th node parameter at point X(z,.).
- DNOPDX double precision, array: DNOPDX(L,NOP,DIM), input
-
Derivative of the interpolation of the node parameters with
respect to the space direction in the case of CLASS=DIM and
with respect to the tangential directions in the case of
CLASS<DIM. DNOPDX(z,i,j) is the derivative of the
i-th node parameter with respect to the j-th space direction/with respect
to TAU(z,.,i) at point X(z,.).
- NRSP integer, scalar, input
-
Number of real scalar parameters of the current group.
- RSPARM double precision, array: RSPARM(NRSP), input
-
Set of the real scalar parameters of the current group.
- NRVP integer, scalar, input
-
Number of real vector parameters of the current group.
- RVP1 integer, scalar, input
-
Leading dimension of the real vector parameters of the current group.
- RVPARM double precision, array: RVPARM(RVP1,NRVP), input
-
Set of the real vector parameters of the current
group. RVPARM(LAST+z,*) is the parameter set of the z-th element
in the stripe.
- NISP integer, scalar, input
-
Number of integer scalar parameters of the current group.
- ISPARM integer, array: ISPARM(NISP), input
-
Set of the real scalar parameters of the current group.
- NIVP integer, scalar, input
-
Number of integer vector parameters of the current group.
- IVP1 integer, scalar, input
-
Leading dimension of the integer vector parameters of the current group.
- IVPARM integer, array: IVPARM(IVP1,NIVP), input
-
Set of the integer vector parameters of the current
group. IVPARM(LAST+z,*) is the parameter set of the z-th
element in the stripe.
- L3 double precision, array: L3(L,CLASS,CLASS), output
-
Coefficients for the coupling of the X-derivatives of the test
functions. L3(z,j1,j2)
is the coefficient for the interaction of the derivative of the
COMPV-th component of the first test function with respect to
the j1-th space variable/to TAU(z,.,j1) and the derivative
of the COMPW-th component of the second test function with respect to
the j2-th space variable to TAU(z,.,j2) at point X(z,.). Only
nonzero elements of L3 have to be defined.
- L2 double precision, array: L2(L,CLASS), output
-
Coefficients for the coupling of the X-derivatives of the first test function
and the second test function. L2(z,j1) is
the coefficient for the interaction of
the derivative of the COMPV-th component of the test function
with respect to the j1-th space variable/to TAU(z,.,j1) and
the COMPW-th component of the second test function at
point X(z,.). Only nonzero elements of L2 have to be defined.
- L1 double precision, array: L1(L,CLASS), output
-
Coefficients for the coupling of the first test functions and
the X-derivatives of the second test function. L1(z,j2)
is the coefficient for the interaction of the COMPV-th
component of the first test function and the derivative
of the COMPW-th component of the second test function with respect to
the j2-th space variable/to TAU(z,.,j2) at point X(z,.). Only
nonzero elements of L1 have to be defined.
- L0 double precision, array: L0(L), output
-
Coefficients for the coupling of the test functions. L0(z)
is the coefficient for the interaction
of the COMPV-th component of the first test function and
the COMPW-th component of the second test function at
point X(z,.). Only nonzero elements of L0 have to be defined.
EXAMPLE
See also vemexamples.
In the following
example we have NK=2 and DIM=2. V=(V1,V2) is the
first and W=(W1,W2) the second test function. ViXj denotes
the derivative of the i-th component of V with respect to the j-th space
direction and ViTAUj denotes the derivative of the i-th component
of V with respect to the j-th tangential direction TAUj.
The integration kernel for manifold M(2) is
V1X1 * W1X1 + V1X2 * W1X2 + C11 * V1 * W1 + C12 * V1 * W2 +
V2X1 * W2X1 + V2X2 * W2X2 + C21 * V2 * W1 + C22 * V2 * W2
where C11,C12,C21 and C22 are real constants. The matrix C
is zero for the elements in group 1 and depends on the element
number in group 2. Therefore the values are stored as real
vector parameters for the group 2. The integration kernel
for manifold M(1) represented by the elements in group 3 is
r * V1 * W1 + V2 * W1TAU1 + V2TAU1 * W1
where r is the distance to the origin. The masks have to be set as
follows:
MASKL(.,.,1)=( true , false )
( false , true )
MASKL(.,.,2)=( true , true )
( true , true )
MASKL(.,.,3)=( true , false )
( false , true )
The following statements have to be entered into userl:
C
C this is group 1:
C
IF ((COMPV.EQ.1).AND.(COMPW.EQ.1).AND.(GROUP.EQ.1)) THEN
DO 111 Z=1,NELIS
L3(Z,1,1)=1.
L3(Z,2,2)=1.
111 CONTINUE
ENDIF
IF ((COMPV.EQ.2).AND.(COMPW.EQ.2).AND.(GROUP.EQ.1)) THEN
DO 221 Z=1,NELIS
L3(Z,1,1)=1.
L3(Z,2,2)=1.
221 CONTINUE
ENDIF
C
C this is group 2:
C
IF ((COMPV.EQ.1).AND.(COMPW.EQ.1).AND.(GROUP.EQ.2)) THEN
DO 112 Z=1,NELIS
C11=RVPARM(LAST+Z,1)
L3(Z,1,1)=1.
L3(Z,2,2)=1.
L0(Z)=C11
112 CONTINUE
ENDIF
IF ((COMPV.EQ.1).AND.(COMPW.EQ.2).AND.(GROUP.EQ.2)) THEN
DO 122 Z=1,NELIS
C12=RVPARM(LAST+Z,2)
L0(Z)=C12
122 CONTINUE
ENDIF
IF ((COMPV.EQ.2).AND.(COMPW.EQ.1).AND.(GROUP.EQ.2)) THEN
DO 212 Z=1,NELIS
C21=RVPARM(LAST+Z,3)
L0(Z)=C21
212 CONTINUE
ENDIF
IF ((COMPV.EQ.2).AND.(COMPW.EQ.2).AND.(GROUP.EQ.2)) THEN
DO 222 Z=1,NELIS
C22=RVPARM(LAST+Z,4)
L3(Z,1,1)=1.
L3(Z,2,2)=1.
L0(Z)=C22
222 CONTINUE
ENDIF
C
C this is group 3:
C
IF ((COMPV.EQ.1).AND.(COMPW.EQ.1).AND.(GROUP.EQ.3)) THEN
DO 113 Z=1,NELIS
L0(Z)=SQRT(X(X,1)**2+X(Z,2)**2)
113 CONTINUE
ENDIF
IF ((COMPV.EQ.2).AND.(COMPW.EQ.3).AND.(GROUP.EQ.3)) THEN
DO 223 Z=1,NELIS
L1(Z,1)=1.
L2(Z,2)=1.
223 CONTINUE
ENDIF
The cases COMPV<>COMPW and CLASS=1 do not have to be
specified. The bilinear form is symmetrical if for all elements C12=C21.
SEE ALSO
VECFEM, mesh, equation, userf,
usrfu, userl, veme00,
vemexamples, vemfre.
COPYRIGHTS
Copyrights by Universitaet Karlsruhe 1989-1996.
Copyrights by Lutz Grosz 1996.
All rights reserved. More details see VECFEM.
by L. Grosz, Auckland , 6. June, 2000. |