Changeset 2189


Ignore:
Timestamp:
Mar 31, 2016 4:12:34 PM (7 years ago)
Author:
vondreele
Message:

comment out import pydiffax since g77 version woun't compile (argh)

Location:
trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/GSASIIpwd.py

    r2187 r2189  
    3737import GSASIImath as G2mth
    3838import pypowder as pyd
    39 import pydiffax as pyx
     39#import pydiffax as pyx
    4040
    4141# trig functions in degrees
  • trunk/fsource/pydiffax.for

    r2188 r2189  
     1      SUBROUTINE PYGETSADP(CNTRLS,NSADP,SADP,HKLIM,INCR)
     2       
     3Cf2py intent(in) CNTRLS
     4Cf2py intent(in) NSADP
     5Cf2py intent(in/out) SADP
     6Cf2py depend(NSADP) SADP
     7Cf2py intent(out) HKLIM
     8Cf2py intent(out) INCR
     9   
     10      INCLUDE 'DIFFaXsubs/DIFFaX.par'
     11      INCLUDE 'DIFFaXsubs/DIFFaX.inc'
     12
     13      EXTERNAL GET_G,AGLQ16,GET_SYM                 
     14      INTEGER*4 CNTRLS(7),NSADP,GET_SYM,i_plane,hk_lim,i,j,k
     15      INTEGER*4 HKLIM
     16      REAL*8 SADP(NSADP),AGLQ16,l_upper,INCR
     17      LOGICAL ok,GET_G
     18       
     19                   
     20      i_plane = CNTRLS(2)
     21      l_upper = CNTRLS(3)
     22C      print *,n_actual,(l_n_atoms(i),i=1,n_actual)
     23C      do j=1,n_actual
     24C        do i=1,l_n_atoms(j)
     25C          print *,a_name(i,j),(a_pos(k,i,j),k=1,3)
     26C        end do
     27C      end do
     28C      print *, recrsv,inf_thick,xplcit,rndm,l_cnt,has_l_mirror
     29C      do i=1,n_layers
     30C      print *,' layer',i
     31C         do j=1,n_layers
     32C            print *,'layer',j,l_alpha(i,j),(l_r(k,i,j),k=1,3)
     33C         end do
     34C      end do
     35      ok = .TRUE.
     36       
     37C      print *,cell_a,cell_b,cell_c,cell_gamma,pnt_grp,SymGrpNo
     38c      DoSymDump = .TRUE.
     39      CALL SPHCST()
     40      CALL DETUN()
     41      ok = GET_G()
     42      CALL OPTIMZ('GSAS-II',ok)
     43C      print *,lambda,max_angle,h_bnd,k_bnd,l_bnd,no_trials,
     44C     1  rad_type,X_RAY,n_atoms
     45C      print *,(l_g(j),j=1,n_layers)
     46C      do j=1,n_layers
     47C        print *,(hx_ky(i,j),i=1,l_n_atoms(j))
     48C        print *,(mat(i,j),i=1,n_layers)
     49C        print *,(mat1(i,j),i=1,n_layers)
     50C        print *,(l_phi(i,j),i=1,n_layers)
     51C      end do
     52      CALL GETSAD(AGLQ16,i_plane,l_upper,hk_lim,'GSAS-II',ok)
     53      HKLIM = hk_lim+1
     54      INCR = dble(SADSIZE/2)/l_upper
     55      if (i_plane.eq.1) then
     56        INCR = INCR*sqrt(a0/c0)
     57      else if (i_plane.eq.2) then
     58        INCR = INCR*sqrt(b0/c0)
     59      else if (i_plane.eq.3) then
     60        INCR = INCR*sqrt((a0+b0+d0)/c0)
     61      else if (i_plane.eq.4) then
     62        INCR = INCR*sqrt((a0+b0-d0)/c0)
     63      end if
     64      do I=1,NSADP
     65        SADP(i) = spec(i)
     66      end do
     67      RETURN
     68      END
     69
    170      SUBROUTINE PYLOADSCF(NATP,ATYPES,SFDAT)
    271       
     
    183252       
    184253           
    185       SUBROUTINE PYGETSADP(CNTRLS,NSADP,SADP,HKLIM,INCR)
    186        
    187 Cf2py intent(in) CNTRLS
    188 Cf2py intent(in) NSADP
    189 Cf2py intent(in/out) SADP
    190 Cf2py depend(NSADP) SADP
    191 Cf2py intent(out) HKLIM
    192 Cf2py intent(out) INCR
    193    
    194       INCLUDE 'DIFFaXsubs/DIFFaX.par'
    195       INCLUDE 'DIFFaXsubs/DIFFaX.inc'
    196 
    197       INTEGER*4 CNTRLS(7),NSADP,GET_SYM,i_plane,hk_lim,i,j,k
    198       INTEGER*4 HKLIM
    199       REAL*8 SADP(NSADP),AGLQ16,l_upper,INCR
    200       LOGICAL ok,GET_G
    201        
    202       EXTERNAL AGLQ16,GET_SYM,GET_G                 
    203                    
    204       i_plane = CNTRLS(2)
    205       l_upper = CNTRLS(3)
    206 C      print *,n_actual,(l_n_atoms(i),i=1,n_actual)
    207 C      do j=1,n_actual
    208 C        do i=1,l_n_atoms(j)
    209 C          print *,a_name(i,j),(a_pos(k,i,j),k=1,3)
    210 C        end do
    211 C      end do
    212 C      print *, recrsv,inf_thick,xplcit,rndm,l_cnt,has_l_mirror
    213 C      do i=1,n_layers
    214 C      print *,' layer',i
    215 C         do j=1,n_layers
    216 C            print *,'layer',j,l_alpha(i,j),(l_r(k,i,j),k=1,3)
    217 C         end do
    218 C      end do
    219       ok = .TRUE.
    220        
    221 C      print *,cell_a,cell_b,cell_c,cell_gamma,pnt_grp,SymGrpNo
    222 c      DoSymDump = .TRUE.
    223       CALL SPHCST()
    224       CALL DETUN()
    225       ok = GET_G()
    226       CALL OPTIMZ('GSAS-II',ok)
    227 C      print *,lambda,max_angle,h_bnd,k_bnd,l_bnd,no_trials,
    228 C     1  rad_type,X_RAY,n_atoms
    229 C      print *,(l_g(j),j=1,n_layers)
    230 C      do j=1,n_layers
    231 C        print *,(hx_ky(i,j),i=1,l_n_atoms(j))
    232 C        print *,(mat(i,j),i=1,n_layers)
    233 C        print *,(mat1(i,j),i=1,n_layers)
    234 C        print *,(l_phi(i,j),i=1,n_layers)
    235 C      end do
    236       CALL GETSAD(AGLQ16,i_plane,l_upper,hk_lim,'GSAS-II',ok)
    237       HKLIM = hk_lim+1
    238       INCR = dble(SADSIZE/2)/l_upper
    239       if (i_plane.eq.1) then
    240         INCR = INCR*sqrt(a0/c0)
    241       else if (i_plane.eq.2) then
    242         INCR = INCR*sqrt(b0/c0)
    243       else if (i_plane.eq.3) then
    244         INCR = INCR*sqrt((a0+b0+d0)/c0)
    245       else if (i_plane.eq.4) then
    246         INCR = INCR*sqrt((a0+b0-d0)/c0)
    247       end if
    248       do I=1,NSADP
    249         SADP(i) = spec(i)
    250       end do
    251       RETURN
    252       END
Note: See TracChangeset for help on using the changeset viewer.