Changeset 2191


Ignore:
Timestamp:
Apr 1, 2016 12:39:12 PM (8 years ago)
Author:
vondreele
Message:

reduce printing from DIFFaX routines - new fortran binaries
fix bug in PWDR simulation
begin CalcStackingPWDR to call GETSPEC from DIFFaXsubs

Location:
trunk
Files:
23 edited

Legend:

Unmodified
Added
Removed
  • trunk/GSASIIgrid.py

    r2187 r2191  
    617617    def GetSelection(self):
    618618        if 'powder' in self.calcType:
    619             return '0\n0\n3\n','','',self.Parm,self.parmRange,self.parmStep
     619            return '0\n0\n3\n','','','',self.Parm,self.parmRange,self.parmStep
    620620        elif 'selected' in self.calcType:
    621621            return '0\n0\n4\n1\n%d\n%d\n16\n1\n%d\n0\nend\n'%    \
  • trunk/GSASIIphsGUI.py

    r2187 r2191  
    29642964            dlg.Destroy()       
    29652965            G2pwd.StackSim(data['Layers'],ctrls,HistName,scale,background,limits,inst,profile)
     2966            G2pwd.CalcStackingPWDR(data['Layers'],HistName,scale,background,limits,inst,profile)
    29662967            G2plt.PlotPatterns(G2frame,plotType='PWDR')
    29672968        else:   #selected area
    2968             G2pwd.StackSim(data['Layers'],ctrls)
    2969 #            G2pwd.CalcStackingSADP(data['Layers'])
     2969#            G2pwd.StackSim(data['Layers'],ctrls)
     2970            G2pwd.CalcStackingSADP(data['Layers'])
    29702971        wx.CallAfter(UpdateLayerData)
    29712972       
  • trunk/GSASIIpwd.py

    r2190 r2191  
    19351935    os.remove('GSASII-DIFFaX.dat')
    19361936   
     1937def CalcStackingPWDR(Layers,HistName,scale,background,limits,inst,profile):
     1938    pass
     1939   
    19371940def CalcStackingSADP(Layers):
    19381941   
     
    19631966        laueId = ['-1','2/m(ab)','2/m(c)','mmm','-3','-3m','4/m','4/mmm',
    19641967            '6/m','6/mmm'].index(Layers['Laue'])+1
    1965     except ValueError:
     1968    except ValueError:  #for 'unknown'
    19661969        laueId = -1
    19671970    planeId = ['h0l','0kl','hhl','h-hl'].index(Layers['Sadp']['Plane'])+1
     
    20282031    pyx.pygettrans(Nlayers,TransP,TransX)
    20292032# result as Sadp
    2030     mirror = laueId in [2,3,4,7,8,9,10]
     2033    mirror = laueId in [-1,2,3,7,8,9,10]
    20312034    Nspec = 20001       
    20322035    spec = np.zeros(Nspec,dtype='double')   
    20332036    time0 = time.time()
    2034     hkLim,Incr = pyx.pygetsadp(controls,Nspec,spec)
    2035 #    GSASIIpath.IPyBreak()
     2037    hkLim,Incr,Nblk = pyx.pygetsadp(controls,Nspec,spec)
    20362038    Sapd = np.zeros((256,256))
    20372039    maxInt = np.max(spec[1:])
     
    20392041    iB = 0
    20402042    for i in range(hkLim):
    2041         iF = iB+128
    2042         p1 = 128+int(i*Incr)
    2043         Sapd[128:,p1] = spec[iB:iF]
    2044         Sapd[:128,p1] = spec[iF:iB:-1]
    2045         if mirror:
    2046             p2 = 128-int(i*Incr)
     2043        iF = iB+Nblk
     2044        p1 = 127+int(i*Incr)
     2045        p2 = 128-int(i*Incr)
     2046        if Nblk == 128:
     2047            if i:
     2048                Sapd[128:,p1] = spec[iB:iF]
     2049                Sapd[:128,p1] = spec[iF:iB:-1]
    20472050            Sapd[128:,p2] = spec[iB:iF]
    20482051            Sapd[:128,p2] = spec[iF:iB:-1]
    2049         iB += 128
     2052        else:
     2053            if i:
     2054                Sapd[:,p1] = spec[iB:iF]
     2055            Sapd[:,p2] = spec[iB:iF]
     2056        iB += Nblk
    20502057    Sapd *= Scale
    20512058    Sapd = np.where(Sapd<32767.,Sapd,32767.)
    20522059    Layers['Sadp']['Img'] = Sapd
    20532060    print 'GETSAD time = %.2fs'%(time.time()-time0)
     2061#    GSASIIpath.IPyBreak()
    20542062   
    20552063#testing data
  • trunk/fsource/DIFFaXsubs/DIFFaX.inc

    r2188 r2191  
    5353*                    incompatible with the input data, then this       *
    5454*                    will be reset to FALSE.                           *
     55*    debug        -  TRUE for printouts to appear on screen (RVD)      *
    5556*    DoDatdump    -  TRUE if the user wants a dump of the data file    *
    5657*    DoSymDump    -  TRUE if the user wants to dump the output of      *
     
    382383     |        xplcit, rndm, inf_thick, has_l_mirror, h_mirror,
    383384     |        k_mirror, hk_mirror, check_sym, same_rz, any_sharp,
    384      |        same_layer, finite_width
     385     |        same_layer, finite_width,debug
    385386*
    386387      integer*4 l_seq(XP_MAX), pow(MAX_BIN), a_type(MAX_A,MAX_L),
     
    422423     |                recrsv, xplcit, rndm, inf_thick, has_l_mirror,
    423424     |                h_mirror, k_mirror, hk_mirror, check_sym,
    424      |                same_rz, any_sharp, same_layer, finite_width
     425     |                same_rz, any_sharp, same_layer, finite_width,
     426     |                debug
    425427*
    426428      common /integ1/ l_seq, pow, a_type, l_n_atoms, l_symmetry,
  • trunk/fsource/DIFFaXsubs/DIFFaXsubs.for

    r2190 r2191  
    23522352*
    23532353* write progress to screen
    2354         write(op,102) h, k, infile(1:LENGTH(infile))
     2354        if (debug) write(op,102) h, k, infile(1:LENGTH(infile))
    23552355*
    23562356        call XYPHSE(h, k)
     
    23852385          if(cnt.gt.MAX_SP) goto 998
    23862386          spec(cnt) = x
    2387           if(mod(info,info_step).eq.0) then
     2387          if(mod(info,info_step).eq.0 .and. debug) then
    23882388            if(loglin.eq.0) then
    23892389              if(ONE+x.gt.ZERO) then
  • trunk/fsource/pydiffax.for

    r2190 r2191  
    1       SUBROUTINE PYGETSADP(CNTRLS,NSADP,SADP,HKLIM,INCR)
    2        
    3 Cf2py intent(in) CNTRLS
    4 Cf2py intent(in) NSADP
    5 Cf2py intent(in/out) SADP
    6 Cf2py depend(NSADP) SADP
    7 Cf2py intent(out) HKLIM
    8 Cf2py intent(out) INCR
    9    
    10       INCLUDE 'DIFFaXsubs/DIFFaX.par'
    11       INCLUDE 'DIFFaXsubs/DIFFaX.inc'
    12 
    13       INTEGER*4 CNTRLS(7),NSADP,GET_SYM,i_plane,hk_lim,i,j,k
    14       INTEGER*4 HKLIM
    15       REAL*8 SADP(NSADP),AGLQ16,l_upper,INCR
    16       LOGICAL ok
    17        
    18       EXTERNAL AGLQ16,GET_SYM                 
    19                    
    20       i_plane = CNTRLS(2)
    21       l_upper = CNTRLS(3)
    22 C      print *,n_actual,(l_n_atoms(i),i=1,n_actual)
    23 C      do j=1,n_actual
    24 C        do i=1,l_n_atoms(j)
    25 C          print *,a_name(i,j),(a_pos(k,i,j),k=1,3)
    26 C        end do
    27 C      end do
    28 C      print *, recrsv,inf_thick,xplcit,rndm,l_cnt,has_l_mirror
    29 C      do i=1,n_layers
    30 C      print *,' layer',i
    31 C         do j=1,n_layers
    32 C            print *,'layer',j,l_alpha(i,j),(l_r(k,i,j),k=1,3)
    33 C         end do
    34 C      end do
    35       ok = .TRUE.
    36        
    37 C      print *,cell_a,cell_b,cell_c,cell_gamma,pnt_grp,SymGrpNo
    38 c      DoSymDump = .TRUE.
    39       CALL SPHCST()
    40       CALL DETUN()
    41       CALL OPTIMZ('GSAS-II',ok)
    42 C      print *,lambda,max_angle,h_bnd,k_bnd,l_bnd,no_trials,
    43 C     1  rad_type,X_RAY,n_atoms
    44 C      print *,(l_g(j),j=1,n_layers)
    45 C      do j=1,n_layers
    46 C        print *,(hx_ky(i,j),i=1,l_n_atoms(j))
    47 C        print *,(mat(i,j),i=1,n_layers)
    48 C        print *,(mat1(i,j),i=1,n_layers)
    49 C        print *,(l_phi(i,j),i=1,n_layers)
    50 C      end do
    51       CALL GETSAD(AGLQ16,i_plane,l_upper,hk_lim,'GSAS-II',ok)
    52       HKLIM = hk_lim+1
    53       INCR = dble(SADSIZE/2)/l_upper
    54       if (i_plane.eq.1) then
    55         INCR = INCR*sqrt(a0/c0)
    56       else if (i_plane.eq.2) then
    57         INCR = INCR*sqrt(b0/c0)
    58       else if (i_plane.eq.3) then
    59         INCR = INCR*sqrt((a0+b0+d0)/c0)
    60       else if (i_plane.eq.4) then
    61         INCR = INCR*sqrt((a0+b0-d0)/c0)
    62       end if
    63       do I=1,NSADP
    64         SADP(i) = spec(i)
    65       end do
    66       RETURN
    67       END
    68 
    691      SUBROUTINE PYLOADSCF(NATP,ATYPES,SFDAT)
    702       
     
    8214               
    8315C fill common x-ray scattering factors
     16      debug = .FALSE.
    8417      DO J=1,NATP
    8518        WRITE(atom_l(J),'(A4)') ATYPES(J)
     
    8720          x_sf(I,J) = SFDAT(I,J)
    8821        END DO
    89 C        print *,ATYPES(J),(x_sf(I,J),I=1,9)
     22        if (debug) print '(1x,a4,9f10.6)',ATYPES(J),(x_sf(I,J),I=1,9)
    9023      END DO
    9124      intp_F = .TRUE.
     
    15083        xplcit = .FALSE.
    15184        IF (CNTRLS(6).NE.0) THEN
    152             l_cnt = CNTRLS(7)
     85            l_cnt = CNTRLS(6)
    15386            inf_thick = .FALSE.
    15487        ELSE
     
    188121      cell_gamma = CELL(4)*DEG2RAD
    189122C fill common layer stuff - atoms & symm
    190 C      print *,NL,LNUM,NU,LSYM
    191123      DO I=1,NATM
    192124        IL = NINT(ATMXOU(1,I))
    193125        IA = NINT(ATMXOU(2,I))       
    194126        a_type(IA,IL) = NINT(ATMXOU(3,I))
    195 C        print *,ATMTP(I),IL,IA,a_type(IA,IL),(ATMXOU(j,I),j=4,6)
    196127        a_number(IA,IL) = IA
    197128        WRITE(a_name(IA,IL),'(A4)') ATMTP(I)
     
    210141        l_symmetry(IL) = LSYM(IL)
    211142      END DO
    212 C      print *,IL,high_atom(IL),low_atom(IL)
    213143      n_actual = IL
    214144      n_layers = NL
     
    250180      END
    251181       
     182      SUBROUTINE PYGETSADP(CNTRLS,NSADP,SADP,HKLIM,INCR,NBLK)
     183       
     184Cf2py intent(in) CNTRLS
     185Cf2py intent(in) NSADP
     186Cf2py intent(in/out) SADP
     187Cf2py depend(NSADP) SADP
     188Cf2py intent(out) HKLIM
     189Cf2py intent(out) INCR
     190Cf2py intent(out) NBLK
     191   
     192      INCLUDE 'DIFFaXsubs/DIFFaX.par'
     193      INCLUDE 'DIFFaXsubs/DIFFaX.inc'
     194
     195      INTEGER*4 CNTRLS(7),NSADP,GET_SYM,i_plane,hk_lim,i,j,k
     196      INTEGER*4 HKLIM,NBLK
     197      REAL*8 SADP(NSADP),AGLQ16,l_upper,INCR
     198      LOGICAL ok
     199       
     200      EXTERNAL AGLQ16,GET_SYM                 
     201                   
     202      i_plane = CNTRLS(2)
     203      l_upper = CNTRLS(3)
     204C      print *,n_actual,(l_n_atoms(i),i=1,n_actual)
     205C      do j=1,n_actual
     206C        do i=1,l_n_atoms(j)
     207C          print *,a_name(i,j),(a_pos(k,i,j),k=1,3)
     208C        end do
     209C      end do
     210c      print *, recrsv,inf_thick,xplcit,rndm,l_cnt,has_l_mirror
     211C      do i=1,n_layers
     212C      print *,' layer',i
     213C         do j=1,n_layers
     214C            print *,'layer',j,l_alpha(i,j),(l_r(k,i,j),k=1,3)
     215C         end do
     216C      end do
     217      ok = .TRUE.
     218       
     219c      print *,cell_a,cell_b,cell_c,cell_gamma,pnt_grp,SymGrpNo
     220c      DoSymDump = .TRUE.
     221      CALL SPHCST()
     222      CALL DETUN()
     223      CALL OPTIMZ('GSAS-II',ok)
     224C      print *,lambda,max_angle,h_bnd,k_bnd,l_bnd,no_trials,
     225C     1  rad_type,X_RAY,n_atoms
     226C      print *,(l_g(j),j=1,n_layers)
     227C      do j=1,n_layers
     228C        print *,(hx_ky(i,j),i=1,l_n_atoms(j))
     229C        print *,(mat(i,j),i=1,n_layers)
     230C        print *,(mat1(i,j),i=1,n_layers)
     231C        print *,(l_phi(i,j),i=1,n_layers)
     232C      end do
     233      CALL GETSAD(AGLQ16,i_plane,l_upper,hk_lim,'GSAS-II',ok)
     234      NBLK = sadblock
     235      HKLIM = hk_lim+1
     236      INCR = dble(SADSIZE/2)/l_upper
     237      if (i_plane.eq.1) then
     238        INCR = INCR*sqrt(a0/c0)
     239      else if (i_plane.eq.2) then
     240        INCR = INCR*sqrt(b0/c0)
     241      else if (i_plane.eq.3) then
     242        INCR = INCR*sqrt((a0+b0+d0)/c0)
     243      else if (i_plane.eq.4) then
     244        INCR = INCR*sqrt((a0+b0-d0)/c0)
     245      end if
     246      do I=1,NSADP
     247        SADP(i) = spec(i)
     248      end do
     249      RETURN
     250      END
     251
    252252           
Note: See TracChangeset for help on using the changeset viewer.