Google

VECFEM3 Reference Manual: userf

Type: FORTRAN routine


NAME

userf - subroutine frame for the definition of linear form F


SYNOPSIS

SUBROUTINE USERF (
T, GROUP, CLASS, COMPV, RHS, 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, F1, F0)
INTEGER
GROUP, CLASS, COMPV, RHS, 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), F1(L,CLASS), F0(L)


PURPOSE

userf is the subroutine which defines the linear form F. F depends linearly on one argument called test function and depends on the time T, the searched solution U and its derivative UT with respect to time in an arbitrary way. The dependency on U is considered by the calling routines veme02 and the general case, which is the dependency on T, U and UT, is considered by the calling routines vemp02.

F is a sum over the component COMPV of the test functions (COMPV=1,... ,NK) and the manifolds M(CLASS) (CLASS=0,1,... ,DIM), which are defined by the elements of CLASS. The terms of the sum are integrals with M(CLASS) as domain of integration and the test functions and their derivatives with respect to the space direction/tangential direction multiplied by coefficients F0 and F1 as the kernel of integration. The routine userf defines the values of the coefficients F0 and F1. 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, the time, the solution and its derivative with respect to space, and the T-derivative of the solution and its derivative with respect to space.

You have to enter the statements, which define the coefficients into a subroutine with the argument list of userf. 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 USERF into the argument list of veme00, veme02 and vemp02.
By one call the coefficients of the component COMPV of the test functions 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, userf 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, GROUP) userf is called by veme00, veme02 and vemp02, if MASKF(COMPV, GROUP)=true and NELTYP>0 for component COMPV in group GROUP. In the other case the coefficients F1 and F0 are set to zero by the calling program.


ARGUMENTS

T double precision, scalar, input
Current time (only used for vemp02).
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 test function whose coefficients have to be set.
RHS integer, scalar, input
Current right hand side, only used by veme00.
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 stripe.
TAU double precision, array: TAU(L,DIM,CLASS), input
Normalised 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 solution.
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. The dependency of the coefficients of F on U is not considered in the calling routines veme00. If userf 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 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. The dependency of the coefficients of F on DUDX is not considered in the calling routines veme00. If userf is called by veme00 with STARTU=false, DUDX is undefined.
LT integer, scalar, input
Leading dimension, =0 for the calling routines veme00 and veme02.
UT double precision, array: UT(LT,NK), input
The values of the T- derivative of the solution. UT(z,j) is the j-th component of the T-derivative of the solution at the point X(z,.). UT has undefined values for the components with NELTYP=0 in the current group. The dependency of the coefficients of F on UT is not considered in the calling routines veme00 and veme02.
DUTDX double precision, array: DUTDX(LT,NK,DIM), input
The values of the derivatives of the T-derivative 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. DUTDX(z,j,i) is the derivative of the j-th component of the T-derivative of the solution at the point X(z,.) with respect to the i-th space direction/with respect to TAU(z,.,i). DUTDX has undefined values for the components with NELTYP=0 in the current group. The dependency of the coefficients of F on DUTDX is not considered in the calling routines veme00 and veme02.
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,j,i) is the derivative of the j-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.
F1 double precision, array: F1(L,CLASS), output
Coefficients for contributions of the X-derivatives of the test functions. F1(z,i) is the coefficient for the contribution of the derivative of the COMPV-th component of the test function with respect to the i-th space variable/to TAU(z,.,i) at the point X(z,.). Only non-zero elements of F1 have to be defined.
F0 double precision, array: F0(L), output
Coefficient for the contributions of the test functions to F. F0(z) is the coefficient for the contribution of the COMPV-th component of the test function at the point X(z,.). Only non-zero elements of F0 have to be defined.


EXAMPLES

See also vemexamples. In the following examples we have NK=2 and DIM=2. 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. VT denotes the derivative of V with respect of time T.

1st

This is a typical example for veme00. The integration kernel for manifold M(2) and the first right hand side is

A * V1  + B1 *  V2X1  + B2 * V2X2  ,

where A, B1 and B2 are real constants, which are non-zero in group 1 and zero in group 2. MASKF has the following entries:

   MASKF(.,1)=( true  , true  )
   MASKF(.,2)=( false , false )

The following statements have to be entered into userf:

      IF ((RHS.EQ.1).AND.(COMPV.EQ.1).AND.(GROUP.EQ.1)) THEN
        DO 10 Z=1,NELIS
         F0(Z) = A
