Merge lp:~mapdes/fluidity/firedrake-extrusion into lp:fluidity/firedrake

Proposed by Doru Bercea
Status: Merged
Merged at revision: 4329
Proposed branch: lp:~mapdes/fluidity/firedrake-extrusion
Merge into: lp:fluidity/firedrake
Diff against target: 2161 lines (+1502/-97)
42 files modified
femtools/Fields_Allocates.F90 (+7/-3)
femtools/Global_Numbering.F90 (+31/-17)
femtools/Python_Interface_f.F90 (+38/-3)
python/firedrake/core_types.pyx (+365/-35)
python/firedrake/fluidity_types.pxd (+1/-0)
python/firedrake/io.py (+71/-32)
python/firedrake/mesh.py (+0/-2)
python/firedrake/solving.py (+15/-2)
tests/firedrake_extrusion_assemble_p0/Makefile (+5/-0)
tests/firedrake_extrusion_assemble_p0/firedrake_assemble_p0.xml (+19/-0)
tests/firedrake_extrusion_assemble_p0/test_firedrake_assemble_p0.py (+88/-0)
tests/firedrake_extrusion_assembly/Makefile (+5/-0)
tests/firedrake_extrusion_assembly/firedrake_assembly.xml (+22/-0)
tests/firedrake_extrusion_assembly/test_firedrake_assembly.py (+57/-0)
tests/firedrake_extrusion_helmholtz/Makefile (+5/-0)
tests/firedrake_extrusion_helmholtz/test_firedrake_extrusion_helmholtz.py (+59/-0)
tests/firedrake_extrusion_identity/Makefile (+5/-0)
tests/firedrake_extrusion_identity/firedrake_extrusion.xml (+22/-0)
tests/firedrake_extrusion_identity/test_firedrake_extrusion.py (+58/-0)
tests/firedrake_extrusion_lsw/Makefile (+5/-0)
tests/firedrake_extrusion_lsw/firedrake_extrusion_lsw.xml (+19/-0)
tests/firedrake_extrusion_lsw/test_firedrake_extrusion_lsw.py (+77/-0)
tests/firedrake_extrusion_p0/Makefile (+5/-0)
tests/firedrake_extrusion_p0/firedrake_p0.xml (+19/-0)
tests/firedrake_extrusion_p0/test_firedrake_p0.py (+72/-0)
tests/firedrake_extrusion_project/Makefile (+5/-0)
tests/firedrake_extrusion_project/test_firedrake_extrusion_project.py (+45/-0)
tests/firedrake_extrusion_rhs/Makefile (+5/-0)
tests/firedrake_extrusion_rhs/firedrake_rhs.xml (+19/-0)
tests/firedrake_extrusion_rhs/test_firedrake_rhs.py (+62/-0)
tests/firedrake_extrusion_two_step/Makefile (+5/-0)
tests/firedrake_extrusion_two_step/firedrake_extrusion_two_step.xml (+19/-0)
tests/firedrake_extrusion_two_step/test_firedrake_extrusion_two_step.py (+84/-0)
tests/firedrake_extrusion_unit_cube/Makefile (+5/-0)
tests/firedrake_extrusion_unit_cube/firedrake_unit_cube.xml (+19/-0)
tests/firedrake_extrusion_unit_cube/test_firedrake_unit_cube.py (+64/-0)
tests/firedrake_extrusion_var_p0/Makefile (+5/-0)
tests/firedrake_extrusion_var_p0/firedrake_var_p0.xml (+19/-0)
tests/firedrake_extrusion_var_p0/test_firedrake_var_p0.py (+74/-0)
tests/firedrake_identity/firedrake_identity.xml (+1/-1)
tests/firedrake_identity/test_firedrake_identity.py (+0/-1)
tests/firedrake_identity_parallel/firedrake_identity_parallel.xml (+1/-1)
To merge this branch: bzr merge lp:~mapdes/fluidity/firedrake-extrusion
Reviewer Review Type Date Requested Status
Florian Rathgeber Approve
Lawrence Mitchell Approve
Review via email: mp+187998@code.launchpad.net

Description of the change

Adding etruded mesh handling in Firedrake. Changing the global numbering to handle columns of elements and introducing a new Mesh subclass, ExtrudedMesh, to handle the creation of an extruded mesh as a Lagrange 1 function space.
Tests have been introduced to cover: matrix and RHS assembly, unit cube integration with various function space types and extruded helmoltz.
Functionality to output extruded meshes that can be visualized in Paraview has also been introduced.

To post a comment you must log in.
Revision history for this message
David Ham (david-ham) wrote :

Is there a reason why the new tests use gmsh files for unit squares rather than the intrinsic function?

Revision history for this message
Lawrence Mitchell (wence) wrote :

On the Fortran side:

Why do you add a check for lshape%type /= -666 in make_mesh?

In make_global_numbering_new:

extrusion is a logical and should be declared as such:

logical :: extrusion

extrusion = .true. etc...

Why introduce dofs_per_stack? What was wrong with dofs_per. They're the same shape are they not? If not, I don't see how things work.

In topology_dofs: Remove the debugging (commented out) dof_old and halo_dof_old stuff, unless it's supposed to actually do something.

Is it clear why we don't use mesh%nodes = total_dofs in both extruded and unextruded cases? It seems to me like they should be the same.

In the python code:

The magic here is horribly underdocumented. A description of the shape of the key datastructures in comments will be very useful if anyone else is to ever have a chance of fixing any bugs.

is it clear why you insist on building fixed-length lists which you then immediately convert into numpy arrays? numpy.zeros(size, dtype=foo) is much better than numpy.array([0]*size, dtype=foo).

Since the ExtrudedMesh class inherits from Mesh it shouldn't have to reimplement all the superclass methods except in the cases where they are different. Why does it? It's imperative to document what the extrusion kernel does, and so on.

Why does fiat_element_from_ufl_element no longer take a ufl_cell as an argument?

Just because FunctionSpace was underdocumented before, adding new functionality is a perfect time to add a docstring. Also, I think it should be an error to pass in vfamily as well as family if the mesh is not an extruded mesh, just for error checking.

Why is the degree now optional? I thought that family was just a string so it can't contain any extra information. But it seems like the extruded case the family is not a string. This /definitely/ needs documenting. I guess the family is now a cross of function spaces? In any case, there's now no error checking if the degree is not passed in an you've asked for a normal function space. So you need to fix that.

op2.Set instantiation does the right thing if layers is passed as None (it sets layers to 1 internally). So there's no need to do that again before Set instantiation.

Python has a != operator, so can you write foo != bar rather than not (foo == bar)?

Function output in the extruded case looks like it's going to be hideously bad, I note that you comment this. Maybe splat a big warning to the screen for now too?

Test directories should be named firedrake_foo with the test python file named test_firedrake_foo.py (so that we can import more than one test in the same python interpreter). As dham says, don't put mesh files in, use the builtin mesh generation routines.

In the tests, why do you return values as strings? Is it for floating point comparison purposes? If so, don't do that, use numpy.allclose. If not, why?

Why are the tolerances on some existing tests altered?

The helmholtz test comments don't match the code. Also, it doesn't actually /test/ anything. Is it a demo?

review: Needs Fixing
4281. By Doru Bercea

Fixes to Fortran and Python. New LSW test.

4282. By Doru Bercea

Name fix.

4283. By Doru Bercea

Changes made to fortran and python. Tests renamed and GMSH removed.

4284. By Doru Bercea

Two step test added for extrusion.

4285. By Doru Bercea

Tests changed and renamed properly.

4286. By Lawrence Mitchell

Merge from firedrake trunk

4287. By Lawrence Mitchell

Describe why -666 is a magic number when checking mesh continuity

4288. By Lawrence Mitchell

Remove dead commented code

4289. By Lawrence Mitchell

Add docstrings for extrusion functions

4290. By Lawrence Mitchell

Document make_extruded_coords better

4291. By Lawrence Mitchell

Clean up make_extruded_coords a little

Don't build lists only to turn them into numpy arrays.

4292. By Lawrence Mitchell

Document ExtrudedMesh better

4293. By Lawrence Mitchell

Use public API to get a numpy array data pointer

4294. By Lawrence Mitchell

Remove duplicate layers property from ExtrudedMesh

4295. By Lawrence Mitchell

Document FunctionSpace better

Describe the different methods of getting an extruded function space
as well as a normal function space, and raise errors if the arguments
mismatch in some way.

4296. By Lawrence Mitchell

Put back insertion of tensor into mat_cache

4297. By Lawrence Mitchell

Whitespace fixup

4298. By Lawrence Mitchell

Extruded LSW test doesn't test anything so mark it as special

4299. By Lawrence Mitchell

Rename more tests appropriately

4300. By Lawrence Mitchell

And final test rename fix

Revision history for this message
Lawrence Mitchell (wence) wrote :

I'm now happy with this, but it would be nice to have another pair of eyes.

However, it can't land until all the other bits are in place, which will necessitate kicking Andrew into shape. In particular, all the extrusion tests fail if you have the wrong ffc/ufl/fiat setup, and with the right setup for that, the facet integrals test fails (because of a change Andrew has made in ffc).

review: Approve
Revision history for this message
Florian Rathgeber (florian-rathgeber) wrote :

I think this is looking good now.

review: Approve
4301. By Florian Rathgeber

Merge Firedrake trunk

4302. By Florian Rathgeber

Fix typo in ufl.OuterProductElement

4303. By Florian Rathgeber

