source: codes/icosagcm/devel/src/sphere/compute_geometry.f90

Last change on this file was 1026, checked in by dubos, 4 years ago

devel : towards conformity to F2008 standard

File size: 16.7 KB
Line 
1MODULE compute_geometry_mod
2  USE geometry
3  USE dimensions
4
5  USE domain_mod, ONLY : t_domain, t_cellset, &
6       domain, ndomain, assigned_domain, &
7       domain_glo, ndomain_glo, domloc_glo_ind, swap_needed
8  USE omp_para, ONLY : is_omp_level_master, is_master
9  USE transfert_mod, ONLY : req_i0, req_i1, t_message, transfert_request, transfert_message, init_message
10
11  USE spherical_geom_mod, ONLY : xyz2lonlat, circumcenter, compute_centroid, &
12       surf_triangle, dist_cart, div_arc_bis, schmidt_transform
13  USE vector, ONLY : norm, cross_product2
14
15  IMPLICIT NONE
16  PRIVATE
17  SAVE
18
19  PUBLIC :: compute_geometry
20
21CONTAINS
22
23  SUBROUTINE update_circumcenters 
24
25    REAL(rstd) :: x1(3),x2(3)
26    REAL(rstd) :: vect(3,6)
27    REAL(rstd) :: centr(3)
28    INTEGER :: ind,i,j,n,k
29    TYPE(t_message),SAVE :: message0, message1
30    LOGICAL, SAVE :: first=.TRUE.
31!$OMP THREADPRIVATE(first)   
32   
33    IF (first) THEN
34      CALL init_message(geom%xyz_i, req_i0 ,message0)
35      CALL init_message(geom%xyz_i, req_i1 ,message1)
36      first=.FALSE.
37    ENDIF
38   
39    CALL transfert_message(geom%xyz_i,message0)
40    CALL transfert_message(geom%xyz_i,message1)
41   
42    DO ind=1,ndomain
43
44      CALL swap_dimensions(ind)
45      CALL swap_geometry(ind)
46      DO j=jj_begin,jj_end
47        DO i=ii_begin,ii_end
48          n=(j-1)*iim+i
49          DO k=0,5
50            x1(:) = xyz_i(n+t_pos(k+1),:)
51            x2(:) = xyz_i(n+t_pos(MOD(k+1,6)+1),:)
52            if (norm(x1-x2)<1e-16) x2(:) = xyz_i(n+t_pos(MOD(k+2,6)+1),:)
53            CALL circumcenter(xyz_i(n,:), x1, x2, xyz_v(n+z_pos(k+1),:))
54          ENDDO
55        ENDDO
56      ENDDO
57    ENDDO
58
59  END SUBROUTINE update_circumcenters
60
61  SUBROUTINE remap_schmidt_loc
62    USE getin_mod
63    INTEGER :: ind,i,j,n
64    REAL(rstd) :: schmidt_factor, schmidt_lon, schmidt_lat
65
66    ! Schmidt transform parameters
67    schmidt_factor = 1.
68    CALL getin('schmidt_factor', schmidt_factor)
69    schmidt_factor =  schmidt_factor**2.
70   
71    schmidt_lon = 0.
72    CALL getin('schmidt_lon', schmidt_lon)
73    schmidt_lon = schmidt_lon * pi/180.
74
75    schmidt_lat = 45.
76    CALL getin('schmidt_lat', schmidt_lat)
77    schmidt_lat = schmidt_lat * pi/180.
78
79    DO ind=1,ndomain
80      IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE
81      CALL swap_dimensions(ind)
82      CALL swap_geometry(ind)
83      DO j=jj_begin,jj_end
84        DO i=ii_begin,ii_end
85          n=(j-1)*iim+i
86          CALL schmidt_transform(xyz_i(n,:), schmidt_factor, schmidt_lon, schmidt_lat)
87        ENDDO
88      ENDDO
89    ENDDO
90  END SUBROUTINE remap_schmidt_loc
91
92  SUBROUTINE optimize_geometry
93  USE getin_mod
94    INTEGER :: nb_it=0
95    TYPE(t_domain),POINTER :: d
96    INTEGER :: ind,it,i,j,n,k
97    REAL(rstd) :: x1(3),x2(3)
98    REAL(rstd) :: vect(3,6)
99    REAL(rstd) :: centr(3)
100    REAL(rstd) :: sum
101    LOGICAL    :: check
102   
103   
104    CALL getin('optim_it',nb_it)
105   
106    DO ind=1,ndomain
107      IF (.NOT. assigned_domain(ind)  .OR. .NOT. is_omp_level_master) CYCLE
108      d=>domain(ind)
109      CALL swap_dimensions(ind)
110      CALL swap_geometry(ind)
111      xyz_i(:,1) = 0 ; xyz_i(:,2) = 0 ;  xyz_i(:,3) = 1
112     
113      DO j=jj_begin,jj_end
114        DO i=ii_begin,ii_end
115          n=(j-1)*iim+i
116          xyz_i(n,:)=d%xyz(:,i,j) 
117        ENDDO
118      ENDDO
119    ENDDO
120   
121    CALL update_circumcenters
122
123!ym you get discrepency if you try to read metric from file, vertex are not saved in file
124!    DO ind=1,ndomain
125!      IF (.NOT. assigned_domain(ind)  .OR. .NOT. is_omp_level_master ) CYCLE
126!      d=>domain(ind)
127!      CALL swap_dimensions(ind)
128!      CALL swap_geometry(ind)
129!      DO j=jj_begin,jj_end
130!        DO i=ii_begin,ii_end
131!          n=(j-1)*iim+i
132!          DO k=0,5
133!            x1(:) = xyz_v(n+z_pos(k+1),:)
134!            x2(:) = d%vertex(:,k,i,j)
135!            IF (norm(x1-x2)>1e-10) THEN
136!              PRINT*,"vertex diff ",ind,i,j,k
137!              PRINT*,x1
138!              PRINT*,x2
139!            ENDIF
140!          ENDDO
141!        ENDDO
142!      ENDDO
143!   ENDDO
144   
145   
146    DO it=1,nb_it
147      IF (MOD(it,100)==0) THEN
148        check=is_master
149      ELSE
150        check=.FALSE.
151      ENDIF
152     
153      sum=0
154      DO ind=1,ndomain
155      IF (.NOT. assigned_domain(ind)  .OR. .NOT. is_omp_level_master ) CYCLE
156        CALL swap_dimensions(ind)
157        CALL swap_geometry(ind)
158        DO j=jj_begin,jj_end
159          DO i=ii_begin,ii_end
160            n=(j-1)*iim+i
161            vect(:,1)=xyz_v(n+z_rup,:)
162            vect(:,2)=xyz_v(n+z_up,:)
163            vect(:,3)=xyz_v(n+z_lup,:)
164            vect(:,4)=xyz_v(n+z_ldown,:)
165            vect(:,5)=xyz_v(n+z_down,:)
166            vect(:,6)=xyz_v(n+z_rdown,:)
167            CALL compute_centroid(vect,6,centr)
168            IF (check) THEN
169              sum=MAX(sum,norm(xyz_i(n,:)-centr(:)))
170            ENDIF
171            xyz_i(n,:)=centr(:)
172          ENDDO
173        ENDDO
174       
175      ENDDO
176
177      IF (check) PRINT *,"it = ",it,"  diff centroid circumcenter ",sum
178
179     CALL update_circumcenters
180
181    ENDDO
182   
183  END SUBROUTINE optimize_geometry
184
185  SUBROUTINE update_domain 
186    ! copy position of generators and vertices back into domain(:)%xyz/vertex
187    ! so that XIOS/create_header_gen gets the right values
188    USE transfert_mpi_mod, ONLY : gather_field, bcast_field
189
190    INTEGER :: ind,i,j,k,n
191    TYPE(t_domain),POINTER :: d
192    TYPE(t_field),POINTER,SAVE :: xyz_glo(:), xyz_loc(:), vertex_glo(:), vertex_loc(:)
193    REAL(rstd), POINTER :: xyz(:,:), vertex(:,:)
194   
195    CALL allocate_field(xyz_loc, field_t, type_real, 3)
196    CALL allocate_field(vertex_loc, field_z, type_real, 3)
197
198    DO ind=1,ndomain
199       IF (.NOT. assigned_domain(ind)  .OR. .NOT. is_omp_level_master ) CYCLE
200       CALL swap_dimensions(ind)
201       CALL swap_geometry(ind)
202       xyz = xyz_loc(ind)
203       xyz(:,:) = xyz_i(:,:)
204       vertex = vertex_loc(ind)
205       vertex(:,:) = xyz_v(:,:)
206    END DO
207
208!$OMP BARRIER   
209!$OMP MASTER
210    CALL allocate_field_glo(xyz_glo, field_t, type_real, 3)
211    CALL allocate_field_glo(vertex_glo, field_z, type_real, 3)
212
213    CALL gather_field(xyz_loc, xyz_glo)
214    CALL gather_field(vertex_loc, vertex_glo)
215
216    CALL bcast_field(xyz_glo)
217    CALL bcast_field(vertex_glo)
218
219    DO ind=1,ndomain_glo
220       d=>domain_glo(ind)
221       xyz = xyz_glo(ind)
222       vertex = vertex_glo(ind)
223       DO j=d%jj_begin,d%jj_end
224          DO i=d%ii_begin,d%ii_end         
225             n=(j-1)*d%iim+i
226             d%xyz(:,i,j)=xyz(n,:)
227             DO k=0,5
228                d%vertex(:,k,i,j) = vertex(n+d%z_pos(k+1),:)
229             END DO
230          END DO
231       END DO
232    END DO
233
234    CALL deallocate_field_glo(vertex_glo)
235    CALL deallocate_field_glo(xyz_glo)
236!$OMP END MASTER
237!$OMP BARRIER
238    CALL deallocate_field(vertex_loc)
239    CALL deallocate_field(xyz_loc)
240
241  END SUBROUTINE update_domain
242 
243  SUBROUTINE set_geometry
244  USE metric
245
246    REAL(rstd) :: surf(6)
247    REAL(rstd) :: surf_v(6)
248    REAL(rstd) :: vect(3,6)
249    REAL(rstd) :: centr(3)
250    REAL(rstd) :: vet(3),vep(3), vertex(3)
251    INTEGER :: ind,i,j,k,n
252    TYPE(t_domain),POINTER :: d
253    REAL(rstd) ::  S12
254    REAL(rstd) :: w(6)
255    REAL(rstd) :: lon,lat
256    INTEGER :: ii_glo,jj_glo
257    REAL(rstd) :: S
258         
259     
260    CALL optimize_geometry
261    CALL remap_schmidt_loc
262    CALL update_circumcenters
263
264    DO ind=1,ndomain
265      IF (.NOT. assigned_domain(ind)  .OR. .NOT. is_omp_level_master ) CYCLE
266      d=>domain(ind)
267      CALL swap_dimensions(ind)
268      CALL swap_geometry(ind)
269      lon_i(:)=0 ; lat_i(:)=0
270      lon_e(:)=0 ; lat_e(:)=0
271      DO j=jj_begin-1,jj_end+1
272        DO i=ii_begin-1,ii_end+1
273          n=(j-1)*iim+i
274
275          DO k=0,5
276            ne(n,k+1)=d%ne(k,i,j)
277          ENDDO
278
279          vect(:,1)=xyz_v(n+z_rup,:)
280          vect(:,2)=xyz_v(n+z_up,:)
281          vect(:,3)=xyz_v(n+z_lup,:)
282          vect(:,4)=xyz_v(n+z_ldown,:)
283          vect(:,5)=xyz_v(n+z_down,:)
284          vect(:,6)=xyz_v(n+z_rdown,:)
285          CALL compute_centroid(vect,6,centr)
286          centroid(n,:)=centr(:)
287
288               
289          CALL xyz2lonlat(xyz_v(n+z_up,:),lon,lat)
290          fv(n+z_up)=2*sin(lat)*omega
291          CALL xyz2lonlat(xyz_v(n+z_down,:),lon,lat)
292          fv(n+z_down)=2*sin(lat)*omega
293         
294          bi(n)=0. 
295       
296          CALL dist_cart(xyz_i(n,:),xyz_i(n+t_right,:),de(n+u_right))
297          CALL dist_cart(xyz_i(n,:),xyz_i(n+t_lup,:),de(n+u_lup))
298          CALL dist_cart(xyz_i(n,:),xyz_i(n+t_ldown,:),de(n+u_ldown))
299         
300          CALL div_arc_bis(xyz_i(n,:),xyz_i(n+t_right,:),0.5,xyz_e(n+u_right,:))
301          CALL div_arc_bis(xyz_i(n,:),xyz_i(n+t_lup,:),0.5,xyz_e(n+u_lup,:))
302          CALL div_arc_bis(xyz_i(n,:),xyz_i(n+t_ldown,:),0.5,xyz_e(n+u_ldown,:))
303
304          CALL dist_cart(xyz_v(n+z_rdown,:), xyz_v(n+z_rup,:),le(n+u_right))
305          CALL dist_cart(xyz_v(n+z_up,:), xyz_v(n+z_lup,:),le(n+u_lup))
306          CALL dist_cart(xyz_v(n+z_ldown,:), xyz_v(n+z_down,:),le(n+u_ldown))
307
308          le_de(n+u_right)=le(n+u_right)/de(n+u_right) ! NaN possible but should be harmless
309          le_de(n+u_lup)  =le(n+u_lup)  /de(n+u_lup)
310          le_de(n+u_ldown)=le(n+u_ldown)/de(n+u_ldown)
311
312          Ai(n)=0
313          DO k=0,5
314            CALL surf_triangle(xyz_i(n,:),xyz_i(n+t_pos(k+1),:),xyz_i(n+t_pos(MOD((k+1+6),6)+1),:),surf_v(k+1))
315            CALL surf_triangle(xyz_i(n,:),xyz_v(n+z_pos(MOD((k-1+6),6)+1),:),xyz_v(n+z_pos(k+1),:),surf(k+1))
316            Ai(n)=Ai(n)+surf(k+1)
317            IF (i==ii_end .AND. j==jj_begin) THEN
318              IF (Ai(n)<1e20) THEN
319              ELSE
320                PRINT *,"PB !!",Ai(n),k,surf(k+1)
321                PRINT*,xyz_i(n,:),xyz_v(n+z_pos(MOD((k-1+6),6)+1),:),xyz_v(n+z_pos(k+1),:)
322              ENDIF
323            ENDIF
324          ENDDO
325
326          ! Sign convention : Ringler et al., JCP 2010, eq. 21 p. 3071
327          ! Normal component is along outgoing normal vector if ne=1
328
329          CALL cross_product2(xyz_v(n+z_rdown,:),xyz_v(n+z_rup,:),vep)
330          IF (norm(vep)>1e-30) THEN
331            vep(:)=vep(:)/norm(vep)                         ! Inward normal vector
332            CALL cross_product2(vep,xyz_e(n+u_right,:),vet) ! Counter-clockwise tangent vector
333            vet(:)=vet(:)/norm(vet)
334            ep_e(n+u_right,:)=-vep(:)*ne(n,right)
335            et_e(n+u_right,:)=vet(:)*ne(n,right)
336          ENDIF
337
338          CALL cross_product2(xyz_v(n+z_up,:),xyz_v(n+z_lup,:),vep)
339          IF (norm(vep)>1e-30) THEN
340            vep(:)=vep(:)/norm(vep)
341            CALL cross_product2(vep,xyz_e(n+u_lup,:),vet)
342            vet(:)=vet(:)/norm(vet)
343            ep_e(n+u_lup,:)=-vep(:)*ne(n,lup)
344            et_e(n+u_lup,:)=vet(:)*ne(n,lup)
345          ENDIF
346
347          CALL cross_product2(xyz_v(n+z_ldown,:),xyz_v(n+z_down,:),vep)
348          IF (norm(vep)>1e-30) THEN
349            vep(:)=vep(:)/norm(vep)
350            CALL cross_product2(vep,xyz_e(n+u_ldown,:),vet)
351            vet(:)=vet(:)/norm(vet)
352            ep_e(n+u_ldown,:)=-vep(:)*ne(n,ldown)
353            et_e(n+u_ldown,:)=vet(:)*ne(n,ldown)
354          ENDIF
355
356          CALL xyz2lonlat(xyz_i(n,:),lon,lat)
357          lon_i(n)=lon
358          lat_i(n)=lat
359          elon_i(n,1) = -sin(lon)
360          elon_i(n,2) = cos(lon)
361          elon_i(n,3) = 0
362          elat_i(n,1) = -cos(lon)*sin(lat)
363          elat_i(n,2) = -sin(lon)*sin(lat)
364          elat_i(n,3) = cos(lat)
365
366         
367          CALL xyz2lonlat(xyz_e(n+u_right,:),lon,lat)
368          lon_e(n+u_right)=lon
369          lat_e(n+u_right)=lat
370          elon_e(n+u_right,1) = -sin(lon)
371          elon_e(n+u_right,2) = cos(lon)
372          elon_e(n+u_right,3) = 0
373          elat_e(n+u_right,1) = -cos(lon)*sin(lat)
374          elat_e(n+u_right,2) = -sin(lon)*sin(lat)
375          elat_e(n+u_right,3) = cos(lat)
376         
377          CALL xyz2lonlat(xyz_e(n+u_lup,:),lon,lat)
378          lon_e(n+u_lup)=lon
379          lat_e(n+u_lup)=lat
380          elon_e(n+u_lup,1) = -sin(lon)
381          elon_e(n+u_lup,2) = cos(lon)
382          elon_e(n+u_lup,3) = 0
383          elat_e(n+u_lup,1) = -cos(lon)*sin(lat)
384          elat_e(n+u_lup,2) = -sin(lon)*sin(lat)
385          elat_e(n+u_lup,3) = cos(lat)
386 
387          CALL xyz2lonlat(xyz_e(n+u_ldown,:),lon,lat)
388          lon_e(n+u_ldown)=lon
389          lat_e(n+u_ldown)=lat
390          elon_e(n+u_ldown,1) = -sin(lon)
391          elon_e(n+u_ldown,2) = cos(lon)
392          elon_e(n+u_ldown,3) = 0
393          elat_e(n+u_ldown,1) = -cos(lon)*sin(lat)
394          elat_e(n+u_ldown,2) = -sin(lon)*sin(lat)
395          elat_e(n+u_ldown,3) = cos(lat)
396 
397         
398          DO k=0,5
399            CALL surf_triangle(xyz_i(n,:), xyz_v(n+z_pos(k+1),:), xyz_i(n+t_pos(k+1),:),S1(n,k+1) )
400            CALL surf_triangle(xyz_i(n,:), xyz_v(n+z_pos(k+1),:), xyz_i(n+t_pos(MOD(k+1+6,6)+1),:),S2(n,k+1) )
401            S12 = .5*(S1(n,k+1)+S2(n,k+1))
402            Riv(n,k+1)=S12/Ai(n)
403            Riv2(n,k+1)=S12/surf_v(k+1)
404          ENDDO
405
406          DO k=1,6
407            IF (ABS(surf_v(k))<1e-30) THEN
408              Riv(n,k)=0.
409            ENDIF
410          ENDDO
411         
412          Av(n+z_up)=surf_v(vup)+1e-100
413          Av(n+z_down)=surf_v(vdown)+1e-100
414       
415        ENDDO
416      ENDDO
417     
418      DO j=jj_begin,jj_end
419        DO i=ii_begin,ii_end
420          n=(j-1)*iim+i
421   
422          CALL compute_wee(n,right,w)
423          Wee(n+u_right,:,1)=w(1:5)
424
425          CALL compute_wee(n+t_right,left,w)
426          Wee(n+u_right,:,2)=w(1:5)
427
428
429          CALL compute_wee(n,lup,w)
430          Wee(n+u_lup,:,1)=w(1:5)
431
432          CALL compute_wee(n+t_lup,rdown,w)
433          Wee(n+u_lup,:,2)=w(1:5)
434
435
436          CALL compute_wee(n,ldown,w)
437          Wee(n+u_ldown,:,1)=w(1:5)
438
439          CALL compute_wee(n+t_ldown,rup,w)
440          Wee(n+u_ldown,:,2)=w(1:5)
441
442        ENDDO
443      ENDDO
444     
445      DO j=jj_begin,jj_end
446        DO i=ii_begin,ii_end
447          n=(j-1)*iim+i
448          ii_glo=d%ii_begin_glo-d%ii_begin+i
449          jj_glo=d%jj_begin_glo-d%jj_begin+j
450         
451          IF (ii_glo==1 .AND. jj_glo==1) THEN
452            le(n+u_ldown)=0
453            le_de(n+u_ldown)=0
454            xyz_v(n+z_ldown,:)=xyz_v(n+z_down,:)
455                       
456          ENDIF
457
458          IF (ii_glo==iim_glo .AND. jj_glo==1) THEN
459            le(n+u_right)=0
460            le_de(n+u_right)=0
461            xyz_v(n+z_rdown,:)=xyz_v(n+z_rup,:)
462          ENDIF
463
464          IF (ii_glo==iim_glo .AND. jj_glo==jjm_glo) THEN
465            le(n+u_rup)=0
466            le_de(n+u_rup)=0
467            xyz_v(n+z_rup,:)=xyz_v(n+z_up,:)
468          ENDIF
469
470          IF (ii_glo==1 .AND. jj_glo==jjm_glo) THEN
471            le(n+u_lup)=0
472            le_de(n+u_lup)=0
473            xyz_v(n+z_up,:)=xyz_v(n+z_lup,:)
474          ENDIF
475         
476        ENDDO
477      ENDDO
478
479      DO j=jj_begin-1,jj_end+1
480        DO i=ii_begin-1,ii_end+1
481          n=(j-1)*iim+i
482          xyz_i(n,:)=xyz_i(n,:) * radius
483          xyz_v(n+z_up,:)=xyz_v(n+z_up,:) * radius
484          xyz_v(n+z_down,:)=xyz_v(n+z_down,:) *radius
485          de(n+u_right)=de(n+u_right) * radius
486          de(n+u_lup)=de(n+u_lup)*radius
487          de(n+u_ldown)=de(n+u_ldown)*radius
488          xyz_e(n+u_right,:)=xyz_e(n+u_right,:)*radius
489          xyz_e(n+u_lup,:)=xyz_e(n+u_lup,:)*radius
490          xyz_e(n+u_ldown,:)=xyz_e(n+u_ldown,:)*radius
491          le(n+u_right)=le(n+u_right)*radius
492          le(n+u_lup)=le(n+u_lup)*radius
493          le(n+u_ldown)=le(n+u_ldown)*radius
494          Ai(n)=Ai(n)*radius**2
495          Av(n+z_up)=Av(n+z_up)*radius**2
496          Av(n+z_down)=Av(n+z_down)*radius**2
497        ENDDO
498      ENDDO
499                 
500    ENDDO
501
502    CALL transfert_request(geom%Ai,req_i1)
503    CALL transfert_request(geom%centroid,req_i1)
504
505!    CALL surf_triangle(d%xyz(:,ii_begin,jj_begin),d%xyz(:,ii_begin,jj_end),d%xyz(:,ii_end,jj_begin),S)
506 
507  END SUBROUTINE set_geometry
508
509  SUBROUTINE compute_wee(n,pos,w)
510    INTEGER,INTENT(IN) :: n
511    INTEGER,INTENT(IN) :: pos
512    REAL(rstd),INTENT(OUT) ::w(6)
513
514    REAL(rstd) :: ne_(0:5)
515    REAL(rstd) :: Riv_(6)
516    INTEGER    :: k
517   
518   
519    DO k=0,5
520      ne_(k)=ne(n,MOD(pos-1+k+6,6)+1) 
521      Riv_(k+1)=Riv(n,MOD(pos-1+k+6,6)+1)
522    ENDDO
523         
524    w(1)=-ne_(0)*ne_(1)*(Riv_(1)-0.5)
525    w(2)=-ne_(2)*(ne_(0)*Riv_(2)-w(1)*ne_(1))
526    w(3)=-ne_(3)*(ne_(0)*Riv_(3)-w(2)*ne_(2))
527    w(4)=-ne_(4)*(ne_(0)*Riv_(4)-w(3)*ne_(3))
528    w(5)=-ne_(5)*(ne_(0)*Riv_(5)-w(4)*ne_(4))
529    w(6)=ne_(0)*ne_(5)*(Riv_(6)-0.5)
530   
531!    IF ( ABS(w(5)-w(6))>1e-20) PRINT *, "pb pour wee : w(5)!=w(6)",sum(Riv_(:))
532
533   END SUBROUTINE compute_wee
534           
535 
536  SUBROUTINE compute_geometry
537    USE grid_param
538    USE init_unstructured_mod, ONLY : read_local_mesh
539    USE set_bounds_mod, ONLY : set_bounds
540
541!        CALL allocate_geometry
542
543    SELECT CASE(grid_type)
544    CASE(grid_ico)
545       CALL set_geometry
546       ! copy position of generators and vertices back into domain_glo(:)%xyz/vertex
547       ! so that write_field gets the right values
548       CALL update_domain
549       CALL set_bounds(domain_glo, .TRUE.)
550       CALL set_bounds(domain, .FALSE.)
551    CASE(grid_unst)
552       swap_needed=.FALSE.
553       CALL read_local_mesh
554    CASE DEFAULT
555       STOP 'Invalid value of grid_type encountered in compute_geometry'
556    END SELECT
557  END SUBROUTINE compute_geometry
558 
559END MODULE compute_geometry_mod
Note: See TracBrowser for help on using the repository browser.