source: trunk/fsource/pyspg.for @ 440

Last change on this file since 440 was 341, checked in by vondreele, 14 years ago

new GenHKL routine in fortran

File size: 1.8 KB
Line 
1C Space group access routines for python
2
3      SUBROUTINE SGFORPY(SPG,LAUE,SGINV,SGLATT,SGUNIQ,SGPOL,
4     1  SGNOPS,SGMTRX,SGTRNS,IERR)
5Cf2py intent(in)  SPG
6Cf2py intent(out) LAUE
7Cf2py intent(out) SGINV
8Cf2py intent(out) SGLATT
9Cf2py intent(out) SGUNIQ
10Cf2py intent(out) SGPOL
11Cf2py intent(out) SGNOPS
12Cf2py intent(out) SGMTRX
13Cf2py intent(out) SGTRNS
14Cf2py intent(out) IERR
15
16      CHARACTER*(20) SPG
17      INTEGER*4     LAUE,SGINV,SGLATT,SGUNIQ,SGNOPS,IERR,SGNCEN
18      REAL*4        SGMTRX(24,3,3),SGTRNS(24,3)
19      REAL*4        RT(5,4,25),CEN(3,4)
20      INTEGER*4     JRT(3,5,24)
21
22
23      CALL SGROUPNP(SPG,LAUE,SGUNIQ,SGINV,SGLATT,SGNOPS,SGPOL,JRT,
24     1  CEN,SGNCEN,RT,IERR)
25      DO K=1,SGNOPS
26        DO I=1,3
27          DO J=1,3
28            SGMTRX(K,I,J) = JRT(I,J,K)
29            SGTRNS(K,I) = JRT(I,4,K)/12.
30          END DO
31        END DO
32      END DO
33      RETURN
34      END
35
36      SUBROUTINE GENHKLPY(XH,NSYM,SGMTRX,SGTRNS,ICEN,NCV,SGCEN,JHK,
37     1  HKL,IABSNT,MULP)
38Cf2py intent(in)  XH
39Cf2py intent(in)  NSYM
40Cf2py intent(in)  SGMTRX
41Cf2py intent(in)  SGTRNS
42Cf2py depend(NSYM) SGMTRX,SGTRNS
43Cf2py intent(in)  ICEN
44Cf2py intent(in)  NCV
45Cf2py intent(in)  SGCEN
46Cf2py depend(NCV) SGCEN
47Cf2py intent(out) JHK
48Cf2py intent(out) HKL
49Cf2py intent(out) IABSNT
50Cf2py intent(out) MULP
51
52      INTEGER*4     ICEN,NSYM
53      REAL*4        SGMTRX(NSYM,3,3),SGTRNS(NSYM,3),SGCEN(NCV,3)
54      REAL*4        CEN(3,4),HKL(4,24),XH(4)
55      INTEGER*4     JRT(3,5,24),JHK,NCV
56
57      DO J=1,NCV
58        DO I=1,3
59          CEN(I,J) = SGCEN(J,I)
60        END DO
61      END DO
62      DO K=1,NSYM
63        DO I=1,3
64          DO J=1,3
65            JRT(I,J,K) = SGMTRX(K,I,J)*1.
66            JRT(I,4,K) = SGTRNS(K,I)*12.
67          END DO
68        END DO
69      END DO
70      CALL GENHKL(XH,NSYM,JRT,ICEN,NCV,CEN,JHK,HKL,IABSNT,MULP)
71      RETURN
72      END
Note: See TracBrowser for help on using the repository browser.