source: trunk/00FlowSolve_KW/src/class/ClassSpaceDimension.f90.bk @ 6

Last change on this file since 6 was 6, checked in by xlvlod, 17 years ago

import initial from SVN_BASE_TRUNK

File size: 4.0 KB
Line 
1Module class_SpaceDimension
2!!=====================================================
3!!=====================================================
4!! A SpaceDimension is simply a CoordinateMap
5!! combined with a spatial index 1,2 or 3.
6!! Recall...
7!! Coordinate maps describe the sampling distribution
8!! associated with a coordinate.
9!!
10!! Notation: coordinate x is parameterized via s,
11!! i.e. x=x(s). The discrete arrays [x] [s] and [dxds]
12!! define the mapping. Particular maps are specified 
13!! via their "label". Some maps require parameters,
14!! which are specified via the 2 vector params.
15!!
16!! Currently implemented maps:
17!!        unit, identity, cheby, periodic
18!!=====================================================
19!!=====================================================
20 use class_CoordinateMap
21 implicit none
22 public  :: Map2SpaceDimension
23 public  :: DeleteSpaceDimension
24 public  :: DescribeSpaceDimension
25 !public  :: MergeDimensions
26 
27 type SpaceDimension 
28  integer                    :: DirIndex
29  type( CoordinateMap )      :: map
30 end type SpaceDimension
31 
32 interface assignment (=)
33  module procedure EqualSpaceDimensions
34 end interface
35 
36Contains     
37 
38  subroutine Map2SpaceDimension(map,id,spacedim)   
39   use class_CoordinateMap
40   implicit none 
41   type( CoordinateMap ),intent(in)       :: map
42   type( SpaceDimension ),intent(inout)   :: spacedim
43   integer                                :: id
44   spacedim%DirIndex=id !! i.e. 1,2 or 3   
45   spacedim%map = map   
46  end subroutine Map2SpaceDimension
47 
48 
49 
50 
51  subroutine DeleteSpaceDimension(dim)
52   use class_CoordinateMap
53   type( SpaceDimension )  :: dim
54   call DeleteCoordinateMap( dim%map )  !!DeleteCoordinateMap checks allocation first
55  end subroutine DeleteSpaceDimension
56   
57   
58   
59   
60  subroutine EqualSpaceDimensions(new,old)
61   use class_CoordinateMap
62   type( SpaceDimension ),intent(inout) :: new
63   type( SpaceDimension ),intent(in)    :: old
64   new%map = NewCoordinateMap(old%map%npts,       &
65                              old%map%label,      &
66                              old%map%x,          &
67                              old%map%s,          &
68                              old%map%dxds,       &
69                              old%map%d2xds2 )
70   new%DirIndex = old%DirIndex
71  end subroutine EqualSpaceDimensions
72
73
74 
75
76 
77!  function MergeDimensions(xdim,ydim,zdim) result(AllSpaceDims)
78!   type( SpaceDimension ),intent(in)   :: xdim
79!   type( SpaceDimension ),intent(in)   :: ydim
80!   type( SpaceDimension ),intent(in)   :: zdim
81!   type( SpaceDimension )   :: AllSpaceDims(3)
82!    !! type SpaceDimension has an overloaded assignment operator
83!     AllSpaceDims(1) = xdim
84!     AllSpaceDims(2) = ydim
85!     AllSpaceDims(3) = zdim   
86!  end function MergeDimensions
87   
88 
89  subroutine DescribeSpaceDimension(dim,docfile)
90   use class_CoordinateMap
91   implicit none
92   type( SpaceDimension ), intent(in):: dim
93   character (len=80 )               :: coordlabel
94   character (len=80 )               :: coordname
95   character (len=80 )               :: docfile
96   integer                           :: myid
97   integer                           :: ierr
98   include 'mpif.h'
99   
100   call mpi_comm_rank(MPI_COMM_WORLD,myid,ierr)
101   
102   select case( dim%DirIndex )
103    case(1)
104     coordlabel='x  (or x1 or xsi), parameterized by s -----> x(s)'
105     coordname=' x '
106    case(2)
107     coordlabel='y  (or y1 or eta), parameterized by s -----> y(s)'
108     coordname=' y '
109    case(3)
110     coordlabel='z  (or z1 or zeta), parameterized by s -----> z(s)'
111     coordname=' z '
112   end select
113   
114   if(myid==0) then
115    open(1,file=docfile,position='append')
116    write(1,*) ' '
117    write(1,*) '============================================================'
118    write(1,*) 'SpaceDimension  ',dim%DirIndex
119    write(1,*)  trim(coordlabel)   
120    call DescribeCoordinateMap(dim%map,coordname,docfile,myid)
121    write(1,*) '  '
122    close(1)
123   endif
124  end subroutine DescribeSpaceDimension
125   
126end Module class_SpaceDimension !============================================
Note: See TracBrowser for help on using the repository browser.