6 real(DP),
allocatable,
target,
dimension(:,:,:,:) :: xm1, ym1, zm1
7 real(DP),
pointer,
dimension(:,:,:,:) :: xm2, ym2, zm2
9 real(DP),
allocatable :: jacmi (:,:,:,:)
11 real(DP),
allocatable,
target,
dimension(:,:,:,:) :: &
12 rxm1, sxm1, txm1, rym1, sym1, tym1, rzm1, szm1, tzm1, jacm1
13 real(DP),
pointer,
dimension(:,:,:,:) :: &
14 rxm2, sxm2, txm2, rym2, sym2, tym2, rzm2, szm2, tzm2, jacm2
16 real(DP),
allocatable :: rx(:,:,:) !>
18 real(DP),
allocatable,
dimension(:,:,:,:) :: &
19 g1m1, g2m1, g3m1, g4m1, g5m1, g6m1
21 real(DP),
allocatable,
dimension(:,:,:,:) :: &
26 real(DP),
allocatable,
dimension(:,:,:,:) :: &
27 vnx, vny, vnz, v1x, v1y, v1z, v2x, v2y, v2z
29 real(DP),
allocatable,
target :: bm1(:,:,:,:)
30 real(DP),
pointer :: bm2(:,:,:,:)
32 real(DP),
allocatable,
dimension(:,:,:,:) :: &
33 binvm1, bintm1, bm2inv, baxm1, yinvm1
35 real(DP),
allocatable :: bm1lag(:,:,:,:,:)
37 real(DP) :: volvm1,volvm2,voltm1,voltm2
39 logical :: ifgeom,ifgmsh3,ifvcor,ifsurt,ifmelt,ifwcno, ifbcor
40 logical,
allocatable :: ifrzer(:), ifqinp(:,:), ifeppm(:,:)
41 logical,
allocatable :: iflmsf(:), iflmse(:), iflmsc(:)
42 logical,
allocatable :: ifmsfc(:,:,:), ifmseg(:,:,:),ifmscr(:,:,:)
43 logical,
allocatable :: ifnskp(:,:)
45 logical :: bm1_compress !>
51 use mesh, only : if_ortho
54 allocate( xm1(lx1,ly1,lz1,lelt), ym1(lx1,ly1,lz1,lelt), zm1(lx1,ly1,lz1,lelt) )
58 allocate(rx(lxd*lyd*lzd,ldim,lelv))
59 allocate(sxm1(lx1,ly1,lz1,1), txm1(lx1,ly1,lz1,1) &
60 , rym1(lx1,ly1,lz1,1), tym1(lx1,ly1,lz1,1) &
61 , rzm1(lx1,ly1,lz1,1), szm1(lx1,ly1,lz1,1) )
63 allocate(rx(lxd*lyd*lzd,ldim*ldim,lelv))
64 allocate(sxm1(lx1,ly1,lz1,lelt), txm1(lx1,ly1,lz1,lelt) &
65 , rym1(lx1,ly1,lz1,lelt), tym1(lx1,ly1,lz1,lelt) &
66 , rzm1(lx1,ly1,lz1,lelt), szm1(lx1,ly1,lz1,lelt) )
68 allocate( rxm1(lx1,ly1,lz1,lelt), sym1(lx1,ly1,lz1,lelt), tzm1(lx1,ly1,lz1,lelt) )
69 allocate( jacm1(lx1,ly1,lz1,lelt), jacmi(lx1,ly1,lz1,lelt) )
71 allocate( g1m1(lx1,ly1,lz1,lelt), g2m1(lx1,ly1,lz1,lelt), g3m1(lx1,ly1,lz1,lelt) &
72 , g4m1(lx1,ly1,lz1,lelt), g5m1(lx1,ly1,lz1,lelt), g6m1(lx1,ly1,lz1,lelt) )
75 allocate( unx(lx1,lz1,6,lelt), uny(lx1,lz1,6,lelt), unz(lx1,lz1,6,lelt) )
76 allocate( area(lx1,lz1,6,lelt) )
79 ifrzer(lelt),ifqinp(6,lelv),ifeppm(6,lelv) &
80 ,iflmsf(0:1),iflmse(0:1),iflmsc(0:1) &
82 ,ifmseg(12,lelt,0:1) &
87 allocate( bm1(lx1,ly1,lz1,lelt), binvm1(lx1,ly1,lz1,lelv) )
93 subroutine compress_geom()
94 use size_m
, only : lx1,ly1,lz1,nelt, nid
97 integer,
parameter :: lxyz = lx1*ly1*lz1
99 real(DP),
external :: dnrm2
102 bm1_compress = .true.
103 thresh = 1.d-4 * dnrm2(lxyz*nelt, bm1, 1) / nelt
106 if (dnrm2(lxyz,bm1(:,:,:,ie) - bm1(:,:,:,ie-1),1) > thresh)
then
107 bm1_compress = .false.
109 write(*,*) bm1(:,1,1,ie)
110 write(*,*) bm1(:,1,1,ie-1)
114 write(*,*)
"MAX: bm1_compress =", bm1_compress
116 end subroutine compress_geom