Mark extrusion firedrake tests as such

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'femtools/Fields_Allocates.F90'
2--- femtools/Fields_Allocates.F90 2013-09-18 14:33:36 +0000
3+++ femtools/Fields_Allocates.F90 2013-10-03 16:15:40 +0000
4@@ -989,7 +989,7 @@
5
6 end function wrap_tensor_field
7
8- function make_mesh (model, shape, continuity, name, with_faces) &
9+ function make_mesh (model, shape, continuity, name, with_faces, dofs_per_column) &
10 result (mesh)
11 !!< Produce a mesh based on an old mesh but with a different shape and/or continuity.
12 type(mesh_type) :: mesh
13@@ -999,6 +999,7 @@
14 integer, intent(in), optional :: continuity
15 character(len=*), intent(in), optional :: name
16 logical, intent(in), optional :: with_faces
17+ integer, dimension(0:), intent(in), optional :: dofs_per_column
18
19 integer, dimension(:), allocatable :: ndglno
20 real, dimension(:), pointer :: val
21@@ -1043,8 +1044,10 @@
22 mesh%periodic=model%periodic
23
24 ! You can't have a CG degree 0 mesh!
25+ ! Fluidity doesn't know about outer product elements (lshape%type
26+ ! == -666) so complain.
27 if(mesh%shape%degree==0.and.mesh%continuity>=0.and.mesh%shape&
28- &%type/=ELEMENT_TRACE) then
29+ &%type/=ELEMENT_TRACE.and.lshape%type/=-666) then
30 FLExit("For a P0 mesh, the 'mesh_continuity' must be Discontinuous.")
31 end if
32
33@@ -1054,7 +1057,8 @@
34 end if
35
36 mesh%element_classes = model%element_classes
37- call make_global_numbering_new(mesh)
38+
39+ call make_global_numbering_new(mesh, dofs_per_column=dofs_per_column)
40
41 if (associated(model%element_halos)) then
42 assert(element_halo_count(model) > 0)
43
44=== modified file 'femtools/Global_Numbering.F90'
45--- femtools/Global_Numbering.F90 2013-08-06 12:52:44 +0000
46+++ femtools/Global_Numbering.F90 2013-10-03 16:15:40 +0000
47@@ -56,10 +56,11 @@
48
49 contains
50
51- subroutine make_global_numbering_new(mesh)
52+ subroutine make_global_numbering_new(mesh, dofs_per_column)
53 ! Construct a new global numbering for mesh using the ordering from
54 ! topology.
55 type(mesh_type), intent(inout), target :: mesh
56+ integer, intent(in), dimension(0:), optional :: dofs_per_column
57
58 type(csr_sparsity) :: facet_list, edge_list
59 type(csr_matrix) :: facet_numbers, edge_numbers
60@@ -70,7 +71,8 @@
61 ! The universal identifier. Required for parallel.
62 type(scalar_field), pointer :: uid
63 integer :: max_vertices, total_dofs, start, finish, d
64- logical :: have_facets, have_halos
65+ logical :: have_facets, have_halos, extrusion
66+ integer, dimension(0:mesh_dim(mesh)) :: dofs_per_stack
67
68 type(integer_set), dimension(:,:), allocatable :: entity_send_targets
69 integer, dimension(:), allocatable :: entity_owner
70@@ -127,6 +129,15 @@
71 ! Extract halo information for each topological entity.
72 call create_topology_halos
73
74+ ! In the case of extruded meshes change the numbering
75+ if (present(dofs_per_column)) then
76+ extrusion=.True.
77+ dofs_per_stack=dofs_per_column
78+ else
79+ extrusion=.False.
80+ dofs_per_stack=dofs_per
81+ end if
82+
83 ! Save core/non-core/l1/l2 distinction in mesh node_classes
84 if (have_halos) then
85
86@@ -137,18 +148,18 @@
87 finish = finish + entity_counts(d)
88 ! Count core nodes (primary sort key -2)
89 mesh%node_classes(CORE_ENTITY) = mesh%node_classes(CORE_ENTITY) + &
90- & count(entity_sort_list(start:finish, 0) == -2)*dofs_per(d)
91+ & count(entity_sort_list(start:finish, 0) == -2)*dofs_per_stack(d)
92 ! Count non-core nodes (primary sort key -1)
93 mesh%node_classes(NON_CORE_ENTITY) = &
94 & mesh%node_classes(NON_CORE_ENTITY) + &
95- & count(entity_sort_list(start:finish, 0) == -1)*dofs_per(d)
96+ & count(entity_sort_list(start:finish, 0) == -1)*dofs_per_stack(d)
97 ! L1 halo (primary sort key \in [0, COMM_SIZE])
98 mesh%node_classes(EXEC_HALO_ENTITY) = mesh%node_classes(EXEC_HALO_ENTITY) + &
99 & count(entity_sort_list(start:finish, 0) >= 0 .and. &
100- & entity_sort_list(start:finish, 0) <= getnprocs())*dofs_per(d)
101+ & entity_sort_list(start:finish, 0) <= getnprocs())*dofs_per_stack(d)
102 ! L2 halo (primary sort key \in [COMM_SIZE + 1, \infty))
103 mesh%node_classes(NON_EXEC_HALO_ENTITY) = mesh%node_classes(NON_EXEC_HALO_ENTITY) + &
104- & count(entity_sort_list(start:finish, 0) > getnprocs())*dofs_per(d)
105+ & count(entity_sort_list(start:finish, 0) > getnprocs())*dofs_per_stack(d)
106 end do
107 end if
108
109@@ -514,10 +525,10 @@
110 halo_dof=0
111 do i=1,size(visit_order)
112 entity_dof_starts(visit_order(i))=dof
113- dof=dof+dofs_per(entity_dim(visit_order(i)))
114+ dof=dof+dofs_per_stack(entity_dim(visit_order(i)))
115
116 halo_entity_dof_starts(halo_visit_order(i))=halo_dof
117- halo_dof=halo_dof+dofs_per(entity_dim(halo_visit_order(i)))
118+ halo_dof=halo_dof+dofs_per_stack(entity_dim(halo_visit_order(i)))
119 end do
120
121 assert(halo_dof == dof)
122@@ -582,8 +593,8 @@
123 ele_dofs(element%entity2dofs(d,e)%dofs)=&
124 entity_dofs(d, entity, dofs_per)
125
126- dof_to_halo_dof(entity_dofs(d, entity, dofs_per)) &
127- = halo_entity_dofs(d, entity, dofs_per)
128+ dof_to_halo_dof(entity_dofs(d, entity, dofs_per_stack)) &
129+ = halo_entity_dofs(d, entity, dofs_per_stack)
130
131 end do
132 end do
133@@ -594,12 +605,15 @@
134
135 assert(all(dof_to_halo_dof>0))
136
137- if (size(mesh%ndglno)>0) then
138- mesh%nodes=maxval(mesh%ndglno)
139+ if (extrusion) then
140+ mesh%nodes=total_dofs
141 else
142- mesh%nodes=0
143+ if (size(mesh%ndglno)>0) then
144+ mesh%nodes=maxval(mesh%ndglno)
145+ else
146+ mesh%nodes=0
147+ end if
148 end if
149-
150 end subroutine populate_ndglno
151
152 subroutine create_halos(mesh, thalos)
153@@ -630,7 +644,7 @@
154
155 if (entity_owner(entity)==rank) then
156 ! One of ours
157- local_dofs=local_dofs+dofs_per(entity_dim(entity))
158+ local_dofs=local_dofs+dofs_per_stack(entity_dim(entity))
159
160 do h=1,size(mesh%halos)
161 do k=1,key_count(entity_send_targets(entity,h))
162@@ -638,7 +652,7 @@
163 if (fetch(entity_send_targets(entity,h),k)==rank) cycle
164
165 call insert(sends(h,fetch(entity_send_targets(entity,h),k)),&
166- & entity_dofs(entity_dim(entity),entity, dofs_per))
167+ & entity_dofs(entity_dim(entity),entity, dofs_per_stack))
168
169 end do
170 end do
171@@ -651,7 +665,7 @@
172 do h=size(mesh%halos),entity_receive_level(entity),-1
173
174 call insert(receives(h,entity_owner(entity)),&
175- entity_dofs(entity_dim(entity),entity, dofs_per))
176+ entity_dofs(entity_dim(entity),entity, dofs_per_stack))
177
178 end do
179 end if
180
181=== modified file 'femtools/Python_Interface_f.F90'
182--- femtools/Python_Interface_f.F90 2013-09-19 12:59:14 +0000
183+++ femtools/Python_Interface_f.F90 2013-10-03 16:15:40 +0000
184@@ -197,17 +197,52 @@
185 end subroutine populate_facet_maps
186
187 end function function_space_f
188-
189+
190+ function extruded_mesh_f(mesh_ptr, fiat_element, dofs_per_column_ptr) bind (c)
191+ type(c_ptr), value, intent(in) :: mesh_ptr
192+ type(element_t) :: fiat_element
193+ type(function_space_t) :: extruded_mesh_f
194+
195+ type(mesh_type), pointer :: mesh, fluidity_function_space
196+ type(element_type) :: element
197+ type(c_ptr), intent(in), value :: dofs_per_column_ptr
198+ integer, dimension(:), pointer:: dofs_per_column
199+
200+ call c_f_pointer(mesh_ptr, mesh)
201+
202+ allocate(fluidity_function_space)
203+
204+ element = make_element_shape_from_fiat(fiat_element)
205+
206+ call c_f_pointer(dofs_per_column_ptr, dofs_per_column, [element%dim+1])
207+
208+ fluidity_function_space = make_mesh(mesh, element, dofs_per_column=dofs_per_column, with_faces=.false.)
209+
210+ extruded_mesh_f%fluidity_mesh = c_loc(fluidity_function_space)
211+
212+ extruded_mesh_f%element_dof_list = fluidity_function_space%ndglno_c
213+
214+ extruded_mesh_f%element_count = fluidity_function_space%elements
215+
216+ extruded_mesh_f%dof_count = fluidity_function_space%nodes
217+
218+ extruded_mesh_f%dof_classes = c_loc(fluidity_function_space%node_classes)
219+
220+ end function extruded_mesh_f
221+
222+
223 function halo_f(mesh_ptr, halo_entity_type) bind(c)
224 type(c_ptr), value, intent(in) :: mesh_ptr
225+
226 integer(c_int), value, intent(in) :: halo_entity_type
227 type(halo_t) :: halo_f
228 type(mesh_type), pointer :: mesh
229 type(halo_type), pointer :: halo => null()
230 integer :: i
231 integer, dimension(:), pointer :: tmp
232+
233 call c_f_pointer(mesh_ptr, mesh)
234-
235+
236 select case (halo_entity_type)
237 case (VERTEX)
238 if (associated(mesh%halos)) then
239@@ -412,7 +447,7 @@
240 integer :: d, e, f, dof
241 integer, allocatable :: count(:,:)
242 integer, pointer :: dofs_per(:), entity_dofs(:,:)
243-
244+
245 element%cell => find_cell(fiat_element%dimension, fiat_element%vertices)
246
247 element%dim = fiat_element%dimension
248
249=== modified file 'python/firedrake/core_types.pyx'
250--- python/firedrake/core_types.pyx 2013-09-19 14:10:55 +0000
251+++ python/firedrake/core_types.pyx 2013-10-03 16:15:40 +0000
252@@ -67,10 +67,149 @@
253 if not initialised:
254 op2.init()
255 initialised = True
256-
257-def fiat_from_ufl_element(ufl_element, ufl_cell):
258- return FIAT.supported_elements[ufl_element.family()]\
259- (_FIAT_cells[ufl_cell.cellname()](), ufl_element.degree())
260+
261+def fiat_from_ufl_element(ufl_element):
262+ if isinstance(ufl_element, ufl.OuterProductElement):
263+ a = FIAT.supported_elements[ufl_element._A.family()]\
264+ (_FIAT_cells[ufl_element._A.cell().cellname()](), ufl_element._A.degree())
265+
266+ b = FIAT.supported_elements[ufl_element._B.family()]\
267+ (_FIAT_cells[ufl_element._B.cell().cellname()](), ufl_element._B.degree())
268+
269+ return FIAT.TensorFiniteElement(a, b)
270+ else:
271+ return FIAT.supported_elements[ufl_element.family()]\
272+ (_FIAT_cells[ufl_element.cell().cellname()](), ufl_element.degree())
273+
274+# Functions related to the extruded case
275+def compute_extruded_dofs(fiat_element, flat_dofs, layers):
276+ """Compute the number of dofs in a column"""
277+ size = len(flat_dofs)
278+ dofs_per_column = np.zeros(size, np.int32)
279+ for i in range(size):
280+ for j in range(2): #2 is due to the process of extrusion
281+ dofs_per_column[i] += (layers - j) * len(fiat_element.entity_dofs()[(i,j)][0])
282+ return dofs_per_column
283+
284+def compute_vertical_offsets(ent_dofs, flat_dofs):
285+ """Compute the offset between corresponding dofs in layers.
286+
287+ offsets[i] is the offset from the bottom of the stack to the
288+ corresponding dof in the ith layer.
289+ """
290+ size = len(flat_dofs)
291+ offsets_per_vertical = np.zeros(size, np.int32)
292+ for i in range(size):
293+ if len(flat_dofs[i][0]) > 0:
294+ offsets_per_vertical[i] = len(flat_dofs[i][0]) - len(ent_dofs[(i,0)][0])
295+ return offsets_per_vertical
296+
297+def compute_offset(ent_dofs, flat_dofs, total_dofs):
298+ """Compute extruded offsets for flattened element.
299+
300+ offsets[i] is the number of dofs in the vertical for the ith
301+ column of flattened mesh entities."""
302+ size = len(flat_dofs)
303+ res = np.zeros(total_dofs, np.int32)
304+ vert_dofs = compute_vertical_offsets(ent_dofs, flat_dofs)
305+ for i in range(size):
306+ elems = len(flat_dofs[i])
307+ dofs_per_elem = len(flat_dofs[i][0])
308+ for j in range(elems):
309+ for k in range(dofs_per_elem):
310+ res[flat_dofs[i][j][k]] = vert_dofs[i]
311+ return res
312+
313+def total_num_dofs(flat_dofs):
314+ """Compute the total number of degrees of freedom in the extruded mesh"""
315+ size = len(flat_dofs)
316+ total = 0
317+ for i in range(size):
318+ total += len(flat_dofs[i]) * len(flat_dofs[i][0])
319+ return total
320+
321+def make_flat_fiat_element(ufl_cell_element, ufl_cell, flattened_entity_dofs):
322+ """Create a modified FIAT-style element.
323+ Transform object from 3D-Extruded to 2D-flattened FIAT-style object."""
324+ # Create base element
325+ base_element = fiat_from_ufl_element(ufl_cell_element)
326+
327+ # Alter base element
328+ base_element.dual.entity_ids = flattened_entity_dofs
329+ base_element.poly_set.num_members = total_num_dofs(flattened_entity_dofs)
330+
331+ return base_element
332+
333+def make_extruded_coords(mesh, kernel_str, layers):
334+ """Given a kernel, use it to generate the extruded coordinates.
335+
336+ :arg mesh: the 2d mesh to extrude
337+ :arg layers: the number of layers in the extruded mesh
338+ :arg kernel_str: a C function which produces the z value
339+ of the coordinates. Its calling signature is:
340+
341+ void extrusion_kernel(double *extruded_coords[],
342+ double *two_d_coords[],
343+ int *layer_number[])
344+
345+ So for example to build an evenly-spaced extruded mesh with eleven
346+ layers and height 1 in the vertical you would write:
347+
348+ void extrusion_kernel(double *extruded_coords[],
349+ double *two_d_coords[],
350+ int *layer_number[]) {
351+ extruded_coords[0][0] = two_d_coords[0][0]; // X
352+ extruded_coords[0][1] = two_d_coords[0][1]; // Y
353+ extruded_coords[0][2] = 0.1 * layer_number[0][0]; // Z
354+ }
355+ """
356+ coords_dim = len(mesh._coordinates[0])
357+ coords_xtr_dim = 3 #dimension
358+ kernel = op2.Kernel(kernel_str, "extrusion_kernel")
359+ # BIG TRICK HERE:
360+ # We need the +1 in order to include the entire column of vertices.
361+ # Extrusion is meant to iterate over the 3D cells which are layer - 1 in number.
362+ # The +1 correction helps in the case of iteration over vertices which need
363+ # one extra layer.
364+ iterset = op2.Set(mesh.num_vertices(), "verts1", layers=(layers+1))
365+ vnodes = op2.DataSet(iterset, coords_dim)
366+ lnodes = op2.DataSet(iterset, 1)
367+ nodes_xtr = op2.Set(mesh.num_vertices()*layers, "verts_xtr")
368+ d_nodes_xtr = op2.DataSet(nodes_xtr, coords_xtr_dim)
369+ d_lnodes_xtr = op2.DataSet(nodes_xtr, 1)
370+
371+ # Create an op2.Dat with the base mesh coordinates
372+ coords_vec = mesh._coordinates.flatten()
373+ coords = op2.Dat(vnodes, coords_vec, np.float64, "dat1")
374+
375+ # Create an op2.Dat with slots for the extruded coordinates
376+ coords_new = np.empty(layers * mesh.num_vertices() * coords_xtr_dim, dtype=np.float64)
377+ coords_xtr = op2.Dat(d_nodes_xtr, coords_new, np.float64, "dat_xtr")
378+
379+ # Creat an op2.Dat to hold the layer number
380+ layer_vec = np.tile(np.arange(0, layers), mesh.num_vertices())
381+ layer = op2.Dat(d_lnodes_xtr, layer_vec, np.int32, "dat_layer")
382+
383+ # Map a map for the bottom of the mesh.
384+ vertex_to_coords = [ i for i in range(0, mesh.num_vertices()) ]
385+ v2coords_offset = np.zeros(1, np.int32)
386+ map_2d = op2.Map(iterset, iterset, 1, vertex_to_coords, "v2coords", v2coords_offset)
387+
388+ # Create Map for extruded vertices
389+ vertex_to_xtr_coords = [ layers * i for i in range(0, mesh.num_vertices()) ]
390+ v2xtr_coords_offset = np.array([1], np.int32)
391+ map_xtr = op2.Map(iterset, nodes_xtr, 1, vertex_to_xtr_coords, "v2xtr_coords", v2xtr_coords_offset)
392+
393+ # Create Map for layer number
394+ v2xtr_layer_offset = np.array([1], np.int32)
395+ layer_xtr = op2.Map(iterset, nodes_xtr, 1, vertex_to_xtr_coords, "v2xtr_layer", v2xtr_layer_offset)
396+
397+ op2.par_loop(kernel, iterset,
398+ coords_xtr(op2.INC, map_xtr),
399+ coords(op2.READ, map_2d),
400+ layer(op2.READ, layer_xtr))
401+
402+ return coords_xtr.data
403
404 # C utility functions, not seen in python module
405 cdef void function_space_destructor(object capsule):
406@@ -88,22 +227,27 @@
407 descriptions.
408 """
409 cdef ft.element_t element
410- topology = fiat_element.ref_el.topology
411- element.dimension = len(topology) - 1
412- element.vertices = len(fiat_element.ref_el.vertices)
413- element.ndof = fiat_element.space_dimension()
414- element.degree = fiat_element.degree()
415+ if isinstance(fiat_element, FIAT.tensor_finite_element.TensorFiniteElement):
416+ # Use the reference element of the horizontal element.
417+ f_element = fiat_element.flattened_element()
418+ else:
419+ f_element = fiat_element
420+
421+ element.dimension = len(f_element.ref_el.topology) - 1
422+ element.vertices = len(f_element.ref_el.vertices)
423+ element.ndof = f_element.space_dimension()
424+ element.degree = f_element.degree()
425
426 # Need to free these when you're done
427 element.dofs_per = <int *>malloc((element.dimension + 1) * sizeof(int))
428 element.entity_dofs = <int *>malloc(3 * element.ndof * sizeof(int))
429
430- entity_dofs = fiat_element.entity_dofs()
431+ entity_dofs = f_element.entity_dofs()
432 cdef int d
433 cdef int e
434 cdef int dof
435 cdef int dof_pos = 0
436- for d, dim_entities in entity_dofs.iteritems():
437+ for d, dim_entities in entity_dofs.iteritems():
438 element.dofs_per[d] = 0
439 for e, this_entity_dofs in dim_entities.iteritems():
440 # This overwrites the same data a few times, but all of
441@@ -115,6 +259,7 @@
442 element.entity_dofs[dof_pos+1] = e
443 element.entity_dofs[dof_pos+2] = dof
444 dof_pos += 3
445+
446 return element
447
448 class _Facets(object):
449@@ -160,6 +305,8 @@
450 def __init__(self, *args):
451
452 _init()
453+
454+ self._layers = 1
455
456 self.cell_halo = None
457 self.vertex_halo = None
458@@ -257,6 +404,10 @@
459 for measure in [ufl.dx, ufl.ds, ufl.dS]:
460 measure._domain_data = self._coordinate_field
461
462+ @property
463+ def layers(self):
464+ return self._layers
465+
466 def cells(self):
467 return self._cells
468
469@@ -299,6 +450,89 @@
470 '''Currently a no-op for flop.py compatibility.'''
471 pass
472
473+class ExtrudedMesh(Mesh):
474+ """Build an extruded mesh from a 2D input mesh
475+
476+ :arg mesh: 2D unstructured mesh
477+ :arg layers: number of structured layers in the "vertical"
478+ direction
479+ :arg kernel: C kernel to produce 3D coordinates for the extruded
480+ mesh see :func:`make_extruded_coords` for more details."""
481+ def __init__(self, mesh, layers, kernel):
482+ self._old_mesh = mesh
483+ self._layers = layers
484+ self._cells = mesh._cells
485+ self.cell_halo = mesh.cell_halo
486+ self._entities = mesh._entities
487+ self.parent = mesh.parent
488+ self.uid = mesh.uid
489+ self.region_ids = mesh.region_ids
490+ self.cell_classes = mesh.cell_classes
491+ self._coordinates = mesh._coordinates
492+ self.name = mesh.name
493+
494+ self.ufl_cell_element = ufl.FiniteElement("Lagrange",
495+ domain = mesh._ufl_cell,
496+ degree = 1)
497+ self.ufl_interval_element = ufl.FiniteElement("Lagrange",
498+ domain = ufl.Cell("interval",1),
499+ degree = 1)
500+
501+ self.fiat_base_element = fiat_from_ufl_element(self.ufl_cell_element)
502+ self.fiat_vert_element = fiat_from_ufl_element(self.ufl_interval_element)
503+
504+ fiat_element = FIAT.tensor_finite_element.TensorFiniteElement(self.fiat_base_element, self.fiat_vert_element)
505+
506+ self._ufl_cell = ufl.OuterProductCell(mesh._ufl_cell, ufl.Cell("interval",1))
507+
508+ flat_temp = fiat_element.flattened_element()
509+
510+ # Calculated dofs_per_column from flattened_element and layers.
511+ # The mirrored elements have to be counted only once.
512+ # Then multiply by layers and layers - 1 accordingly.
513+ self.dofs_per_column = compute_extruded_dofs(fiat_element, flat_temp.entity_dofs(), layers)
514+
515+ #Compute Coordinates of the extruded mesh
516+ self._coordinates = make_extruded_coords(mesh, kernel, layers)
517+
518+ # Now we need to produce the extruded mesh using
519+ # techqniues employed when computing the
520+ # function space.
521+ cdef ft.element_t element_f = as_element(fiat_element)
522+ cdef void *fluidity_mesh = py.PyCapsule_GetPointer(mesh._fluidity_mesh, _mesh_name)
523+ if fluidity_mesh == NULL:
524+ raise RuntimeError("Didn't find fluidity mesh pointer in mesh %s" % mesh)
525+
526+ cdef int _ptr = self.dofs_per_column.ctypes.data
527+ cdef int *dofs_per_column = <int *><void *>_ptr
528+
529+ extruded_mesh = ft.extruded_mesh_f(fluidity_mesh, &element_f, dofs_per_column)
530+
531+ #Assign the newly computed extruded mesh as the fluidity mesh
532+ self._fluidity_mesh = py.PyCapsule_New(extruded_mesh.fluidity_mesh,
533+ _mesh_name,
534+ NULL)
535+
536+ self._coordinate_fs = VectorFunctionSpace(self, "Lagrange", 1)
537+
538+ self._coordinate_field = Function(self._coordinate_fs,
539+ val = self._coordinates)
540+
541+
542+ # Set the domain_data on all the default measures to this coordinate field.
543+ for measure in [ufl.dx, ufl.ds, ufl.dS]:
544+ measure._domain_data = self._coordinate_field
545+
546+ @utils.cached_property
547+ def cell_set(self):
548+ if self.cell_halo:
549+ size = self.cell_classes
550+ halo = self.cell_halo.op2_halo
551+ else:
552+ size = self.num_cells()
553+ halo = None
554+ return self.parent.cell_set if self.parent else \
555+ op2.Set(size, "%s_elements" % self.name, halo=halo, layers=self._layers)
556
557 class Halo(object):
558 """Fluidity Halo type"""
559@@ -428,24 +662,116 @@
560
561
562 class FunctionSpace(object):
563- def __init__(self, mesh, family, degree, name = None):
564-
565- self._ufl_element = ufl.FiniteElement(family,
566- domain = mesh._ufl_cell,
567- degree = degree)
568-
569- self.fiat_element = fiat_from_ufl_element(self._ufl_element,
570- mesh._ufl_cell)
571-
572+ """Create a function space
573+
574+ :arg mesh: mesh to build the function space on
575+ :arg family: string describing function space family, or a
576+ :class:`ufl.OuterProductElement`
577+ :arg degree: degree of the function space
578+ :arg name: (optional) name of the function space
579+ :arg vfamily: family of function space in vertical dimension
580+ (:class:`ExtrudedMesh`\es only)
581+ :arg vdegree: degree of function space in vertical dimension
582+ (:class:`ExtrudedMesh`\es only)
583+
584+ If the mesh is an :class:`ExtrudedMesh`, and the `family` argument
585+ is a :class:`ufl.OuterProductElement`, `degree`, `vfamily` and
586+ `vdegree` are ignored, since the `family` provides all necessary
587+ information, otherwise a :class:`ufl.OuterProductElement` is built
588+ from the (`family`, `degree`) and (`vfamily`, `vdegree`) pair. If
589+ the `vfamily` and `vdegree` are not provided, the vertical element
590+ will be the same as the provided (`family`, `degree`) pair.
591+
592+ If the mesh is not an :class:`ExtrudedMesh`, the `family` must be
593+ a string describing the finite element family to use, and the
594+ `degree` must be provided, `vfamily` and `vdegree` are ignored in
595+ this case.
596+ """
597+ def __init__(self, mesh, family, degree=None, name=None, vfamily=None, vdegree=None):
598+ if isinstance(mesh, ExtrudedMesh):
599+ # The function space must adapt to the extrusion
600+ # accordingly.
601+ # The bottom layer maps will come from lement_dof_list
602+ # dof_count is the total number of dofs in the extruded mesh
603+
604+ if isinstance(family, ufl.OuterProductElement):
605+
606+ a = family._A
607+ b = family._B
608+
609+ la = ufl.FiniteElement(a.family(),
610+ domain=mesh._old_mesh._ufl_cell,
611+ degree=a.degree())
612+
613+ lb = ufl.FiniteElement(b.family(),
614+ domain=ufl.Cell("interval",1),
615+ degree=b.degree())
616+
617+ else:
618+ la = ufl.FiniteElement(family,
619+ domain=mesh._old_mesh._ufl_cell,
620+ degree=degree)
621+ # FIAT version of the extrusion
622+ if vfamily is None or vdegree is None:
623+ lb = ufl.FiniteElement(family,
624+ domain=ufl.Cell("interval",1),
625+ degree=degree)
626+ else:
627+ lb = ufl.FiniteElement(vfamily,
628+ domain=ufl.Cell("interval",1),
629+ degree=vdegree)
630+
631+ # Create the Function Space element
632+ self._ufl_element = ufl.OuterProductElement(la, lb)
633+
634+ # Compute the FIAT version of the UFL element above
635+ self.fiat_element = fiat_from_ufl_element(self._ufl_element)
636+
637+ # Get the flattened version of the 3D FIAT element
638+ flat_temp = self.fiat_element.flattened_element()
639+
640+ # Compute the dofs per column
641+ self.dofs_per_column = compute_extruded_dofs(self.fiat_element,
642+ flat_temp.entity_dofs(),
643+ mesh._layers)
644+
645+ # Compute the offset for the extrusion process
646+ self.offset = compute_offset(self.fiat_element.entity_dofs(),
647+ flat_temp.entity_dofs(),
648+ self.fiat_element.space_dimension())
649+ else:
650+ if isinstance(family, ufl.OuterProductElement):
651+ raise RuntimeError("You can't build an extruded element on an unextruded Mesh")
652+ if degree is None:
653+ raise RuntimeError("The function space requires a degree")
654+
655+ self.offset = None
656+ self.dofs_per_column = np.zeros(1, np.int32)
657+ self.extruded = False
658+
659+ self._ufl_element = ufl.FiniteElement(family,
660+ domain=mesh._ufl_cell,
661+ degree=degree)
662+
663+ self.fiat_element = fiat_from_ufl_element(self._ufl_element)
664+
665+ # Create the extruded function space
666 cdef ft.element_t element_f = as_element(self.fiat_element)
667+
668 cdef void *fluidity_mesh = py.PyCapsule_GetPointer(mesh._fluidity_mesh, _mesh_name)
669 if fluidity_mesh == NULL:
670 raise RuntimeError("Didn't find fluidity mesh pointer in mesh %s" % mesh)
671-
672- function_space = ft.function_space_f(fluidity_mesh, &element_f)
673+
674+ cdef int *dofs_per_column = <int *>np.PyArray_DATA(self.dofs_per_column)
675+
676+ if isinstance(mesh, ExtrudedMesh):
677+ function_space = ft.extruded_mesh_f(fluidity_mesh, &element_f, dofs_per_column)
678+ else:
679+ function_space = ft.function_space_f(fluidity_mesh, &element_f)
680
681 free(element_f.dofs_per)
682 free(element_f.entity_dofs)
683+
684 self._fluidity_function_space = py.PyCapsule_New(function_space.fluidity_mesh,
685 _function_space_name,
686 &function_space_destructor)
687@@ -464,13 +790,14 @@
688
689 self._dim = 1
690
691- self.interior_facet_node_list = \
692- np.array(<int[:self._mesh.interior_facets.count,:2*element_f.ndof]>
693- function_space.interior_facet_node_list)
694+ if not isinstance(self._mesh, ExtrudedMesh):
695+ self.interior_facet_node_list = \
696+ np.array(<int[:self._mesh.interior_facets.count,:2*element_f.ndof]>
697+ function_space.interior_facet_node_list)
698
699- self.exterior_facet_node_list = \
700- np.array(<int[:self._mesh.exterior_facets.count,:element_f.ndof]>
701- function_space.exterior_facet_node_list)
702+ self.exterior_facet_node_list = \
703+ np.array(<int[:self._mesh.exterior_facets.count,:element_f.ndof]>
704+ function_space.exterior_facet_node_list)
705
706 # Note that this is the function space rank and is therefore
707 # always 0. The value rank may be different.
708@@ -502,9 +829,9 @@
709 name = "%s_nodes" % self.name
710 if self._halo:
711 return op2.Set(self.dof_classes, name,
712- halo=self._halo.op2_halo)
713+ halo=self._halo.op2_halo, layers=self._mesh.layers)
714 else:
715- return op2.Set(self.dof_count, name)
716+ return op2.Set(self.node_count, name, layers=self._mesh.layers)
717
718 @utils.cached_property
719 def dof_dset(self):
720@@ -526,7 +853,8 @@
721 underlying mesh to the :attr:`node_set` of this :class:FunctionSpace."""
722 return op2.Map(self._mesh.cell_set, self.node_set,
723 self.fiat_element.space_dimension(),
724- self.cell_node_list - 1, "%s_cell_dof" % (self.name))
725+ self.cell_node_list - 1, "%s_cell_dof" % (self.name),
726+ offset=self.offset)
727
728 @utils.cached_property
729 def interior_facet_node_map(self):
730@@ -558,11 +886,13 @@
731 def mesh(self):
732 """The :class:`Mesh` used to construct this :class:`FunctionSpace`."""
733 return self._mesh
734+
735+
736+
737
738 class VectorFunctionSpace(FunctionSpace):
739- def __init__(self, mesh, family, degree, dim = None, name = None):
740- super(VectorFunctionSpace, self).__init__(mesh, family, degree, name)
741-
742+ def __init__(self, mesh, family, degree, dim=None, name=None, vfamily=None, vdegree=None):
743+ super(VectorFunctionSpace, self).__init__(mesh, family, degree, name, vfamily=vfamily, vdegree=vdegree)
744 self.rank = 1
745 if dim is None:
746 # VectorFunctionSpace dimension defaults to the geometric dimension of the mesh.
747@@ -596,7 +926,7 @@
748 else:
749 raise NotImplementedError("Can't make a Function defined on a "
750 +str(type(function_space)))
751-
752+
753 ufl.Coefficient.__init__(self, self._function_space.ufl_element())
754
755 self.name = name
756
757=== modified file 'python/firedrake/fluidity_types.pxd'
758--- python/firedrake/fluidity_types.pxd 2013-09-19 13:10:25 +0000
759+++ python/firedrake/fluidity_types.pxd 2013-10-03 16:15:40 +0000
760@@ -66,3 +66,4 @@
761 cdef extern halo_t halo_f(void *, halo_entity)
762 cdef extern void function_space_destructor_f(void *)
763 cdef extern void vector_field_destructor_f(void *)
764+cdef extern function_space_t extruded_mesh_f(void *, element_t *, int *)
765
766=== modified file 'python/firedrake/io.py'
767--- python/firedrake/io.py 2013-09-10 13:19:41 +0000
768+++ python/firedrake/io.py 2013-10-03 16:15:40 +0000
769@@ -1,6 +1,7 @@
770 from evtk.hl import *
771 from evtk.vtk import _get_byte_order
772 from evtk.hl import _requiresLargeVTKFileSize, _addDataToFile, _appendDataToFile
773+from ufl import Cell, OuterProductCell
774 import numpy as np
775 import os
776 from pyop2.mpi import *
777@@ -8,18 +9,23 @@
778
779 # Dictionary used to translate the cellname of firedrake
780 # to the celltype of evtk module.
781-_cells = {
782- "interval": VtkLine,
783- "triangle": VtkTriangle,
784- "tetrahedron": VtkTetra
785-}
786-
787-_points_per_cell = {
788- "interval": 2,
789- "triangle": 3,
790- "tetrahedron": 4
791-}
792-
793+_cells = {}
794+_cells[Cell("interval")] = VtkLine
795+_cells[Cell("interval", 2)] = VtkLine
796+_cells[Cell("interval", 3)] = VtkLine
797+_cells[Cell("triangle")] = VtkTriangle
798+_cells[Cell("triangle", 3)] = VtkTriangle
799+_cells[Cell("tetrahedron")] = VtkTetra
800+_cells[OuterProductCell(Cell("triangle"),Cell("interval"))] = VtkWedge
801+
802+_points_per_cell = {}
803+_points_per_cell[Cell("interval")] = 2
804+_points_per_cell[Cell("interval", 2)] = 2
805+_points_per_cell[Cell("interval", 3)] = 2
806+_points_per_cell[Cell("triangle")] = 3
807+_points_per_cell[Cell("triangle", 3)] = 3
808+_points_per_cell[Cell("tetrahedron")] = 4
809+_points_per_cell[OuterProductCell(Cell("triangle"),Cell("interval"))] = 6
810
811 class File(object):
812
813@@ -114,20 +120,34 @@
814 # is not 1.
815
816 e = function.function_space().ufl_element()
817-
818 #finite element supported : CG1 and DG0
819- if not ((e.degree() == 1 and e.family() == "Lagrange") or
820- (e.degree() == 0 and e.family() == "Discontinuous Lagrange")):
821+ if not ((e.family() == "Lagrange" and e.degree() == 1) or
822+ (e.family() == "Discontinuous Lagrange" and e.degree() == 0) or
823+ (e.family() == "OuterProductElement")):
824 raise ValueError("ufl element given is not supported.")
825 function.dat.halo_exchange_begin()
826 function.dat.halo_exchange_end()
827 mesh = function.function_space().mesh()
828- num_points = mesh._entities[0]
829- num_cells = mesh._entities[-1]
830-
831+ if not (e.family() == "OuterProductElement"):
832+ num_points = mesh._entities[0]
833+ num_cells = mesh._entities[-1]
834+ else:
835+ num_points = mesh._entities[0]*mesh.layers
836+ num_cells = mesh._entities[-1]*(mesh.layers - 1)
837+
838 # In firedrake, the indexing of the points starts from 1, instead of 0.
839 # However the paraview expect them to have indexing starting from 0.
840- connectivity = mesh._cells.flatten() - 1
841+
842+ if not (e.family() == "OuterProductElement"):
843+ connectivity = mesh._cells.flatten() - 1
844+ else:
845+ # Horribly slow, hard-coded first attempt
846+ connectivity_temp = np.empty([mesh.num_cells(), mesh.layers-1, _points_per_cell[mesh._ufl_cell]],dtype="int32")
847+ for (ii, verts) in enumerate(mesh._cells):
848+ for nl in range(mesh.layers-1): # number of vert cells = layers - 1
849+ connectivity_temp[ii, nl] = np.concatenate((mesh.layers*(mesh._cells[ii]-1)+nl,mesh.layers*(mesh._cells[ii]-1)+nl+1))
850+ connectivity = connectivity_temp.flatten() # no need to subtract 1
851+
852 data = {function.name: function.dat.data.flatten()}
853
854 coordinates = self._fd_to_evtk_coord(mesh._coordinates)
855@@ -135,24 +155,43 @@
856 cell_types = np.empty(num_cells, dtype="uint8")
857
858 # Assume that all cells are of same shape.
859- cell_types[:] = _cells[mesh._ufl_cell.cellname()].tid
860- p_c = _points_per_cell[mesh._ufl_cell.cellname()]
861+ cell_types[:] = _cells[mesh._ufl_cell].tid
862+ p_c = _points_per_cell[mesh._ufl_cell]
863
864 # This tells which are the last nodes of each cell.
865 offsets = np.arange(
866 start=p_c, stop=p_c * (num_cells + 1), step=p_c, dtype='int32')
867- if e.degree() == 1:
868- large_file_flag = _requiresLargeVTKFileSize("VtkUnstructuredGrid",
869- numPoints=num_points,
870- numCells=num_cells,
871- pointData=data,
872- cellData=None)
873+ if (e.family() == "Lagrange" and e.degree() == 1): # if CG1
874+ large_file_flag = _requiresLargeVTKFileSize("VtkUnstructuredGrid",
875+ numPoints=num_points,
876+ numCells=num_cells,
877+ pointData=data,
878+ cellData=None)
879+ elif (e.family() == "Discontinuous Lagrange" and e.degree() == 0): # if DG0
880+ large_file_flag = _requiresLargeVTKFileSize("VtkUnstructuredGrid",
881+ numPoints=num_points,
882+ numCells=num_cells,
883+ pointData=None,
884+ cellData=data)
885+ elif (e.family() == "OuterProductElement" and
886+ e._A.family() == "Lagrange" and e._A.degree() == 1 and
887+ e._B.family() == "Lagrange" and e._B.degree() == 1):
888+ large_file_flag = _requiresLargeVTKFileSize("VtkUnstructuredGrid",
889+ numPoints=num_points,
890+ numCells=num_cells,
891+ pointData=data,
892+ cellData=None)
893+
894+ elif (e.family() == "OuterProductElement" and
895+ e._A.family() == "Discontinuous Lagrange" and e._A.degree() == 0 and
896+ e._B.family() == "Discontinuous Lagrange" and e._B.degree() == 0):
897+ large_file_flag = _requiresLargeVTKFileSize("VtkUnstructuredGrid",
898+ numPoints=num_points,
899+ numCells=num_cells,
900+ pointData=None,
901+ cellData=data)
902 else:
903- large_file_flag = _requiresLargeVTKFileSize("VtkUnstructuredGrid",
904- numPoints=num_points,
905- numCells=num_cells,
906- pointData=None,
907- cellData=data)
908+ raise ValueError("Can only support P1, P0, P1xP1, P0xP0. Hire another UROP for Summer 2014???")
909
910 new_name = self._filename
911
912
913=== modified file 'python/firedrake/mesh.py'
914--- python/firedrake/mesh.py 2013-09-30 13:01:36 +0000
915+++ python/firedrake/mesh.py 2013-10-03 16:15:40 +0000
916@@ -37,7 +37,6 @@
917 _3dexts = [".face"]
918 _pexts = [".halo"]
919
920-
921 def _build_msh_file(input, output, dimension):
922 if gmshpy:
923 # We've got the gmsh python interface available, so
924@@ -81,7 +80,6 @@
925 else:
926 raise e
927
928-
929 def _get_msh_file(source, name, dimension):
930
931 """Given a source code, name and dimension of the mesh,
932
933=== modified file 'python/firedrake/solving.py'
934--- python/firedrake/solving.py 2013-10-03 14:18:31 +0000
935+++ python/firedrake/solving.py 2013-10-03 16:15:40 +0000
936@@ -149,6 +149,7 @@
937 2-forms. The last of these may change to a native Firedrake type
938 in a future release.
939 """
940+
941 kernels = ffc_interface.compile_form(f, "form")
942
943 fd = f.form_data()
944@@ -163,6 +164,7 @@
945
946 if is_mat:
947 test, trial = fd.original_arguments
948+
949 m = test.function_space().mesh()
950 key = (compute_form_signature(f), test.function_space().dof_dset,
951 trial.function_space().dof_dset,
952@@ -189,6 +191,7 @@
953 result = lambda : result_function
954 else:
955 m = coords.function_space().mesh()
956+
957 # 0-forms are always scalar
958 tensor = op2.Global(1, [0.0])
959 result = lambda : tensor.data[0]
960@@ -205,10 +208,20 @@
961 flatten=True)
962 else:
963 tensor_arg = tensor(op2.INC)
964- args = [kernel, m.cell_set, tensor_arg,
965- coords.dat(op2.READ, coords.cell_node_map, flatten=True)]
966+
967+ itspace = m.cell_set
968+ if itspace.layers > 1:
969+ coords_xtr = m._coordinate_field
970+ args = [kernel, itspace, tensor_arg,
971+ coords_xtr.dat(op2.READ, coords_xtr.cell_node_map,
972+ flatten=True)]
973+ else:
974+ args = [kernel, itspace, tensor_arg,
975+ coords.dat(op2.READ, coords.cell_node_map, flatten=True)]
976+
977 for c in fd.original_coefficients:
978 args.append(c.dat(op2.READ, c.cell_node_map))
979+
980 op2.par_loop(*args)
981 if domain_type == 'exterior_facet':
982 if op2.MPI.parallel: raise \
983
984=== added directory 'tests/firedrake_extrusion_assemble_p0'
985=== added file 'tests/firedrake_extrusion_assemble_p0/Makefile'
986--- tests/firedrake_extrusion_assemble_p0/Makefile 1970-01-01 00:00:00 +0000
987+++ tests/firedrake_extrusion_assemble_p0/Makefile 2013-10-03 16:15:40 +0000
988@@ -0,0 +1,5 @@
989+input: clean
990+
991+clean:
992+ rm -f square* *.vtu *.pvd *.s *.d.1 *.stat *.log-0 *.err-0 \
993+ matrixdump matrixdump.info
994
995=== added file 'tests/firedrake_extrusion_assemble_p0/firedrake_assemble_p0.xml'
996--- tests/firedrake_extrusion_assemble_p0/firedrake_assemble_p0.xml 1970-01-01 00:00:00 +0000
997+++ tests/firedrake_extrusion_assemble_p0/firedrake_assemble_p0.xml 2013-10-03 16:15:40 +0000
998@@ -0,0 +1,19 @@
999+<?xml version='1.0' encoding='utf-8'?>
1000+<testproblem>
1001+ <name>identity</name>
1002+ <owner userid="gb308"/>
1003+ <tags>firedrake</tags>
1004+ <problem_definition length="short" nprocs="1">
1005+ <command_line>true</command_line>
1006+ </problem_definition>
1007+ <variables>
1008+ <variable name="result" language="python">
1009+import test_firedrake_assemble_p0 as test
1010+result = test.run_test()
1011+ </variable>
1012+ </variables>
1013+ <pass_tests>
1014+ <test name="Unit Extruded Square Integration value." language="python">assert result[0] == "0.5"</test>
1015+ </pass_tests>
1016+ <warn_tests/>
1017+</testproblem>
1018
1019=== added file 'tests/firedrake_extrusion_assemble_p0/test_firedrake_assemble_p0.py'
1020--- tests/firedrake_extrusion_assemble_p0/test_firedrake_assemble_p0.py 1970-01-01 00:00:00 +0000
1021+++ tests/firedrake_extrusion_assemble_p0/test_firedrake_assemble_p0.py 2013-10-03 16:15:40 +0000
1022@@ -0,0 +1,88 @@
1023+from firedrake import *
1024+import numpy as np
1025+import pyop2 as op2
1026+
1027+power = 5
1028+m = UnitSquareMesh(2**power,2**power)
1029+layers = 11
1030+
1031+# Populate the coordinates of the extruded mesh by providing the
1032+#coordinates as a field.
1033+# TODO: provide a kernel which will describe how coordinates are extruded.
1034+extrusion_kernel = """
1035+void extrusion_kernel(double *xtr[], double *x[], int* j[])
1036+{
1037+ //Only the Z-coord is increased, the others stay the same
1038+ xtr[0][0] = x[0][0];
1039+ xtr[0][1] = x[0][1];
1040+ xtr[0][2] = 0.1*j[0][0];
1041+}"""
1042+
1043+mesh = firedrake.ExtrudedMesh(m, layers, extrusion_kernel)
1044+
1045+#import pyop2.configuration as cfg
1046+#cfg.configure(debug=1)
1047+
1048+def integrate_assemble_p0(family, degree):
1049+ fs = firedrake.FunctionSpace(mesh, family, degree, name="fs")
1050+
1051+ f = firedrake.Function(fs)
1052+
1053+ fs1 = firedrake.FunctionSpace(mesh, family, degree, name="fs1")
1054+
1055+ f_rhs = firedrake.Function(fs1)
1056+
1057+ populate_p0 = op2.Kernel("""
1058+void populate_tracer(double *x[], double *c[])
1059+{
1060+ x[0][0] = (c[1][2] + c[0][2]) / 2;
1061+}""", "populate_tracer")
1062+
1063+ coords = f.function_space().mesh()._coordinate_field
1064+
1065+ op2.par_loop(populate_p0, f.cell_set,
1066+ f.dat(op2.INC, f.cell_node_map),
1067+ coords.dat(op2.READ, coords.cell_node_map))
1068+
1069+ volume = op2.Kernel("""
1070+void comp_vol(double *rhs[], double *x[], double *y[])
1071+{
1072+ double area = x[0][0]*(x[2][1]-x[4][1]) + x[2][0]*(x[4][1]-x[0][1])
1073+ + x[4][0]*(x[0][1]-x[2][1]);
1074+ if (area < 0)
1075+ area = area * (-1.0);
1076+ rhs[0][0] += 0.5 * area * (x[1][2] - x[0][2]) * y[0][0];
1077+}""", "comp_vol")
1078+
1079+ op2.par_loop(volume, f.cell_set,
1080+ f_rhs.dat(op2.WRITE, f_rhs.cell_node_map),
1081+ coords.dat(op2.READ, coords.cell_node_map),
1082+ f.dat(op2.READ, f.cell_node_map)
1083+ )
1084+
1085+ g = op2.Global(1, data=0.0, name='g')
1086+
1087+ reduction = op2.Kernel("""
1088+void comp_reduction(double A[1], double *x[])
1089+{
1090+ A[0] += x[0][0];
1091+}""", "comp_reduction")
1092+
1093+ op2.par_loop(reduction, f_rhs.cell_set,
1094+ g(op2.INC),
1095+ f_rhs.dat(op2.READ, f_rhs.cell_node_map)
1096+ )
1097+
1098+ return str(g.data[0])
1099+
1100+def run_test():
1101+ family = "DG"
1102+ degree = 0
1103+
1104+ return [integrate_assemble_p0(family, degree)]
1105+
1106+if __name__=="__main__":
1107+
1108+ result = run_test()
1109+ for i, res in enumerate(result):
1110+ print "Result for extruded unit cube integration "+`i+1`+": "+`res`
1111
1112=== added directory 'tests/firedrake_extrusion_assembly'
1113=== added file 'tests/firedrake_extrusion_assembly/Makefile'
1114--- tests/firedrake_extrusion_assembly/Makefile 1970-01-01 00:00:00 +0000
1115+++ tests/firedrake_extrusion_assembly/Makefile 2013-10-03 16:15:40 +0000
1116@@ -0,0 +1,5 @@
1117+input: clean
1118+
1119+clean:
1120+ rm -f square* *.vtu *.pvd *.s *.d.1 *.stat *.log-0 *.err-0 \
1121+ matrixdump matrixdump.info
1122
1123=== added file 'tests/firedrake_extrusion_assembly/firedrake_assembly.xml'
1124--- tests/firedrake_extrusion_assembly/firedrake_assembly.xml 1970-01-01 00:00:00 +0000
1125+++ tests/firedrake_extrusion_assembly/firedrake_assembly.xml 2013-10-03 16:15:40 +0000
1126@@ -0,0 +1,22 @@
1127+<?xml version='1.0' encoding='utf-8'?>
1128+<testproblem>
1129+ <name>identity</name>
1130+ <owner userid="gb308"/>
1131+ <tags>firedrake</tags>
1132+ <problem_definition length="short" nprocs="1">
1133+ <command_line>true</command_line>
1134+ </problem_definition>
1135+ <variables>
1136+ <variable name="error" language="python">
1137+import test_firedrake_assembly as test
1138+error = test.run_test()
1139+ </variable>
1140+ </variables>
1141+ <pass_tests>
1142+ <test name="Error inf norm. degree 1" language="python">assert error[0] &lt; 1.0e-14</test>
1143+ <test name="Error inf norm. degree 2" language="python">assert error[1] &lt; 1.0e-6</test>
1144+ <test name="Error inf norm. degree 3" language="python">assert error[2] &lt; 1.0e-6</test>
1145+ <test name="Error inf norm. degree 4" language="python">assert error[3] &lt; 1.0e-6</test>
1146+ </pass_tests>
1147+ <warn_tests/>
1148+</testproblem>
1149
1150=== added file 'tests/firedrake_extrusion_assembly/test_firedrake_assembly.py'
1151--- tests/firedrake_extrusion_assembly/test_firedrake_assembly.py 1970-01-01 00:00:00 +0000
1152+++ tests/firedrake_extrusion_assembly/test_firedrake_assembly.py 2013-10-03 16:15:40 +0000
1153@@ -0,0 +1,57 @@
1154+from firedrake import *
1155+import numpy as np
1156+
1157+power = 1
1158+m = UnitSquareMesh(2**power,2**power)
1159+layers = 11
1160+
1161+# Populate the coordinates of the extruded mesh by providing the
1162+#coordinates as a field.
1163+extrusion_kernel = """
1164+void extrusion_kernel(double *xtr[], double *x[], int* j[])
1165+{
1166+ //Only the Z-coord is increased, the others stay the same
1167+ xtr[0][0] = x[0][0];
1168+ xtr[0][1] = x[0][1];
1169+ xtr[0][2] = 0.1*j[0][0];
1170+}"""
1171+
1172+mesh = firedrake.ExtrudedMesh(m, layers, extrusion_kernel)
1173+
1174+#import pyop2.configuration as cfg
1175+#cfg.configure(debug=1)
1176+
1177+def identity_xtr(family, degree):
1178+ fs = firedrake.FunctionSpace(mesh, family, degree, name="fs")
1179+
1180+ f = firedrake.Function(fs)
1181+ out = firedrake.Function(fs)
1182+
1183+ u = firedrake.TrialFunction(fs)
1184+ v = firedrake.TestFunction(fs)
1185+
1186+ M = firedrake.assemble(firedrake.dot(firedrake.grad(u),firedrake.grad(v))*firedrake.dx)
1187+
1188+ f.interpolate(firedrake.Expression("6.0"))
1189+
1190+ b = firedrake.assemble(f*v*firedrake.dx)
1191+
1192+ firedrake.solve(u*v*firedrake.dx==f*v*firedrake.dx, out)
1193+
1194+ return np.max(np.abs(out.dat.data-f.dat.data))
1195+
1196+def run_test():
1197+ family = "Lagrange"
1198+ degree = range(1,5)
1199+
1200+ error = []
1201+ for d in degree:
1202+ error.append(identity_xtr(family, d))
1203+ return error
1204+
1205+
1206+if __name__=="__main__":
1207+
1208+ error = run_test()
1209+ for i, err in enumerate(error):
1210+ print "Inf norm error in identity for Lagrange "+`i+1`+": "+`err`
1211
1212=== added directory 'tests/firedrake_extrusion_helmholtz'
1213=== added file 'tests/firedrake_extrusion_helmholtz/Makefile'
1214--- tests/firedrake_extrusion_helmholtz/Makefile 1970-01-01 00:00:00 +0000
1215+++ tests/firedrake_extrusion_helmholtz/Makefile 2013-10-03 16:15:40 +0000
1216@@ -0,0 +1,5 @@
1217+input: clean
1218+
1219+clean:
1220+ rm -f square* *.vtu *.pvd *.s *.d.1 *.stat *.log-0 *.err-0 \
1221+ matrixdump matrixdump.info
1222
1223=== added file 'tests/firedrake_extrusion_helmholtz/test_firedrake_extrusion_helmholtz.py'
1224--- tests/firedrake_extrusion_helmholtz/test_firedrake_extrusion_helmholtz.py 1970-01-01 00:00:00 +0000
1225+++ tests/firedrake_extrusion_helmholtz/test_firedrake_extrusion_helmholtz.py 2013-10-03 16:15:40 +0000
1226@@ -0,0 +1,59 @@
1227+"""This demo program solves Helmholtz's equation
1228+
1229+ - div grad u(x, y) + u(x,y) = f(x, y)
1230+
1231+on the unit square with source f given by
1232+
1233+ f(x, y) = (1.0 + 8.0*pi**2)*cos(x[0]*2*pi)*cos(x[1]*2*pi)
1234+
1235+and the analytical solution
1236+
1237+ u(x, y) = cos(x[0]*2*pi)*cos(x[1]*2*pi)
1238+"""
1239+
1240+# Begin demo
1241+from firedrake import *
1242+import sys
1243+
1244+power = int(sys.argv[1])
1245+# Create mesh and define function space
1246+m = UnitSquareMesh(2**power,2**power)
1247+layers = 2**int(sys.argv[1])+1
1248+
1249+# Populate the coordinates of the extruded mesh by providing the
1250+#coordinates as a field.
1251+extrusion_kernel = """
1252+void extrusion_kernel(double *xtr[], double *x[], int* j[])
1253+{
1254+ //Only the Z-coord is increased, the others stay the same
1255+ xtr[0][0] = x[0][0];
1256+ xtr[0][1] = x[0][1];
1257+ xtr[0][2] = %(height)s*j[0][0];
1258+}""" % { 'height' : str(1.0/2**int(sys.argv[1])) }
1259+
1260+mesh = ExtrudedMesh(m, layers, extrusion_kernel)
1261+V = FunctionSpace(mesh, "Lagrange", 1, vfamily="Lagrange", vdegree=1)
1262+
1263+# Define variational problem
1264+u = TrialFunction(V)
1265+v = TestFunction(V)
1266+f = Function(V)
1267+f.interpolate(Expression("(1+12*pi*pi)*cos(x[0]*pi*2)*cos(x[1]*pi*2)*cos(x[2]*pi*2)"))
1268+a = (dot(grad(v),grad(u))+v*u)*dx
1269+L = f*v*dx
1270+
1271+# Compute solution
1272+A = assemble(a)
1273+b = assemble(L)
1274+x = Function(V)
1275+solve(a==L, x)
1276+
1277+# Analytical solution
1278+f.interpolate( Expression("cos(x[0]*pi*2)*cos(x[1]*pi*2)*cos(x[2]*pi*2)"))
1279+
1280+print sqrt(assemble((x-f)*(x-f)*dx))
1281+
1282+# Save solution in VTK format
1283+#file = File("helmholtz.pvd")
1284+#file << x
1285+#file << f
1286
1287=== added directory 'tests/firedrake_extrusion_identity'
1288=== added file 'tests/firedrake_extrusion_identity/Makefile'
1289--- tests/firedrake_extrusion_identity/Makefile 1970-01-01 00:00:00 +0000
1290+++ tests/firedrake_extrusion_identity/Makefile 2013-10-03 16:15:40 +0000
1291@@ -0,0 +1,5 @@
1292+input: clean
1293+
1294+clean:
1295+ rm -f square* *.vtu *.pvd *.s *.d.1 *.stat *.log-0 *.err-0 \
1296+ matrixdump matrixdump.info
1297
1298=== added file 'tests/firedrake_extrusion_identity/firedrake_extrusion.xml'
1299--- tests/firedrake_extrusion_identity/firedrake_extrusion.xml 1970-01-01 00:00:00 +0000
1300+++ tests/firedrake_extrusion_identity/firedrake_extrusion.xml 2013-10-03 16:15:40 +0000
1301@@ -0,0 +1,22 @@
1302+<?xml version='1.0' encoding='utf-8'?>
1303+<testproblem>
1304+ <name>identity</name>
1305+ <owner userid="gb308"/>
1306+ <tags>firedrake</tags>
1307+ <problem_definition length="short" nprocs="1">
1308+ <command_line>true</command_line>
1309+ </problem_definition>
1310+ <variables>
1311+ <variable name="error" language="python">
1312+import test_firedrake_extrusion as test
1313+error = test.run_test()
1314+ </variable>
1315+ </variables>
1316+ <pass_tests>
1317+ <test name="Error inf norm. degree 1" language="python">assert error[0] &lt; 1.0e-14</test>
1318+ <test name="Error inf norm. degree 2" language="python">assert error[1] &lt; 1.0e-6</test>
1319+ <test name="Error inf norm. degree 3" language="python">assert error[2] &lt; 1.0e-6</test>
1320+ <test name="Error inf norm. degree 4" language="python">assert error[3] &lt; 1.0e-6</test>
1321+ </pass_tests>
1322+ <warn_tests/>
1323+</testproblem>
1324
1325=== added file 'tests/firedrake_extrusion_identity/test_firedrake_extrusion.py'
1326--- tests/firedrake_extrusion_identity/test_firedrake_extrusion.py 1970-01-01 00:00:00 +0000
1327+++ tests/firedrake_extrusion_identity/test_firedrake_extrusion.py 2013-10-03 16:15:40 +0000
1328@@ -0,0 +1,58 @@
1329+from firedrake import *
1330+import numpy as np
1331+
1332+power = 1
1333+m = UnitSquareMesh(2**power,2**power)
1334+layers = 11
1335+
1336+# Populate the coordinates of the extruded mesh by providing the
1337+#coordinates as a field.
1338+# TODO: provide a kernel which will describe how coordinates are extruded.
1339+extrusion_kernel = """
1340+void extrusion_kernel(double *xtr[], double *x[], int* j[])
1341+{
1342+ //Only the Z-coord is increased, the others stay the same
1343+ xtr[0][0] = x[0][0];
1344+ xtr[0][1] = x[0][1];
1345+ xtr[0][2] = 0.1*j[0][0];
1346+}"""
1347+
1348+mesh = firedrake.ExtrudedMesh(m, layers, extrusion_kernel)
1349+
1350+#import pyop2.configuration as cfg
1351+#cfg.configure(debug=1)
1352+
1353+def identity_xtr(family, degree):
1354+ fs = firedrake.FunctionSpace(mesh, family, degree, name="fs")
1355+
1356+ f = firedrake.Function(fs)
1357+ out = firedrake.Function(fs)
1358+
1359+ u = firedrake.TrialFunction(fs)
1360+ v = firedrake.TestFunction(fs)
1361+
1362+ M = firedrake.assemble(u*v*firedrake.dx)
1363+
1364+ f.interpolate(firedrake.Expression("x[0]"))
1365+
1366+ b = firedrake.assemble(f*v*firedrake.dx)
1367+
1368+ firedrake.solve(u*v*firedrake.dx==f*v*firedrake.dx, out)
1369+
1370+ return np.max(np.abs(out.dat.data-f.dat.data))
1371+
1372+def run_test():
1373+ family = "Lagrange"
1374+ degree = range(1,5)
1375+
1376+ error = []
1377+ for d in degree:
1378+ error.append(identity_xtr(family, d))
1379+ return error
1380+
1381+
1382+if __name__=="__main__":
1383+
1384+ error = run_test()
1385+ for i, err in enumerate(error):
1386+ print "Inf norm error in identity for Lagrange "+`i+1`+": "+`err`
1387
1388=== added directory 'tests/firedrake_extrusion_lsw'
1389=== added file 'tests/firedrake_extrusion_lsw/Makefile'
1390--- tests/firedrake_extrusion_lsw/Makefile 1970-01-01 00:00:00 +0000
1391+++ tests/firedrake_extrusion_lsw/Makefile 2013-10-03 16:15:40 +0000
1392@@ -0,0 +1,5 @@
1393+input: clean
1394+
1395+clean:
1396+ rm -f square* *.vtu *.pvd *.s *.d.1 *.stat *.log-0 *.err-0 \
1397+ matrixdump matrixdump.info
1398
1399=== added file 'tests/firedrake_extrusion_lsw/firedrake_extrusion_lsw.xml'
1400--- tests/firedrake_extrusion_lsw/firedrake_extrusion_lsw.xml 1970-01-01 00:00:00 +0000
1401+++ tests/firedrake_extrusion_lsw/firedrake_extrusion_lsw.xml 2013-10-03 16:15:40 +0000
1402@@ -0,0 +1,19 @@
1403+<?xml version='1.0' encoding='utf-8'?>
1404+<testproblem>
1405+ <name>identity</name>
1406+ <owner userid="gb308"/>
1407+ <tags>firedrake</tags>
1408+ <problem_definition length="special" nprocs="1">
1409+ <command_line>true</command_line>
1410+ </problem_definition>
1411+ <variables>
1412+ <variable name="result" language="python">
1413+import test_firedrake_extrusion_lsw as test
1414+result = test.run_test()
1415+ </variable>
1416+ </variables>
1417+ <pass_tests>
1418+ <test name="Unit Extruded Square Integration value." language="python">assert result[0] &lt; 0.0002</test>
1419+ </pass_tests>
1420+ <warn_tests/>
1421+</testproblem>
1422
1423=== added file 'tests/firedrake_extrusion_lsw/test_firedrake_extrusion_lsw.py'
1424--- tests/firedrake_extrusion_lsw/test_firedrake_extrusion_lsw.py 1970-01-01 00:00:00 +0000
1425+++ tests/firedrake_extrusion_lsw/test_firedrake_extrusion_lsw.py 2013-10-03 16:15:40 +0000
1426@@ -0,0 +1,77 @@
1427+"""Demo of the Shallow Water
1428+"""
1429+
1430+# Begin demo
1431+from firedrake import *
1432+
1433+power = 5
1434+# Create mesh and define function space
1435+m = UnitSquareMesh(2**power,2**power)
1436+layers = 5
1437+
1438+# Populate the coordinates of the extruded mesh by providing the
1439+#coordinates as a field.
1440+extrusion_kernel = """
1441+void extrusion_kernel(double *xtr[], double *x[], int* j[])
1442+{
1443+ //Only the Z-coord is increased, the others stay the same
1444+ xtr[0][0] = x[0][0];
1445+ xtr[0][1] = x[0][1];
1446+ xtr[0][2] = 0.25*j[0][0];
1447+}"""
1448+
1449+mesh = ExtrudedMesh(m, layers, extrusion_kernel)
1450+W = FunctionSpace(mesh, "BDM", 1, vfamily="Lagrange", vdegree=1)
1451+X = FunctionSpace(mesh, "DG", 0, vfamily="Lagrange", vdegree=1)
1452+Xplot = FunctionSpace(mesh, "CG", 1, vfamily="Lagrange", vdegree=1)
1453+
1454+# Define starting field
1455+u_0 = Function(W)
1456+u_h = Function(W)
1457+u_1 = Function(W)
1458+p_0 = Function(X)
1459+p_1 = Function(X)
1460+p_plot = Function(Xplot)
1461+p_0.interpolate(Expression("sin(4*pi*x[0])*sin(2*pi*x[1])"))
1462+
1463+T = 0.5
1464+t = 0
1465+dt = 0.0025
1466+
1467+file = File("lsw3d.pvd")
1468+p_trial = TrialFunction(Xplot)
1469+p_test = TestFunction(Xplot)
1470+solve(p_trial*p_test*dx == p_0*p_test*dx, p_plot)
1471+file << p_plot, t
1472+
1473+while t < T:
1474+ u = TrialFunction(W)
1475+ w = TestFunction(W)
1476+ a_1 = dot(w, u)*dx
1477+ L_1 = dot(w, u_0)*dx + 0.5*dt*div(w)*p_0*dx
1478+ solve(a_1==L_1, u_h)
1479+
1480+ p = TrialFunction(X)
1481+ phi = TestFunction(X)
1482+ a_2 = phi*p*dx
1483+ L_2 = phi*p_0*dx - dt*phi*div(u_h)*dx
1484+ solve(a_2==L_2, p_1)
1485+
1486+ u = TrialFunction(W)
1487+ w = TestFunction(W)
1488+ a_3 = dot(w, u)*dx
1489+ L_3 = dot(w, u_h)*dx + 0.5*dt*div(w)*p_1*dx
1490+ solve(a_3==L_3, u_1)
1491+
1492+ #u_0.assign(u_1)
1493+ #p_0.assign(p_1)
1494+ u_0 = u_1
1495+ p_0 = p_1
1496+ t += dt
1497+
1498+ # project into P1 x P1 for plotting
1499+ p_trial = TrialFunction(Xplot)
1500+ p_test = TestFunction(Xplot)
1501+ solve(p_trial*p_test*dx == p_0*p_test*dx, p_plot)
1502+ file << p_plot, t
1503+ print t
1504\ No newline at end of file
1505
1506=== added directory 'tests/firedrake_extrusion_p0'
1507=== added file 'tests/firedrake_extrusion_p0/Makefile'
1508--- tests/firedrake_extrusion_p0/Makefile 1970-01-01 00:00:00 +0000
1509+++ tests/firedrake_extrusion_p0/Makefile 2013-10-03 16:15:40 +0000
1510@@ -0,0 +1,5 @@
1511+input: clean
1512+
1513+clean:
1514+ rm -f square* *.vtu *.pvd *.s *.d.1 *.stat *.log-0 *.err-0 \
1515+ matrixdump matrixdump.info
1516
1517=== added file 'tests/firedrake_extrusion_p0/firedrake_p0.xml'
1518--- tests/firedrake_extrusion_p0/firedrake_p0.xml 1970-01-01 00:00:00 +0000
1519+++ tests/firedrake_extrusion_p0/firedrake_p0.xml 2013-10-03 16:15:40 +0000
1520@@ -0,0 +1,19 @@
1521+<?xml version='1.0' encoding='utf-8'?>
1522+<testproblem>
1523+ <name>identity</name>
1524+ <owner userid="gb308"/>
1525+ <tags>firedrake</tags>
1526+ <problem_definition length="short" nprocs="1">
1527+ <command_line>true</command_line>
1528+ </problem_definition>
1529+ <variables>
1530+ <variable name="result" language="python">
1531+import test_firedrake_p0 as test
1532+result = test.run_test()
1533+ </variable>
1534+ </variables>
1535+ <pass_tests>
1536+ <test name="Unit Extruded Square Integration value." language="python">assert result[0] == "3.0"</test>
1537+ </pass_tests>
1538+ <warn_tests/>
1539+</testproblem>
1540
1541=== added file 'tests/firedrake_extrusion_p0/test_firedrake_p0.py'
1542--- tests/firedrake_extrusion_p0/test_firedrake_p0.py 1970-01-01 00:00:00 +0000
1543+++ tests/firedrake_extrusion_p0/test_firedrake_p0.py 2013-10-03 16:15:40 +0000
1544@@ -0,0 +1,72 @@
1545+from firedrake import *
1546+import numpy as np
1547+import pyop2 as op2
1548+
1549+power = 5
1550+m = UnitSquareMesh(2**power,2**power)
1551+layers = 11
1552+
1553+# Populate the coordinates of the extruded mesh by providing the
1554+#coordinates as a field.
1555+# TODO: provide a kernel which will describe how coordinates are extruded.
1556+extrusion_kernel = """
1557+void extrusion_kernel(double *xtr[], double *x[], int* j[])
1558+{
1559+ //Only the Z-coord is increased, the others stay the same
1560+ xtr[0][0] = x[0][0];
1561+ xtr[0][1] = x[0][1];
1562+ xtr[0][2] = 0.1*j[0][0];
1563+}"""
1564+
1565+mesh = firedrake.ExtrudedMesh(m, layers, extrusion_kernel)
1566+
1567+#import pyop2.configuration as cfg
1568+#cfg.configure(debug=1)
1569+
1570+def integrate_p0(family, degree):
1571+ fs = firedrake.FunctionSpace(mesh, family, degree, name="fs")
1572+
1573+ f = firedrake.Function(fs)
1574+
1575+ populate_p0 = op2.Kernel("""
1576+void populate_tracer(double *x[])
1577+{
1578+ x[0][0] = 3;
1579+}""", "populate_tracer")
1580+
1581+ op2.par_loop(populate_p0, f.cell_set,
1582+ f.dat(op2.INC, f.cell_node_map))
1583+
1584+ volume = op2.Kernel("""
1585+void comp_vol(double A[1], double *x[], double *y[])
1586+{
1587+ double area = x[0][0]*(x[2][1]-x[4][1]) + x[2][0]*(x[4][1]-x[0][1])
1588+ + x[4][0]*(x[0][1]-x[2][1]);
1589+ if (area < 0)
1590+ area = area * (-1.0);
1591+ A[0] += 0.5 * area * (x[1][2] - x[0][2]) * y[0][0];
1592+}""", "comp_vol")
1593+
1594+ g = op2.Global(1, data=0.0, name='g')
1595+
1596+ coords = f.function_space().mesh()._coordinate_field
1597+
1598+ op2.par_loop(volume, f.cell_set,
1599+ g(op2.INC),
1600+ coords.dat(op2.READ, coords.cell_node_map),
1601+ f.dat(op2.READ, f.cell_node_map)
1602+ )
1603+
1604+ return str(g.data[0])
1605+
1606+def run_test():
1607+ family = "DG"
1608+ degree = 0
1609+
1610+ return [integrate_p0(family, degree)]
1611+
1612+if __name__=="__main__":
1613+
1614+ result = run_test()
1615+ for i, res in enumerate(result):
1616+ print "Result for extruded unit cube integration "+`i+1`+": "+`res`
1617
1618=== added directory 'tests/firedrake_extrusion_project'
1619=== added file 'tests/firedrake_extrusion_project/Makefile'
1620--- tests/firedrake_extrusion_project/Makefile 1970-01-01 00:00:00 +0000
1621+++ tests/firedrake_extrusion_project/Makefile 2013-10-03 16:15:40 +0000
1622@@ -0,0 +1,5 @@
1623+input: clean
1624+
1625+clean:
1626+ rm -f square* *.vtu *.pvd *.s *.d.1 *.stat *.log-0 *.err-0 \
1627+ matrixdump matrixdump.info
1628
1629=== added file 'tests/firedrake_extrusion_project/test_firedrake_extrusion_project.py'
1630--- tests/firedrake_extrusion_project/test_firedrake_extrusion_project.py 1970-01-01 00:00:00 +0000
1631+++ tests/firedrake_extrusion_project/test_firedrake_extrusion_project.py 2013-10-03 16:15:40 +0000
1632@@ -0,0 +1,45 @@
1633+"""This demo program projects an analytic expression into a function space
1634+"""
1635+
1636+# Begin demo
1637+from firedrake import *
1638+import sys
1639+
1640+power = int(sys.argv[1])
1641+# Create mesh and define function space
1642+m = UnitSquareMesh(2**power,2**power)
1643+layers = 2**int(sys.argv[1])+1
1644+
1645+# Populate the coordinates of the extruded mesh by providing the
1646+#coordinates as a field.
1647+extrusion_kernel = """
1648+void extrusion_kernel(double *xtr[], double *x[], int* j[])
1649+{
1650+ //Only the Z-coord is increased, the others stay the same
1651+ xtr[0][0] = x[0][0];
1652+ xtr[0][1] = x[0][1];
1653+ xtr[0][2] = %(height)s*j[0][0];
1654+}""" % { 'height' : str(1.0/2**int(sys.argv[1])) }
1655+
1656+mesh = ExtrudedMesh(m, layers, extrusion_kernel)
1657+V = FunctionSpace(mesh, "Lagrange", 1, vfamily="DG", vdegree=0)
1658+W = FunctionSpace(mesh, "Lagrange", 3, vfamily="Lagrange", vdegree=3)
1659+
1660+# Define variational problem
1661+u = TrialFunction(V)
1662+v = TestFunction(V)
1663+f = Function(V)
1664+g = Function(W)
1665+f.interpolate(Expression("cos(x[0]*pi*2)*cos(x[1]*pi*2)*cos(x[2]*pi*2)"))
1666+g.interpolate(Expression("cos(x[0]*pi*2)*cos(x[1]*pi*2)*cos(x[2]*pi*2)"))
1667+a = u*v*dx
1668+L = f*v*dx
1669+x = Function(V)
1670+solve(a==L, x)
1671+
1672+print sqrt(assemble((x-g)*(x-g)*dx))
1673+
1674+# Save solution in VTK format
1675+#file = File("helmholtz.pvd")
1676+#file << x
1677+#file << f
1678\ No newline at end of file
1679
1680=== added directory 'tests/firedrake_extrusion_rhs'
1681=== added file 'tests/firedrake_extrusion_rhs/Makefile'
1682--- tests/firedrake_extrusion_rhs/Makefile 1970-01-01 00:00:00 +0000
1683+++ tests/firedrake_extrusion_rhs/Makefile 2013-10-03 16:15:40 +0000
1684@@ -0,0 +1,5 @@
1685+input: clean
1686+
1687+clean:
1688+ rm -f square* *.vtu *.pvd *.s *.d.1 *.stat *.log-0 *.err-0 \
1689+ matrixdump matrixdump.info
1690
1691=== added file 'tests/firedrake_extrusion_rhs/firedrake_rhs.xml'
1692--- tests/firedrake_extrusion_rhs/firedrake_rhs.xml 1970-01-01 00:00:00 +0000
1693+++ tests/firedrake_extrusion_rhs/firedrake_rhs.xml 2013-10-03 16:15:40 +0000
1694@@ -0,0 +1,19 @@
1695+<?xml version='1.0' encoding='utf-8'?>
1696+<testproblem>
1697+ <name>identity</name>
1698+ <owner userid="gb308"/>
1699+ <tags>firedrake</tags>
1700+ <problem_definition length="short" nprocs="1">
1701+ <command_line>true</command_line>
1702+ </problem_definition>
1703+ <variables>
1704+ <variable name="result" language="python">
1705+import test_firedrake_rhs as test
1706+result = test.run_test()
1707+ </variable>
1708+ </variables>
1709+ <pass_tests>
1710+ <test name="Unit Extruded Square Integration value." language="python">assert result[0] == "0.5"</test>
1711+ </pass_tests>
1712+ <warn_tests/>
1713+</testproblem>
1714
1715=== added file 'tests/firedrake_extrusion_rhs/test_firedrake_rhs.py'
1716--- tests/firedrake_extrusion_rhs/test_firedrake_rhs.py 1970-01-01 00:00:00 +0000
1717+++ tests/firedrake_extrusion_rhs/test_firedrake_rhs.py 2013-10-03 16:15:40 +0000
1718@@ -0,0 +1,62 @@
1719+from firedrake import *
1720+import numpy as np
1721+import pyop2 as op2
1722+import ufl
1723+
1724+power = 5
1725+m = UnitSquareMesh(2**power,2**power)
1726+layers = 11
1727+
1728+# Populate the coordinates of the extruded mesh by providing the
1729+#coordinates as a field.
1730+# TODO: provide a kernel which will describe how coordinates are extruded.
1731+extrusion_kernel = """
1732+void extrusion_kernel(double *xtr[], double *x[], int* j[])
1733+{
1734+ //Only the Z-coord is increased, the others stay the same
1735+ xtr[0][0] = x[0][0];
1736+ xtr[0][1] = x[0][1];
1737+ xtr[0][2] = 0.1*j[0][0];
1738+}"""
1739+
1740+mesh = firedrake.ExtrudedMesh(m, layers, extrusion_kernel)
1741+
1742+#import pyop2.configuration as cfg
1743+#cfg.configure(debug=1)
1744+
1745+def integrate_rhs(family, degree):
1746+ horiz = ufl.FiniteElement(family, None, degree)
1747+ vert = ufl.FiniteElement(family, None, degree)
1748+ prod = ufl.OuterProductElement(horiz, vert)
1749+
1750+ fs = firedrake.FunctionSpace(mesh, prod, name="fs")
1751+
1752+ f = firedrake.Function(fs)
1753+
1754+ populate_p0 = op2.Kernel("""
1755+void populate_tracer(double *x[], double *c[])
1756+{
1757+ x[0][0] = ((c[1][2] + c[0][2]) / 2);
1758+}""", "populate_tracer")
1759+
1760+ coords = f.function_space().mesh()._coordinate_field
1761+
1762+ op2.par_loop(populate_p0, f.cell_set,
1763+ f.dat(op2.INC, f.cell_node_map),
1764+ coords.dat(op2.READ, coords.cell_node_map))
1765+
1766+ g = firedrake.assemble(f*firedrake.dx)
1767+
1768+ return str(g)
1769+
1770+def run_test():
1771+ family = "DG"
1772+ degree = 0
1773+
1774+ return [integrate_rhs(family, degree)]
1775+
1776+if __name__=="__main__":
1777+
1778+ result = run_test()
1779+ for i, res in enumerate(result):
1780+ print "Result for extruded unit cube integration "+`i+1`+": "+`res`
1781
1782=== added directory 'tests/firedrake_extrusion_two_step'
1783=== added file 'tests/firedrake_extrusion_two_step/Makefile'
1784--- tests/firedrake_extrusion_two_step/Makefile 1970-01-01 00:00:00 +0000
1785+++ tests/firedrake_extrusion_two_step/Makefile 2013-10-03 16:15:40 +0000
1786@@ -0,0 +1,5 @@
1787+input: clean
1788+
1789+clean:
1790+ rm -f square* *.vtu *.pvd *.s *.d.1 *.stat *.log-0 *.err-0 \
1791+ matrixdump matrixdump.info
1792
1793=== added file 'tests/firedrake_extrusion_two_step/firedrake_extrusion_two_step.xml'
1794--- tests/firedrake_extrusion_two_step/firedrake_extrusion_two_step.xml 1970-01-01 00:00:00 +0000
1795+++ tests/firedrake_extrusion_two_step/firedrake_extrusion_two_step.xml 2013-10-03 16:15:40 +0000
1796@@ -0,0 +1,19 @@
1797+<?xml version='1.0' encoding='utf-8'?>
1798+<testproblem>
1799+ <name>identity</name>
1800+ <owner userid="gb308"/>
1801+ <tags>firedrake</tags>
1802+ <problem_definition length="short" nprocs="1">
1803+ <command_line>true</command_line>
1804+ </problem_definition>
1805+ <variables>
1806+ <variable name="result" language="python">
1807+import test_firedrake_extrusion_two_step as test
1808+result = test.run_test()
1809+ </variable>
1810+ </variables>
1811+ <pass_tests>
1812+ <test name="Unit Extruded Square Integration value." language="python">assert result[0] &lt; 0.0002</test>
1813+ </pass_tests>
1814+ <warn_tests/>
1815+</testproblem>
1816
1817=== added file 'tests/firedrake_extrusion_two_step/test_firedrake_extrusion_two_step.py'
1818--- tests/firedrake_extrusion_two_step/test_firedrake_extrusion_two_step.py 1970-01-01 00:00:00 +0000
1819+++ tests/firedrake_extrusion_two_step/test_firedrake_extrusion_two_step.py 2013-10-03 16:15:40 +0000
1820@@ -0,0 +1,84 @@
1821+"""Testing RT stuff
1822+"""
1823+
1824+# Begin demo
1825+from firedrake import *
1826+
1827+power = 4
1828+# Create mesh and define function space
1829+m = UnitSquareMesh(2**power,2**power)
1830+layers = 11
1831+
1832+# Populate the coordinates of the extruded mesh by providing the
1833+#coordinates as a field.
1834+extrusion_kernel = """
1835+void extrusion_kernel(double *xtr[], double *x[], int* j[])
1836+{
1837+ //Only the Z-coord is increased, the others stay the same
1838+ xtr[0][0] = x[0][0];
1839+ xtr[0][1] = x[0][1];
1840+ xtr[0][2] = 0.1*j[0][0];
1841+}"""
1842+
1843+mesh = ExtrudedMesh(m, layers, extrusion_kernel)
1844+
1845+def two_step():
1846+ V = FunctionSpace(mesh, "Lagrange", 2, vfamily="DG", vdegree=0)
1847+ W = FunctionSpace(mesh, "BDM", 1, vfamily="DG", vdegree=0)
1848+ X = FunctionSpace(mesh, "DG", 0, vfamily="DG", vdegree=0)
1849+
1850+ # Define starting field
1851+ f0 = Function(V)
1852+ f0.interpolate(Expression("1 + x[0]*x[0] + x[1]*x[1]"))
1853+
1854+ # DO IN ONE STEP
1855+ u = TrialFunction(X)
1856+ v = TestFunction(X)
1857+ a = u*v*dx
1858+ L = div(grad(f0))*v*dx
1859+
1860+ A = assemble(a)
1861+ b = assemble(L)
1862+ f_e = Function(X)
1863+ solve(a==L, f_e)
1864+ #print "One step:"
1865+ #print f_e.dat.data
1866+
1867+ # DO IN TWO STEPS
1868+ u = TrialFunction(W)
1869+ v = TestFunction(W)
1870+ a = dot(u,v)*dx
1871+ L = dot(grad(f0),v)*dx
1872+
1873+ # Compute solution
1874+ A = assemble(a)
1875+ b = assemble(L)
1876+ f1 = Function(W)
1877+ solve(a==L, f1)
1878+ # x should be (2x, 2y) but we have no way of checking............
1879+
1880+ u = TrialFunction(X)
1881+ v = TestFunction(X)
1882+ a = u*v*dx
1883+ L = div(f1)*v*dx
1884+
1885+ # Compute solution
1886+ A = assemble(a)
1887+ b = assemble(L)
1888+ f2 = Function(X)
1889+ solve(a==L, f2)
1890+
1891+ #print "Two steps:"
1892+ #print f2.dat.data
1893+
1894+ return sum(f2.dat.data - f_e.dat.data)
1895+
1896+
1897+def run_test():
1898+ return [two_step()]
1899+
1900+if __name__=="__main__":
1901+
1902+ result = run_test()
1903+ for i, res in enumerate(result):
1904+ print "Result for extruded two step error "+`i+1`+": "+`res`
1905\ No newline at end of file
1906
1907=== added directory 'tests/firedrake_extrusion_unit_cube'
1908=== added file 'tests/firedrake_extrusion_unit_cube/Makefile'
1909--- tests/firedrake_extrusion_unit_cube/Makefile 1970-01-01 00:00:00 +0000
1910+++ tests/firedrake_extrusion_unit_cube/Makefile 2013-10-03 16:15:40 +0000
1911@@ -0,0 +1,5 @@
1912+input: clean
1913+
1914+clean:
1915+ rm -f square* *.vtu *.pvd *.s *.d.1 *.stat *.log-0 *.err-0 \
1916+ matrixdump matrixdump.info
1917
1918=== added file 'tests/firedrake_extrusion_unit_cube/firedrake_unit_cube.xml'
1919--- tests/firedrake_extrusion_unit_cube/firedrake_unit_cube.xml 1970-01-01 00:00:00 +0000
1920+++ tests/firedrake_extrusion_unit_cube/firedrake_unit_cube.xml 2013-10-03 16:15:40 +0000
1921@@ -0,0 +1,19 @@
1922+<?xml version='1.0' encoding='utf-8'?>
1923+<testproblem>
1924+ <name>identity</name>
1925+ <owner userid="gb308"/>
1926+ <tags>ufl</tags>
1927+ <problem_definition length="short" nprocs="1">
1928+ <command_line>true</command_line>
1929+ </problem_definition>
1930+ <variables>
1931+ <variable name="result" language="python">
1932+import test_firedrake_unit_cube as test
1933+result = test.run_test()
1934+ </variable>
1935+ </variables>
1936+ <pass_tests>
1937+ <test name="Unit Extruded Square Integration value." language="python">assert result[0] == "1.0"</test>
1938+ </pass_tests>
1939+ <warn_tests/>
1940+</testproblem>
1941
1942=== added file 'tests/firedrake_extrusion_unit_cube/test_firedrake_unit_cube.py'
1943--- tests/firedrake_extrusion_unit_cube/test_firedrake_unit_cube.py 1970-01-01 00:00:00 +0000
1944+++ tests/firedrake_extrusion_unit_cube/test_firedrake_unit_cube.py 2013-10-03 16:15:40 +0000
1945@@ -0,0 +1,64 @@
1946+from firedrake import *
1947+import numpy as np
1948+import pyop2 as op2
1949+
1950+power = 5
1951+m = UnitSquareMesh(2**power,2**power)
1952+layers = 11
1953+
1954+# Populate the coordinates of the extruded mesh by providing the
1955+# coordinates as a field.
1956+# A kernel which describes how coordinates are extruded.
1957+extrusion_kernel = """
1958+void extrusion_kernel(double *xtr[], double *x[], int* j[])
1959+{
1960+ //Only the Z-coord is increased, the others stay the same
1961+ xtr[0][0] = x[0][0];
1962+ xtr[0][1] = x[0][1];
1963+ xtr[0][2] = 0.1*j[0][0];
1964+}"""
1965+
1966+mesh = firedrake.ExtrudedMesh(m, layers, extrusion_kernel)
1967+
1968+def integrate_unit_cube(family, degree):
1969+ fs = firedrake.FunctionSpace(mesh, family, degree, name="fs")
1970+
1971+ f = firedrake.Function(fs)
1972+
1973+ volume = op2.Kernel("""
1974+void comp_vol(double A[1], double *x[], double *y[])
1975+{
1976+ double area = x[0][0]*(x[2][1]-x[4][1]) + x[2][0]*(x[4][1]-x[0][1])
1977+ + x[4][0]*(x[0][1]-x[2][1]);
1978+ if (area < 0)
1979+ area = area * (-1.0);
1980+ A[0] += 0.5 * area * (x[1][2] - x[0][2]);
1981+}""", "comp_vol")
1982+
1983+ g = op2.Global(1, data=0.0, name='g')
1984+
1985+ coords = f.function_space().mesh()._coordinate_field
1986+
1987+ op2.par_loop(volume, f.cell_set,
1988+ g(op2.INC),
1989+ coords.dat(op2.READ, coords.cell_node_map),
1990+ f.dat(op2.READ, f.cell_node_map)
1991+ )
1992+
1993+ return str(g.data[0])
1994+
1995+def run_test():
1996+ family = "Lagrange"
1997+ degree = range(1,2)
1998+
1999+ result = []
2000+ for d in degree:
2001+ result.append(integrate_unit_cube(family, d))
2002+ return result
2003+
2004+
2005+if __name__=="__main__":
2006+
2007+ result = run_test()
2008+ for i, res in enumerate(result):
2009+ print "Result for extruded unit cube integration "+`i+1`+": "+`res`
2010
2011=== added directory 'tests/firedrake_extrusion_var_p0'
2012=== added file 'tests/firedrake_extrusion_var_p0/Makefile'
2013--- tests/firedrake_extrusion_var_p0/Makefile 1970-01-01 00:00:00 +0000
2014+++ tests/firedrake_extrusion_var_p0/Makefile 2013-10-03 16:15:40 +0000
2015@@ -0,0 +1,5 @@
2016+input: clean
2017+
2018+clean:
2019+ rm -f square* *.vtu *.pvd *.s *.d.1 *.stat *.log-0 *.err-0 \
2020+ matrixdump matrixdump.info
2021
2022=== added file 'tests/firedrake_extrusion_var_p0/firedrake_var_p0.xml'
2023--- tests/firedrake_extrusion_var_p0/firedrake_var_p0.xml 1970-01-01 00:00:00 +0000
2024+++ tests/firedrake_extrusion_var_p0/firedrake_var_p0.xml 2013-10-03 16:15:40 +0000
2025@@ -0,0 +1,19 @@
2026+<?xml version='1.0' encoding='utf-8'?>
2027+<testproblem>
2028+ <name>identity</name>
2029+ <owner userid="gb308"/>
2030+ <tags>ufl</tags>
2031+ <problem_definition length="short" nprocs="1">
2032+ <command_line>true</command_line>
2033+ </problem_definition>
2034+ <variables>
2035+ <variable name="result" language="python">
2036+import test_firedrake_var_p0 as test
2037+result = test.run_test()
2038+ </variable>
2039+ </variables>
2040+ <pass_tests>
2041+ <test name="Unit Extruded Square Integration value." language="python">assert result[0] == "0.5"</test>
2042+ </pass_tests>
2043+ <warn_tests/>
2044+</testproblem>
2045
2046=== added file 'tests/firedrake_extrusion_var_p0/test_firedrake_var_p0.py'
2047--- tests/firedrake_extrusion_var_p0/test_firedrake_var_p0.py 1970-01-01 00:00:00 +0000
2048+++ tests/firedrake_extrusion_var_p0/test_firedrake_var_p0.py 2013-10-03 16:15:40 +0000
2049@@ -0,0 +1,74 @@
2050+from firedrake import *
2051+import numpy as np
2052+import pyop2 as op2
2053+
2054+power = 5
2055+m = UnitSquareMesh(2**power,2**power)
2056+layers = 11
2057+
2058+# Populate the coordinates of the extruded mesh by providing the
2059+#coordinates as a field.
2060+# TODO: provide a kernel which will describe how coordinates are extruded.
2061+extrusion_kernel = """
2062+void extrusion_kernel(double *xtr[], double *x[], int* j[])
2063+{
2064+ //Only the Z-coord is increased, the others stay the same
2065+ xtr[0][0] = x[0][0];
2066+ xtr[0][1] = x[0][1];
2067+ xtr[0][2] = 0.1*j[0][0];
2068+}"""
2069+
2070+mesh = firedrake.ExtrudedMesh(m, layers, extrusion_kernel)
2071+
2072+#import pyop2.configuration as cfg
2073+#cfg.configure(debug=1)
2074+
2075+def integrate_var_p0(family, degree):
2076+ fs = firedrake.FunctionSpace(mesh, family, degree, name="fs")
2077+
2078+ f = firedrake.Function(fs)
2079+
2080+ populate_p0 = op2.Kernel("""
2081+void populate_tracer(double *x[], double *c[])
2082+{
2083+ //printf("%f %f \\n", c[1][2], c[0][2]);
2084+ x[0][0] = (c[1][2] + c[0][2]) / 2;
2085+}""", "populate_tracer")
2086+
2087+ coords = f.function_space().mesh()._coordinate_field
2088+
2089+ op2.par_loop(populate_p0, f.cell_set,
2090+ f.dat(op2.INC, f.cell_node_map),
2091+ coords.dat(op2.READ, coords.cell_node_map))
2092+
2093+ volume = op2.Kernel("""
2094+void comp_vol(double A[1], double *x[], double *y[])
2095+{
2096+ double area = x[0][0]*(x[2][1]-x[4][1]) + x[2][0]*(x[4][1]-x[0][1])
2097+ + x[4][0]*(x[0][1]-x[2][1]);
2098+ if (area < 0)
2099+ area = area * (-1.0);
2100+ A[0] += 0.5 * area * (x[1][2] - x[0][2]) * y[0][0];
2101+}""", "comp_vol")
2102+
2103+ g = op2.Global(1, data=0.0, name='g')
2104+
2105+ op2.par_loop(volume, f.cell_set,
2106+ g(op2.INC),
2107+ coords.dat(op2.READ, coords.cell_node_map),
2108+ f.dat(op2.READ, f.cell_node_map)
2109+ )
2110+
2111+ return str(g.data[0])
2112+
2113+def run_test():
2114+ family = "DG"
2115+ degree = 0
2116+
2117+ return [integrate_var_p0(family, degree)]
2118+
2119+if __name__=="__main__":
2120+
2121+ result = run_test()
2122+ for i, res in enumerate(result):
2123+ print "Result for extruded unit cube integration "+`i+1`+": "+`res`
2124
2125=== modified file 'tests/firedrake_identity/firedrake_identity.xml'
2126--- tests/firedrake_identity/firedrake_identity.xml 2013-09-20 09:37:44 +0000
2127+++ tests/firedrake_identity/firedrake_identity.xml 2013-10-03 16:15:40 +0000
2128@@ -13,7 +13,7 @@
2129 </variable>
2130 </variables>
2131 <pass_tests>
2132- <test name="Error inf norm. degree 1" language="python">assert error[0] &lt; 1.0e-14</test>
2133+ <test name="Error inf norm. degree 1" language="python">assert error[0] &lt; 1.0e-15</test>
2134 <test name="Error inf norm. degree 2" language="python">assert error[1] &lt; 1.0e-6</test>
2135 <test name="Error inf norm. degree 3" language="python">assert error[2] &lt; 1.0e-6</test>
2136 <test name="Error inf norm. degree 4" language="python">assert error[3] &lt; 1.0e-5</test>
2137
2138=== modified file 'tests/firedrake_identity/test_firedrake_identity.py'
2139--- tests/firedrake_identity/test_firedrake_identity.py 2013-09-19 14:51:06 +0000
2140+++ tests/firedrake_identity/test_firedrake_identity.py 2013-10-03 16:15:40 +0000
2141@@ -2,7 +2,6 @@
2142 import numpy as np
2143 mesh = firedrake.UnitCubeMesh(1, 1, 1)
2144
2145-
2146 def identity(family, degree):
2147 fs = firedrake.FunctionSpace(mesh, family, degree)
2148
2149
2150=== modified file 'tests/firedrake_identity_parallel/firedrake_identity_parallel.xml'
2151--- tests/firedrake_identity_parallel/firedrake_identity_parallel.xml 2013-09-20 09:37:44 +0000
2152+++ tests/firedrake_identity_parallel/firedrake_identity_parallel.xml 2013-10-03 16:15:40 +0000
2153@@ -14,7 +14,7 @@
2154 </variable>
2155 </variables>
2156 <pass_tests>
2157- <test name="Error inf norm. degree 1" language="python">assert error[0] &lt; 1.0e-14</test>
2158+ <test name="Error inf norm. degree 1" language="python">assert error[0] &lt; 1.0e-15</test>
2159 <test name="Error inf norm. degree 2" language="python">assert error[1] &lt; 1.0e-6</test>
2160 <test name="Error inf norm. degree 3" language="python">assert error[2] &lt; 1.0e-6</test>
2161 <test name="Error inf norm. degree 4" language="python">assert error[3] &lt; 1.0e-5</test>

Subscribers

People subscribed via source and target branches