[cig-commits] commit: change VTK output to legacy VTK binary format, fixes run2.sh

Mercurial hg at geodynamics.org
Tue Sep 20 12:13:16 PDT 2011


changeset:   18:88603e5baf07
user:        Sylvain Barbot <sylbar.vainbot at gmail.com>
date:        Mon May 23 21:48:51 2011 -0700
files:       examples/run2.sh export.f90 relax.f90
description:
change VTK output to legacy VTK binary format, fixes run2.sh


diff -r 54afa44116df -r 88603e5baf07 examples/run2.sh
--- a/examples/run2.sh	Sun May 22 13:19:25 2011 -0700
+++ b/examples/run2.sh	Mon May 23 21:48:51 2011 -0700
@@ -3,7 +3,7 @@
 # nonlinear viscoelastic relaxation (power exponent n=3)
 # following slip on a strike-slip fault
 #
-# output every computational step (Dt = -2). 
+# output every two computational steps (Dt = -2). 
 # The time step is computed automatically and the value unchanged (scale = 1)
 #
 # to visualize coseismic deformation (requires GRD output, or manual conversion to GRD format):
@@ -37,7 +37,7 @@ 0 0.5
 # elastic parameters and gamma = (1-nu) rho g / mu = 8.33e-7 /m = 8.33e-4 /km
 1 1 8.33e-4
 # integration time (t1)
-50 -2 1
+100 -2 1
 # number of observation planes
 0
 # number of observation points
@@ -63,7 +63,7 @@ 1
 # number of shear dislocations
 1
 # index slip x1 x2 x3 length width strike dip rake
-      1    1  1  0  0      2     1      0  90    0
+      1    1 -1  0  0      2     1      0  90    0
 # number of tensile cracks
 0
 # number of dilatation sources
diff -r 54afa44116df -r 88603e5baf07 export.f90
--- a/export.f90	Sun May 22 13:19:25 2011 -0700
+++ b/export.f90	Mon May 23 21:48:51 2011 -0700
@@ -1571,6 +1571,79 @@ END SUBROUTINE exportcreep
   END SUBROUTINE exportvtk_vectors
 
   !------------------------------------------------------------------
