FE-Project
Loading...
Searching...
No Matches
scale_meshutil_cubedsphere3d.F90
Go to the documentation of this file.
1!-------------------------------------------------------------------------------
9!-------------------------------------------------------------------------------
10#include "scaleFElib.h"
12 !-----------------------------------------------------------------------------
13 !
14 !++ used modules
15 !
16 use scale_const, only: &
17 pi => const_pi, &
18 eps => const_eps
19 use scale_precision
20 use scale_prc
21 use scale_io
22 use scale_prc
23
24 use scale_meshutil_3d, only: &
25 meshutilcubedsphere3d_gencubedomain => meshutil3d_gencubedomain, &
26 meshutilcubedsphere3d_genconnectivity => meshutil3d_genconnectivity, &
27 meshutilcubedsphere3d_buildinteriormap => meshutil3d_buildinteriormap, &
28 meshutilcubedsphere3d_genpatchboundarymap => meshutil3d_genpatchboundarymap
29 !-----------------------------------------------------------------------------
30 implicit none
31 private
32
33 !-----------------------------------------------------------------------------
34 !
35 !++ Public procedure
36 !
37 public :: meshutilcubedsphere3d_gencubedomain
38 public :: meshutilcubedsphere3d_genconnectivity
39 public :: meshutilcubedsphere3d_buildinteriormap
41 public :: meshutilcubedsphere3d_genpatchboundarymap
42
43contains
44!OCL SERIAL
46 panelID_table, pi_table, pj_table, pk_table, &
47 tileID_map, tileFaceID_map, tilePanelID_map, &
48 Ntile, &
49 NeZ )
50
51 ! use scale_prc, only: PRC_isMaster
52 use scale_meshutil_3d, only: &
56 implicit none
57
58 integer, intent(in) :: ntile
59 integer, intent(out) :: panelid_table(ntile)
60 integer, intent(out) :: pi_table(ntile)
61 integer, intent(out) :: pj_table(ntile)
62 integer, intent(out) :: pk_table(ntile)
63 integer, intent(out) :: tileid_map(6,ntile)
64 integer, intent(out) :: tilefaceid_map(6,ntile)
65 integer, intent(out) :: tilepanelid_map(6,ntile)
66 integer, intent(in) :: nez
67
68 integer :: ntileperpanel
69 integer :: nex, ney, nvx, nvy, nvz
70 integer, allocatable :: nodesid_3d(:,:,:,:)
71 integer, allocatable :: etov(:,:)
72 integer, allocatable :: etoe(:,:)
73 integer, allocatable :: etof(:,:)
74 integer :: i, j, k, f
75 integer :: panelid
76 integer :: tileid, tileid_r
77 integer :: counter
78
79 integer :: pi_, pj_
80 !-----------------------------------------------------------------------------
81
82 ntileperpanel = ntile / 6
83 ney = int( sqrt(dble(ntileperpanel)) )
84 nex = ntileperpanel/ney
85 nvx = nex + 1
86 nvy = ney + 1
87 nvz = nez + 1
88 allocate( nodesid_3d(nvx,nvy,nvz,6) )
89 allocate( etov(ntile,8), etoe(ntile,6), etof(ntile,6) )
90
91 counter = 0
92 do panelid = 1, 6
93 do k = 1, nvz
94 do j = 1, nvy
95 do i = 1, nvx
96 counter = counter + 1
97 nodesid_3d(i,j,k,panelid) = counter
98 end do
99 end do
100 end do
101 end do
102
103 !----
104
105 tileid = 0
106 do panelid = 1, 6
107 do k = 1, nez
108 do j = 1, ney
109 do i = 1, nex
110 tileid = tileid + 1
111 panelid_table(tileid) = panelid
112 pi_table(tileid) = i; pj_table(tileid) = j; pk_table(tileid) = k
113 etov(tileid,:) = (/ nodesid_3d(i,j ,k ,panelid), nodesid_3d(i+1,j ,k ,panelid), &
114 nodesid_3d(i,j+1,k ,panelid), nodesid_3d(i+1,j+1,k ,panelid), &
115 nodesid_3d(i,j ,k+1,panelid), nodesid_3d(i+1,j ,k+1,panelid), &
116 nodesid_3d(i,j+1,k+1,panelid), nodesid_3d(i+1,j+1,k+1,panelid) /)
117 end do
118 end do
119 end do
120 end do
121
122 call meshutil3d_genconnectivity( etoe, etof, &
123 etov, ntile, 6 )
124 tileid_map(:,:) = transpose(etoe)
125 tilefaceid_map(:,:) = transpose(etof)
126
127 do tileid=1, ntile
128 do f=1, 6
129 tileid_r = tileid_map(f,tileid)
130 tilepanelid_map(f,tileid) = panelid_table(tileid_r)
131 end do
132 end do
133
135 tilepanelid_map, tileid_map, tilefaceid_map, & ! (inout)
136 panelid_table, pi_table, pj_table, nex, ney, ntile, 6 ) ! (in)
137
138 return
140
module FElib / Mesh / utility for 3D mesh
subroutine, public meshutil3d_buildinteriormap(vmapm, vmapp, mapm, mapp, pos_en, pos_ev, etoe, etof, etov, fmask_h, fmask_v, ne, nv, np, nfp_h, nfp_v, nfptot, nfaces_h, nfaces_v, nfaces)
subroutine, public meshutil3d_genconnectivity(etoe, etof, etov, ne, nfaces)
subroutine, public meshutil3d_gencubedomain(pos_v, etov, ke_x, xmin, xmax, ke_y, ymin, ymax, ke_z, zmin, zmax, fz)
subroutine, public meshutil3d_genpatchboundarymap(vmapb, mapb, vmapp, pos_en, xmin, xmax, ymin, ymax, zmin, zmax, fmask_h, fmask_v, ne, nv, np, nfp_h, nfp_v, nfptot, nfaces_h, nfaces_v, nfaces)
module FElib / Mesh / utility for 2D cubed-sphere mesh
subroutine, public meshutilcubedsphere2d_modifyconnectivity(tilepanelid_map, tileid_map, tilefaceid_map, panelid_table, pi_table, pj_table, nex, ney, ntile, nface)
module FElib / Mesh / utility for 3D cubed-sphere mesh
subroutine, public meshutilcubedsphere3d_buildglobalmap(panelid_table, pi_table, pj_table, pk_table, tileid_map, tilefaceid_map, tilepanelid_map, ntile, nez)