Google

VECFEM3 Reference Manual: usrfu

Type: FORTRAN routine


NAME

usrfu - subroutine frame for the Frechet derivative of linear form F.


SYNOPSIS

SUBROUTINE USRFU(
T, GROUP, CLASS, COMPV, COMPU, 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, F1UX, F1U, F0UX, F0U)
 
INTEGER
GROUP, CLASS, COMPV, COMPU, 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), F1UX(L,CLASS,CLASS), F1U(L,CLASS), F0UX(L,CLASS), F0U(L)


PURPOSE

usrfu is the subroutine which defines the Frechet derivative of the linear form F with respect to the solution U. For vemp02 the same subroutine frame is used under the name USRFUT to define the Frechet derivative with respect to the time derivative UT of the solution (you have to replace 'with respect to U/DUDX' by 'with respect to UT/DUTDX'). The tool vemfre can be used to check whether your Frechet derivatives are defined correctly.

You have to enter the statements, which define the derivatives of the coefficients in linear form F with respect to U and DUDX into a subroutine with the argument list of usrfu. 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 USRFU (or USRFUT, respectively) into the argument lists of veme02 and vemp02.

By one call the derivatives of coefficients of the component COMPV of the test functions and the manifold M(CLASS) with respect to the component COMPU of the solution have to be set for a set of NELIS points (called stripe), which are in different elements of the group GROUP. Since normally NELIS<>NE, usrfu 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, COMPU, GROUP), usrfu is called if MASKL(COMPV, COMPU, GROUP)=true and NELTYP>0 for component COMPV and component COMPU in group GROUP. In the other case, the coefficients F1UX, F1U, F0UX and F0U are set to zero by the calling program.

The Frechet derivative of F is called symmetrical if for all j1,j2=1,...,CLASS, COMPV,COMPU=1,...,NK and all groups, the derivatives of the coefficients of F satisfy the following conditions:

  F1(.,j1) for COMPV with respect to DUDX(COMPU,j2) =
             F1(.,j2) for COMPU with respect to DUDX(COMPV,j1)

  F1(.,j1) for COMPV with respect to U(COMPU) =
                F0(.) for COMPU with respect to DUDX(COMPV,j1)

  F0(.) for COMPV with respect to U(COMPU) =
                      F0(.) for COMPU with respect to U(COMPV)

The use of the symmetry reduces the CPU time and the storage amount during the solution, so you should carefully check whether your Frechet derivative is symmetrical.


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 derivatives of coefficients have to be set.
COMPU integer, scalar, input
The component of the solution with respect to which the derivatives of the 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
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.
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.
LT integer, scalar, input
Leading dimension, =0 for the calling routines 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. If usrfu is called by veme02, UT is undefined.
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. If usrfu is called by veme02, DUTDX is undefined.
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.
F1UX double precision, array: F1UX(L,CLASS,CLASS), output
Derivative of the coefficients for contributions of the X-derivatives of the test functions with respect to the X-derivative of the solution. F1UX(z,j1,j2) is the DUDX(.,COMPU,j2)-derivative of the coefficient for the contribution of the derivative of the COMPV-th component of the test function with respect to the j1-th space variable/to TAU(z,.,j1) at the point X(z,.). Only non-ero elements of F1UX have to be defined.
F1U double precision, array: F1U(L,CLASS), output
Derivative of the coefficients for contributions of the X-derivatives of the test functions with respect to the solution. F1U(z,j1) is the U(.,COMPU)-derivative of the coefficient for the contribution of the derivative of the COMPV-th component of the test function with respect to the j1-th space variable/to TAU(z,.,j1) at the point X(z,.). Only non-ero elements of F1U have to be defined.
F0UX double precision, array: F0UX(L,CLASS), output
Derivative of the coefficients for contributions of the test functions with respect to the X-derivative of the solution. F0UX(z,j2) is the DUDX(.,COMPU,j2)-derivative of the coefficient for the contribution of the COMPV-th component of the test function at the point X(z,.). Only non-ero elements of F0UX have to be defined.
F0U double precision, array: F0U(L), output
Derivative of the coefficients for contributions of the test functions with respect to the solution. F0U(z) is the U(.,COMPU)-derivative of the coefficient for the contribution of the COMPV-th component of the test function at the point X(z,.). Only non-ero elements of F0U 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 to the time T.