+  !> subroutine ExportVTK_Vectors_Legacy
+  !! creates a .vtk file in the VTK Legacy binary format with 
+  !! structured points containing a vector field.
+  !!
+  !! \author sylvain barbot 05/23/11 - original form
+  !------------------------------------------------------------------
+  SUBROUTINE exportvtk_vectors_legacy(u1,u2,u3,sx1,sx2,sx3,dx1,dx2,dx3, &
+                                      j1,j2,j3,vcfilename,title,name)
+    INTEGER, INTENT(IN) :: sx1,sx2,sx3,j1,j2,j3
+#ifdef ALIGN_DATA
+    REAL*4, INTENT(IN), DIMENSION(sx1+2,sx2,sx3) :: u1,u2,u3
+#else
+    REAL*4, INTENT(IN), DIMENSION(sx1,sx2,sx3) :: u1,u2,u3
+#endif
+    REAL*8, INTENT(IN) :: dx1,dx2,dx3
+    CHARACTER(80), INTENT(IN) :: vcfilename,title,name
+
+    INTEGER :: iostatus,idum,i1,i2,i3
+    CHARACTER :: q,end_rec
+    CHARACTER(LEN=180) :: s_buffer
+    REAL*8 :: x1,x2,x3
+
+    ! double-quote character
+    q=char(34)
+    ! end-character for binary-record finalize
+    end_rec=char(10)
+
+    ! open file for mixed binary/ascii writing in VTK legacy format
+    OPEN(UNIT=15,FILE=vcfilename,form='UNFORMATTED',ACCESS='SEQUENTIAL', &
+         ACTION='WRITE',CONVERT='BIG_ENDIAN',RECORDTYPE='STREAM', &
+         BUFFERED='YES',IOSTAT=iostatus)
+    IF (iostatus>0) THEN
+       WRITE_DEBUG_INFO
+       PRINT '(a)', vcfilename
+       STOP "could not open file in mixed binary/ascii for export in legacy format"
+    END IF
+
+    ! writing header of file (INIT)
+    WRITE(UNIT=15,IOSTAT=iostatus) '# vtk DataFile Version 3.0'//end_rec
+    WRITE(UNIT=15,IOSTAT=iostatus) TRIM(title)//end_rec
+    WRITE(UNIT=15,IOSTAT=iostatus) 'BINARY'//end_rec
+    WRITE(UNIT=15,IOSTAT=iostatus) 'DATASET '//'STRUCTURED_POINTS'//end_rec
+
+    ! structured points grid (GEO)
+    WRITE(s_buffer,FMT='(A,3I12)',IOSTAT=iostatus) 'DIMENSIONS ',sx1/j1,sx2/j2,sx3/j3
+    WRITE(UNIT=15,IOSTAT=iostatus) TRIM(s_buffer)//end_rec
+    WRITE(s_buffer,FMT='(A,3E14.6E2)',IOSTAT=iostatus) 'ORIGIN ',-dx1*(sx1/2),-dx2*(sx2/2),0.d0
+    WRITE(UNIT=15,IOSTAT=iostatus) TRIM(s_buffer)//end_rec
+    WRITE(s_buffer,FMT='(A,3E14.6E2)',IOSTAT=iostatus) 'SPACING ',dx1*j1,dx2*j2,dx3*j3
+    WRITE(UNIT=15,IOSTAT=iostatus) TRIM(s_buffer)//end_rec
+
+    ! data header for this grid (DAT)
+    WRITE(s_buffer,FMT='(A,I12)',IOSTAT=iostatus) 'POINT_DATA ', (sx1/j1)*(sx2/j2)*(sx3/j3)
+    WRITE(UNIT=15,IOSTAT=iostatus) TRIM(s_buffer)//end_rec
+
+    ! data array (VAR)
+    WRITE(UNIT=15,IOSTAT=iostatus) 'VECTORS '//TRIM(name)//' float'//end_rec
+    DO x3=0,sx3-1,j3
+       DO x2=-sx2/2,sx2/2-1,j2
+          DO x1=-sx1/2,sx1/2-1,j1
+             CALL shiftedindex(x1,x2,1._8,sx1,sx2,sx3,1._8,1._8,1._8,i1,i2,idum)
+             WRITE (UNIT=15,IOSTAT=iostatus) REAL(u1(i1,i2,x3+1)),REAL(u2(i1,i2,x3+1)),REAL(u3(i1,i2,x3+1))
+          END DO
+       END DO
+    END DO
+    WRITE(UNIT=15,IOSTAT=iostatus) end_rec
+
+    ! close binary file (END)
+    CLOSE(15)
+
+  END SUBROUTINE exportvtk_vectors_legacy
+
+  !------------------------------------------------------------------
   !> subroutine ExportVTK_Vectors_Slice
   !! creates a .vtr file (in the VTK Rectilinear XML format) 
   !! containing a vector field.
diff -r 54afa44116df -r 88603e5baf07 relax.f90
--- a/relax.f90	Sun May 22 13:19:25 2011 -0700
+++ b/relax.f90	Mon May 23 21:48:51 2011 -0700
@@ -181,6 +181,7 @@
   !!   - homogenize VTK output so that geometry of events match event index
   !!   - evaluate Green function, stress and body forces in GPU
   !!   - create a ./configure ./install framework
+  !!   - input a list of planes to compute Coulomb stress
   !------------------------------------------------------------------------
 PROGRAM relax
 
@@ -207,7 +208,7 @@ PROGRAM relax
   REAL*8 :: maxwell(3)
   TYPE(SIMULATION_STRUC) :: in
 #ifdef VTK
-  CHARACTER(80) :: vcfilename
+  CHARACTER(80) :: vcfilename,title,name
   CHARACTER(3) :: digit
 #endif
   REAL*8 :: t,Dt,tm
@@ -356,8 +357,13 @@ PROGRAM relax
 #endif
 #ifdef VTK
   IF (in%isoutputvtk) THEN
-     vcfilename=trim(in%wdir)//"/disp-000.vtr"
-     CALL exportvtk_vectors(u1,u2,u3,in%sx1,in%sx2,in%sx3/4,in%dx1,in%dx2,in%dx3,8,8,8,vcfilename)
+     !vcfilename=trim(in%wdir)//"/disp-000.vtr"
+     !CALL exportvtk_vectors(u1,u2,u3,in%sx1,in%sx2,in%sx3/4,in%dx1,in%dx2,in%dx3,8,8,8,vcfilename)
+     vcfilename=trim(in%wdir)//"/disp-000.vtk"
+     title="coseismic displacement vector field"
+     name="displacement"
+     CALL exportvtk_vectors_legacy(u1,u2,u3,in%sx1,in%sx2,in%sx3/4,in%dx1,in%dx2,in%dx3, &
+                                   4,4,8,vcfilename,title,name)
      !CALL exportvtk_vectors_slice(u1,u2,u3,in%sx1,in%sx2,in%sx3/2,in%dx1,in%dx2,in%dx3,in%oz,8,8,vcfilename)
   END IF
 #endif