10      CONTINUE
      ENDIF
      IF ((RHS.EQ.1).AND.(COMPV.EQ.2).AND.(GROUP.EQ.1)) THEN
        DO 20 Z=1,NELIS
         F1(Z,1) = B1
         F1(Z,2) = B2
20      CONTINUE
      ENDIF

The case GROUP=2 does not have to be specified.

2nd

This is a typical example for veme02. The integration kernel for manifold M(2) is

V1X1 * U1X1 + V1X2 * U1X2 + V1 * C1*U1*U2 +
 
V2X1 * U2X1 + V2X2 * U2X2 + V2 * C2*U2  ,

where C1 and C2 are real numbers. It is assumed that the value of C1 depends on the element number and was stored as the third real vector parameter for all groups of CLASS=DIM. C2 is a given distribution on the domain and it is defined by its values at the geometrical nodes of the domain. These values constitute the second node parameter set in the main program. In the case of NGROUP=1, MASKF has the following entries:

   MASKF(.,1)=( true , true  )

The following statements have to be entered into userf:

      IF ((COMPV.EQ.1).AND.(CLASS.EQ.DIM)) THEN
        DO 10 Z=1,NELIS
          F1(Z,1)=DUDX(Z,1,1)
          F1(Z,2)=DUDX(Z,1,2)
          F0(Z)  =RVPARM(LAST+Z,3)*U(Z,1)*U(Z,2)
10      CONTINUE
      ENDIF
      IF ((COMPV.EQ.2).AND.(CLASS.EQ.DIM)) THEN
        DO 20 Z=1,NELIS
          F1(Z,1)=DUDX(Z,2,1)
          F1(Z,2)=DUDX(Z,2,2)
          F0(Z)  =NOPARM(Z,2)*U(Z,2)
20      CONTINUE
      ENDIF

 

3rd

This is a typical example for vemp02. The integration kernel for manifold M(2) is

V1X1 * U1X1 + V1X2 * U1X2 + V1 * SIN(X1*C) * U1T*U2T +
 
V2X1 * U2X1 + V2X2 * U2X2 + V2 * COS(U2T)

where C is a real value. It is assumed that the value of C varies over the domain. C equals a constant C1 on a special set of the elements and equals C2 on the remaining elements. The values of C1 and C2 are stored as the first and second real scalar parameter. The first integer vector marks the case C=C1 by 1. The remaining elements get the mark 0. In the case of NGROUP=1, MASKF has the following entries:

   MASKF(.,1)=( true , true  )

The following statements have to be entered into userf:

      IF ((COMPV.EQ.1).AND.(CLASS.EQ.DIM)) THEN
        DO 10 Z=1,NELIS

          IF (IVPARM(LAST+Z,1).EQ.1) THEN
            C=RSPARM(1)
          ELSE
            C=RSPARM(2)
          ENDIF

          F1(Z,1)=DUDX(Z,1,1)
          F1(Z,2)=DUDX(Z,1,2)
          F0(Z)  =SIN(X(Z,1)*C)*UT(Z,1)*UT(Z,2)
	   
10      CONTINUE
      ENDIF
      IF ((COMPV.EQ.2).AND.(CLASS.EQ.DIM)) THEN
        DO 20 Z=1,NELIS
          F1(Z,1)=DUDX(Z,2,1)
          F1(Z,2)=DUDX(Z,2,2)
          F0(Z)  =COS(UT(Z,2))
20      CONTINUE
      ENDIF

Another possibility to distinguish the cases C=C1 and C=C2 is the subdivision of the elements into two groups.

4th

The integration kernel for manifold M(1) is

V2 *C*U1T*U2TAU1

where C is a real value. It is assumed that the value of C depends on the element number and was stored as the third real vector parameter for all groups of CLASS=1. In the case that the elements in group 2 describe the manifold M(1), MASKF has the following entries:

   MASKF(.,2)=( false , true  )

The following statements have to be entered into userf:

      IF ((COMPV.EQ.2).AND.(CLASS.EQ.1)) THEN
        DO 10 Z=1,NELIS
          F0(Z)=RVPARM(LAST+Z,3)*UT(Z,1)*DUDX(Z,2,1)
10      CONTINUE
      ENDIF

The case COMPV=1 and CLASS=1 does not have to be specified.


SEE

VECFEM, mesh, vemexamples, equation, usrfu, userl, veme00, veme02, vemfre, vemp02.


COPYRIGHTS

Copyrights by Universitaet Karlsruhe 1989-1996. Copyrights by Lutz Grosz 1996. All rights reserved. More details see VECFEM.