1st Example

This is an example for the application of veme02, see also userf. 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, MASKL has the following entries:
   MASKL(.,.,1)=( true  , true  )
                ( false , true  )
The following statements have to be entered into usrfu and the routine has to be entered into the veme02 call for USRFU:
      IF ((COMPV.EQ.1).AND.(COMPU.EQ.1).AND.(CLASS.EQ.DIM)) THEN
        DO 11 Z=1,NELIS
          F1UX(Z,1,1)=1.
          F1UX(Z,2,2)=1.
          F0U(Z)  =RVPARM(LAST+Z,3)*U(Z,2)
11      CONTINUE
      ENDIF
      IF ((COMPV.EQ.1).AND.(COMPU.EQ.2).AND.(CLASS.EQ.DIM)) THEN
        DO 12 Z=1,NELIS
          F0U(Z)  =RVPARM(LAST+Z,3)*U(Z,1)
12      CONTINUE
      ENDIF

      IF ((COMPV.EQ.2).AND.(COMPU.EQ.2).AND.(CLASS.EQ.DIM)) THEN
        DO 20 Z=1,NELIS
          F1(Z,1)=1.
          F1(Z,2)=1.
          F0U(Z)  =NOPARM(Z,2)
20      CONTINUE
      ENDIF
In the case of C1=0 the Frechet derivative of F is symmetrical.

2nd Example

This is an example for the application of vemp02, see also userf. 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  )
               =( false , true  )
The following statements have to be entered into usrfu and the routine has to be entered into the vemp02 call for USRFU:
      IF ((COMPV.EQ.1).AND.(COMPU.EQ.1).AND.(CLASS.EQ.DIM)) THEN
        DO 11 Z=1,NELIS
          F1UX(Z,1,1)=1.
          F1UX(Z,2,2)=1.
11      CONTINUE
      ENDIF
      IF ((COMPV.EQ.2).AND.(COMPU.EQ.2).AND.(CLASS.EQ.DIM)) THEN
        DO 22 Z=1,NELIS
          F1UX(Z,1,1)=1.
          F1UX(Z,2,2)=1.
22      CONTINUE
      ENDIF
The Frechet derivative of F with respect to U is symmetrical.
The following statements have to be entered into usrfu and the routine has to be entered into the vemp02 call for USRFUT:

      IF ((COMPV.EQ.1).AND.(COMPU.EQ.1).AND.(CLASS.EQ.DIM)) THEN
        DO 11 Z=1,NELIS
          IF (IVPARM(LAST+Z,1).EQ.1) THEN
            C=RSPARM(1)
          ELSE
            C=RSPARM(2)
          ENDIF
          F0UT(Z)  =SIN(X(Z,1)*C)*UT(Z,2)
11      CONTINUE
      ENDIF
      IF ((COMPV.EQ.1).AND.(COMPU.EQ.2).AND.(CLASS.EQ.DIM)) THEN
        DO 12 Z=1,NELIS
          IF (IVPARM(LAST+Z,1).EQ.1) THEN
            C=RSPARM(1)
          ELSE
            C=RSPARM(2)
          ENDIF
          F0UT(Z)  =SIN(X(Z,1)*C)*UT(Z,1)
12      CONTINUE
      ENDIF
      IF ((COMPV.EQ.2).AND.(COMPU.EQ.2).AND.(CLASS.EQ.DIM)) THEN
        DO 22 Z=1,NELIS
          F0UT(Z)  =-SIN(UT(Z,2))
22      CONTINUE
      ENDIF

In the case of C=0, the Frechet derivative of F with respect to UT is symmetrical.


SEE ALSO

VECFEM, mesh, vemexamples, equation, userf, userl, veme02, vemfre, vemp02.


COPYRIGHTS

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