[cig-commits] [commit] master: include MANIFOLD type and add pts2series subroutine (293b281)

cig_noreply at geodynamics.org cig_noreply at geodynamics.org
Fri Jan 23 01:11:56 PST 2015


Repository : https://github.com/geodynamics/relax

On branch  : master
Link       : https://github.com/geodynamics/relax/compare/196ac0b9d49f79f91757c5f5d312afe75c3f17e7...293b281689facd77a00ce8ffa744eb7e8e21339e

>---------------------------------------------------------------

commit 293b281689facd77a00ce8ffa744eb7e8e21339e
Author: Sylvain Barbot <sbarbot at ntu.edu.sg>
Date:   Fri Jan 23 17:11:32 2015 +0800

    include MANIFOLD type and add pts2series subroutine


>---------------------------------------------------------------

293b281689facd77a00ce8ffa744eb7e8e21339e
 src/export.f90 | 48 ++++++++++++++++++++++++++++++++++++++++++++++++
 src/types.f90  | 12 ++++++++++++
 2 files changed, 60 insertions(+)

diff --git a/src/export.f90 b/src/export.f90
index cdf3210..0f583f1 100644
--- a/src/export.f90
+++ b/src/export.f90
@@ -3024,4 +3024,52 @@ END SUBROUTINE exportcreep_vtk
   END SUBROUTINE exportvtk_vectors_slice
 #endif
 
+  !------------------------------------------------------------------
+  !> subroutine pts2series
+  !! sample a vector field at a series of points for export.
+  !! each location is attributed a file in which the time evolution
+  !! of the vector value is listed in the format:
+  !!
+  !!                t_0 u(t_0) v(t_0) w(t_0)
+  !!                t_1 u(t_1) v(t_1) w(t_1)
+  !!                ...
+  !!
+  !! \author sylvain barbot (11/10/07) - original form
+  !------------------------------------------------------------------
+  SUBROUTINE pts2series(c1,c2,c3,sx1,sx2,sx3,dx1,dx2,dx3, &
+       opts,time,index,gps)
+    INTEGER, INTENT(IN) :: sx1,sx2,sx3
+#ifdef ALIGN_DATA
+    REAL*4, INTENT(IN), DIMENSION(sx1+2,sx2,sx3) :: c1,c2,c3
+#else
+    REAL*4, INTENT(IN), DIMENSION(sx1,sx2,sx3) :: c1,c2,c3
+#endif
+    TYPE(VECTOR_STRUCT), INTENT(IN), DIMENSION(:) :: opts
+    REAL*8, INTENT(IN) :: dx1,dx2,dx3,time
+    INTEGER, INTENT(IN) :: index
+    TYPE(MANIFOLD_STRUCT), INTENT(INOUT), DIMENSION(:) :: gps
+
+    INTEGER :: i1,i2,i3,k
+    REAL*8 :: u1,u2,u3,x1,x2,x3
+
+    DO k=1,SIZE(opts)
+       x1=opts(k)%v1
+       x2=opts(k)%v2
+       x3=opts(k)%v3
+
+       CALL shiftedindex(x1,x2,x3,sx1,sx2,sx3,dx1,dx2,dx3,i1,i2,i3)
+
+       u1=c1(i1,i2,i3)
+       u2=c2(i1,i2,i3)
+       u3=c3(i1,i2,i3)
+
+       gps(k)%nepochs=index
+       gps(k)%t(index)=time
+       gps(k)%u1(index)=u1
+       gps(k)%u2(index)=u2
+       gps(k)%u3(index)=u3
+    END DO
+  
+  END SUBROUTINE pts2series
+
 END MODULE export
diff --git a/src/types.f90 b/src/types.f90
index 752f209..8c982dc 100644
--- a/src/types.f90
+++ b/src/types.f90
@@ -87,6 +87,16 @@ MODULE types
      TYPE(SOURCE_STRUCT), DIMENSION(:), ALLOCATABLE :: s,sc,ts,tsc,m,mc,l,lc
   END TYPE EVENT_STRUC
   
+  TYPE MANIFOLD_STRUCT
+     INTEGER :: nepochs
+     ! time axis
+     REAL*8, DIMENSION(:), ALLOCATABLE :: t
+     ! displacement time series
+     REAL*8, DIMENSION(:), ALLOCATABLE :: u1,u2,u3
+     ! uncertainties
+     REAL*8, DIMENSION(:), ALLOCATABLE :: s1,s2,s3
+  END TYPE MANIFOLD_STRUCT
+
   TYPE, PUBLIC :: SIMULATION_STRUC
      ! grid dimension
      INTEGER :: sx1,sx2,sx3
@@ -213,6 +223,8 @@ MODULE types
      LOGICAL :: ishelp=.FALSE.
      LOGICAL :: isversion=.FALSE.
 
+     TYPE(MANIFOLD_STRUCT), DIMENSION(:), ALLOCATABLE :: gps,sim
+
   END TYPE SIMULATION_STRUC
 
 END MODULE types



More information about the CIG-COMMITS mailing list