Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
HeatLoad_Hex.f90
Go to the documentation of this file.
1 
2 !!****
3 !!
4 !! NAME
5 !! HeatLoad_Hex
6 !!
7 !! FUNCTION
8 !! This subroutine takes a heat flux (InterfaceHeatFlux)(W/m2) and divides it amoung the
9 !! nodes associated with the interface patch.
10 !!
11 !! INPUTS
12 !! coor -- Coordinates of the nodes
13 !! ElConnVol -- The connectivity table
14 !! dmat -- Material stiffness matrix
15 !! numnp -- Number of nodes
16 !! NumEl -- Number of elements
17 !! MatType -- Mapping of materials to elements
18 !! NumMatType -- Total number of materials
19 !!
20 !! OUTPUTS
21 !! none
22 !!
23 !! USES
24 !! none
25 !!
26 !!****
27 
28 SUBROUTINE heatload_hex(Q_ex, numnp, InterfaceHeatFlux, InterfaceNumElems, InterfaceNumNodes, &
29  interfaceelemconn, mapnode, lwrbnd, uppbnd, coor)
30 
31  IMPLICIT NONE
32 
33  INTEGER :: lwrbnd,uppbnd
34 
35  INTEGER :: interfacenumelems,interfacenumnodes
36  INTEGER, DIMENSION(1:UppBnd,1:InterfaceNumElems) :: interfaceelemconn
37  INTEGER, DIMENSION(1:InterfaceNumNodes) :: mapnode
38  REAL*8, DIMENSION(1:InterfaceNumElems) :: interfaceheatflux
39 
40  INTEGER :: numnp ! number of nodes
41 
42  REAL*8, DIMENSION(1:numnp) :: q_ex ! external force
43 
44  INTEGER :: nx, ny, nz
45  INTEGER :: i,j
46 
47  INTEGER,DIMENSION(1:4) :: conn2d
48  real*8 :: qmag
49  REAL*8 :: elemarea
50 
51  ! ... mesh coordinates
52  REAL*8, DIMENSION(1:3,1:numnp) :: coor
53 
54  REAL*8, DIMENSION(1:3) :: veca, vecb, outwd_surface_normal, &
55  half_normal_veca, half_normal_vecb
56 
57  DO i = 1, interfacenumelems
58 
59  ! ... Nodes of the Quad ( Vertex Nodes ). Gives surface node numbers,
60  ! ... not global node numbers
61  conn2d(1:4) = interfaceelemconn(1:4,i)
62 
63  ! ... Uses the fact that the norm of the cross product vector
64  ! ... is the area of the parallelogram they form. The triangle they
65  ! ... form has half that area.
66 
67  ! ... Vector between element interface surface nodes 2 and 1
68  veca(1:3) = coor(1:3,mapnode(conn2d(2)))- coor(1:3,mapnode(conn2d(1)))
69  ! ... Vector between element interface surface nodes 2 and 1
70  vecb(1:3) = coor(1:3,mapnode(conn2d(4)))- coor(1:3,mapnode(conn2d(1)))
71 
72  ! ... The norm of the vector 'half_normal_veca' is the area of the parallelogram
73  ! ... formed by element interface surface nodes 2-1-4.
74  half_normal_veca(1) = veca(2)*vecb(3) - vecb(2)*veca(3)
75  half_normal_veca(2) = veca(3)*vecb(1) - vecb(3)*veca(1)
76  half_normal_veca(3) = veca(1)*vecb(2) - vecb(1)*veca(2)
77 
78  ! ... Vector between element interface surface nodes 4 and 3
79  veca(1:3) = coor(1:3,mapnode(conn2d(4))) - coor(1:3,mapnode(conn2d(3)))
80  ! ... Vector between element interface surface nodes 2 and 3
81  vecb(1:3) = coor(1:3,mapnode(conn2d(2))) - coor(1:3,mapnode(conn2d(3)))
82 
83  ! ... The norm of the vector 'half_normal_vecb' is the area of the parallelogram
84  ! ... formed by element interface surface nodes 2-3-4.
85  half_normal_vecb(1) = veca(2)*vecb(3) - vecb(2)*veca(3)
86  half_normal_vecb(2) = veca(3)*vecb(1) - vecb(3)*veca(1)
87  half_normal_vecb(3) = veca(1)*vecb(2) - vecb(1)*veca(2)
88 
89  ! ... Outward surface normal is a vector normal to the element
90  ! ... interface surface with magnitude of
91  ! ... 2*(element interface surface area)
92  outwd_surface_normal = half_normal_veca + half_normal_vecb
93 
94  ! ... Element interface area
95  elemarea = 0.0d0
96  do j = 1,3
97  elemarea = elemarea + outwd_surface_normal(j) * outwd_surface_normal(j)
98  end do
99  elemarea = sqrt(elemarea) * 0.50d0
100 
101  ! ... qmag is the heat flux/(2*(element interface surface area)) magnitude into
102  ! ... each of the four nodes on the element interface surface.
103  ! ... Note: multiplied by factor of two contained in outward_surface_normal below.
104  qmag = interfaceheatflux(i)*0.250d0
105  qmag = qmag * elemarea
106 
107  ! ... Assembly into global external load vector Q_ex
108  ! ... InterfaceElemConn contains interface surface
109  ! ... node numbers corresponding to element i.
110  ! ... (Not global element i, surface element i)
111  conn2d(1:4) = interfaceelemconn(lwrbnd:uppbnd,i)
112 
113  ! ... MapNode gives the global node number of a given surface
114  ! ... node number j.
115  DO j = 1, 4
116  q_ex(mapnode(conn2d(j))) = q_ex(mapnode(conn2d(j))) + qmag
117  ENDDO
118  ENDDO
119 
120  RETURN
121 END SUBROUTINE heatload_hex
double sqrt(double d)
Definition: double.h:73
blockLoc i
Definition: read.cpp:79
j indices j
Definition: Indexing.h:6
subroutine heatload_hex(Q_ex, numnp, InterfaceHeatFlux, InterfaceNumElems, InterfaceNumNodes, InterfaceElemConn, MapNode, LwrBnd, UppBnd, coor)