@@ -546,8 +552,13 @@ PROGRAM relax
 #ifdef VTK_EQBF
         IF (in%isoutputvtk) THEN
            WRITE (digit,'(I3.3)') oi
-           vcfilename=trim(in%wdir)//"/eqbf-"//digit//".vtr"
-           CALL exportvtk_vectors(v1,v2,v3,in%sx1,in%sx2,in%sx3/4,in%dx1,in%dx2,in%dx3,8,8,8,vcfilename)
+           !vcfilename=trim(in%wdir)//"/eqbf-"//digit//".vtr"
+           !CALL exportvtk_vectors(v1,v2,v3,in%sx1,in%sx2,in%sx3/4,in%dx1,in%dx2,in%dx3,8,8,8,vcfilename)
+           vcfilename=trim(in%wdir)//"/eqbf-"//digit//".vtk"
+           title="instantaneous equivalent body-force rate vector field"
+           name="body-force-rate"
+           CALL exportvtk_vectors_legacy(v1,v2,v3,in%sx1,in%sx2,in%sx3/4,in%dx1,in%dx2,in%dx3, &
+                                         4,4,8,vcfilename,title,name)
         END IF
 #endif
 #ifdef GRD_EQBF
@@ -646,13 +657,23 @@ PROGRAM relax
         IF (in%isoutputvtk) THEN
            WRITE (digit,'(I3.3)') oi
            ! export total displacement in VTK XML format
-           vcfilename=trim(in%wdir)//"/disp-"//digit//".vtr"
-           CALL exportvtk_vectors(u1,u2,u3,in%sx1,in%sx2,in%sx3/4,in%dx1,in%dx2,in%dx3,8,8,8,vcfilename)
+           !vcfilename=trim(in%wdir)//"/disp-"//digit//".vtr"
+           !CALL exportvtk_vectors(u1,u2,u3,in%sx1,in%sx2,in%sx3/4,in%dx1,in%dx2,in%dx3,8,8,8,vcfilename)
+           vcfilename=trim(in%wdir)//"/disp-"//digit//".vtk"
+           title="cumulative displacement vector field"
+           name="displacement"
+           CALL exportvtk_vectors_legacy(u1,u2,u3,in%sx1,in%sx2,in%sx3/4,in%dx1,in%dx2,in%dx3, &
+                                         4,4,8,vcfilename,title,name)
            !CALL exportvtk_vectors_slice(u1,u2,u3,in%sx1,in%sx2,in%sx3/2,in%dx1,in%dx2,in%dx3,in%oz,8,8,vcfilename)
 
            ! export instantaneous velocity in VTK XML format
-           vcfilename=trim(in%wdir)//"/vel-"//digit//".vtr"
-           CALL exportvtk_vectors(v1,v2,v3,in%sx1,in%sx2,in%sx3/4,in%dx1,in%dx2,in%dx3,8,8,8,vcfilename)
+           !vcfilename=trim(in%wdir)//"/vel-"//digit//".vtr"
+           !CALL exportvtk_vectors(v1,v2,v3,in%sx1,in%sx2,in%sx3/4,in%dx1,in%dx2,in%dx3,8,8,8,vcfilename)
+           vcfilename=trim(in%wdir)//"/vel-"//digit//".vtk"
+           title="instantaneous velocity vector field"
+           name="velocity"
+           CALL exportvtk_vectors_legacy(v1,v2,v3,in%sx1,in%sx2,in%sx3/2,in%dx1,in%dx2,in%dx3, &
+                                         8,8,16,vcfilename,title,name)
            !CALL exportvtk_vectors_slice(v1,v2,v3,in%sx1,in%sx2,in%sx3/2,in%dx1,in%dx2,in%dx3,in%oz,8,8,vcfilename)
         END IF
 #endif



More information about the CIG-COMMITS mailing list