Skip to main content

Introduction to Spring Systems

  • Chapter
  • First Online:
  • 1114 Accesses

Part of the book series: Springer Series in Solid-State Sciences ((SSSOL,volume 188))

Abstract

The new science of sound focuses on aspects of wave phenomena that have not been emphasized in traditional instruction. To elucidate these new aspects of wave phenomena, particularly the phase, in a clear exposition, we will rely on a number of simple models. We first define phase and group velocities using the one-dimensional monatomic harmonic crystal. Then, we advance to the diatomic one-dimension harmonic crystal and the one-dimensional harmonic crystal with alternating stiffness. We introduce the Green’s function approach to solving the wave equation, which will prove to be an indispensable tool in exploring phase related wave behavior. Three simple systems provide the basics of the Green’s function formalism, monatomic harmonic crystals with (1) a single mass defect, (2) a general perturbing potential, and (3) locally resonant structures. The introduction concludes with the introduction of Interface Response Theory (IRT) where we present the fundamental equations, introduce the cleavage operator, and demonstrate its use in a few examples. The Appendix 1 includes a Fortran77 code that will allow the reader to further explore the concepts presented here and in other chapters in greater detail.

This is a preview of subscription content, log in via an institution.

Buying options

Chapter
USD   29.95
Price excludes VAT (USA)
  • Available as PDF
  • Read on any device
  • Instant download
  • Own it forever
eBook
USD   139.00
Price excludes VAT (USA)
  • Available as EPUB and PDF
  • Read on any device
  • Instant download
  • Own it forever
Softcover Book
USD   179.99
Price excludes VAT (USA)
  • Compact, lightweight edition
  • Dispatched in 3 to 5 business days
  • Free shipping worldwide - see info
Hardcover Book
USD   179.99
Price excludes VAT (USA)
  • Durable hardcover edition
  • Dispatched in 3 to 5 business days
  • Free shipping worldwide - see info

Tax calculation will be finalised at checkout

Purchases are for personal use only

Learn about institutional subscriptions

References

  1. E.N. Economou, Green’s Functions in Quantum Physics (Springer, New York, 1990)

    Google Scholar 

  2. L. Dobrzynski, Interface response theory of composite systems. Surf. Sci. 200, 435 (1988)

    Article  ADS  Google Scholar 

  3. W.H. Press, S.A. Teukolsky, W.T. Vetterling, B.P. Flannery, Numerical Recipes in Fortran 77, 2nd edn. (Cambridge University Press, New York, 1992)

    MATH  Google Scholar 

Download references

Author information

Authors and Affiliations

Authors

Appendix 1: Code Based on Green’s Function Approach

Appendix 1: Code Based on Green’s Function Approach

Fortran 77 code used to calculate the transmission, density of state and transmission phase of an infinite chain with grafted finite side chains (For relevant equations see Sects. 1.8.4, 1.8.5 and 2.5). This code was used to generate the data of Figs. 1.9, 2.6, and 2.7.

C ************************** C definition of variables C ************************** IMPLICIT REAL*8(A-H,O-X) IMPLICIT COMPLEX*16(Y-Z) PARAMETER (NM=4) C NM needs to be fixed to NM=2*NC where NC is the number of chains C W is a arrays containing the various values of frequency C ETA is an array containing the reflection phase as a function of frequency C DEN is an array containing the difference of density of state between reference system (uncoupled) and coupled system DIMENSION W(15000),ETA(15000),DEN(15000) C ZGREEN is an array containing the complex Green’s function

C ZDEL is an array containing the matrix \( \overleftrightarrow{\Delta}(MM) \)

C VI is the coupling operator: \( \overleftrightarrow{V_I}(MM) \)

DIMENSION ZGREEN(NM,NM),ZDEL(NM,NM),VI(NM,NM) DIMENSION DIS(NM),YDEL(NM,NM),INDX(NM),XL(NM) DIMENSION YDENT(NM,NM)

C YAMD is \( \overleftrightarrow{A}\left(M,n\right) \)

DIMENSION YAMD(NM),YDM1AMD(NM) C YU is the vector U(M) DIMENSION YU(NM) C Output: file “TRANS.DAT” contains the transmission coefficient , transmission amplitude and transmission phase as functions of frequency OPEN(UNIT=2,FILE=’TRANS.DAT’,STATUS=OLD C OUTPUT: file “DENS.DAT” contains the reflection phase and the density of states as functions of frequency OPEN(UNIT=3,FILE=’DENS.DAT’,STATUS=OLD) C ************ C Parameters C ************ c NC : number of finite side chains NC=2 c Number of frequency intervals (NTOT) c Size of frequency interval (DELO) NTOT=1500 DELO=0.0015D00 C number Pi PI=ACOS(-1.D00) c XL : length of finite side chains (in terms of number of masses) XL(1)=5.D00 XL(2)=5.D00 C Spring constants of the infinite chain (BE1), side chains(BE2) C and coupling spring (BEI) BE1=1.D00 BE2=1.D00 BEI=1.D00 C Mass in infinite chain (AM1) and mass in side chains (AM2) AM1=1.D00 AM2=1.D00 c DIS(I) : position of side chains along the infinite chain in units of inter-mass spacing. DIS(1)=0.D00 DIS(2)=4.D00 C Normalization of arrays DO I=1,2*NC INDX(I)=0.D00 DO J=1,2*NC ZGREEN(I,J)=DCMPLX(0.D00,0.D00) VI(I,J)=0.D00 END DO END DO c VI : constructing the coupling operator DO I=1,NC IC=(I-1)*2 VI(IC+1,IC+1)=-BEI/AM1 VI(IC+1,IC+2)=BEI/AM1 VI(IC+2,IC+1)=BEI/AM2 VI(IC+2,IC+2)=-BEI/AM2 END DO C ********************************************* C Main loop over frequencies C ********************************************* W(1)=0.00000001D00 DO 1 IM=2,NTOT W(IM)=W(IM-1)+DELO WW=W(IM)**2

C Calculating \( \xi =1-\frac{m{\omega}^2}{2\beta } \) for infinite chain and side chains

CZ1=1.D00-AM1*WW/(2.D00*BE1) CZ2=1.D00-AM2*WW/(2.D00*BE2)

C Calculating t = ξ + i(1 − ξ 2)1/2 since − 1 ≤ ξ ≤ 1 for infinite chain and side chains

IF(ABS(CZ1).LT.1.D00) THEN AZ1=DSQRT(1.D00-CZ1*CZ1) ZT1=DCMPLX(CZ1,AZ1) ELSE SQR1=DSQRT(CZ1*CZ1-1.D00) IF(CZ1.GT.1.D00) ZT1=DCMPLX((CZ1-SQR1),0.D00) IF(CZ1.LT.-1.D00) ZT1=DCMPLX((CZ1+SQR1),0.D00) ENDIF C IF(ABS(CZ2).LT.1.D00) THEN AZ2=DSQRT(1.D00-CZ2*CZ2) ZT2=DCMPLX(CZ2,AZ2) ELSE SQR2=DSQRT(CZ2*CZ2-1.D00) IF(CZ2.LT.-1.D00) ZT2=DCMPLX((CZ2+SQR2),0.D00) IF(CZ2.GT.1.D00) ZT2=DCMPLX((CZ2-SQR2),0.D00) ENDIF

C Constructing the reference Green’s function , \( \overleftrightarrow{G_S}(MM) \)

C Components of \( \overleftrightarrow{G_S}(MM) \) from infinite chain (1.98)

DO I=1,NC DO J=1,NC IC=(I-1)*2 JC=(J-1)*2 POS1=DIS(I) POS2=DIS(J) CALL GR(ZT1,POS1,POS2,AM1,BE1,ZG0) ZGREEN(IC+1,JC+1)=ZG0 END DO END DO

C Components of \( \overleftrightarrow{G_S}(MM) \) from side chains (1.99)

DO I=1,NC ZT21=ZT2**(2.0D00*XL(I)) ZT22=(AM2/BE2)*(ZT2+ZT21)/((ZT2-1.0D00)*(1.0D00-ZT21)) IC=(I-1)*2 ZGREEN(IC+2,IC+2)=ZT22 END DO

C Calculation of the matrix \( \overleftrightarrow{\Delta}(MM) \)

DO I=1,2*NC DO J=1,2*NC ZDEL(I,J)=DCMPLX(0.D00,0.D00) DO K=1,2*NC ZDEL(I,J)=ZDEL(I,J)+VI(I,K)*ZGREEN(K,J) END DO END DO END DO DO I=1,2*NC ZDEL(I,I)=DCMPLX(1.D00,0.D0)+ZDEL(I,I) END DO

C Calculation of \( {\overleftrightarrow{\Delta}}^{-1}(MM) \)

NX=2*NC DO I=1,NX DO J=1,NX YDEL(I,J)=ZDEL(I,J) END DO END DO C Identity matrix DO I=1,NX DO J=1,NX YDENT(I,J)=DCMPLX(0.D0,0.D0) END DO YDENT(I,I)=DCMPLX(1.0D0,0.D0) END DO CALL LUDCMP(YDEL,NX,NX,INDX,D) C LUDCMP is a subroutine for the lower-upper decomposition of matrices from “Numerical Recipes” see reference [3] C YDEL contains the LU decomposition C******************************************* C Calculation of the transmission phase (see Chap. 2 for details)

C calculation of the determinant of the matrix \( \overleftrightarrow{\Delta}(MM) \) from its LU decomposition

ZD=DCMPLX(D,0.D00) DO I=1,NX ZD=ZD*YDEL(I,I) END DO ZN1=ZD C Calculation of the transmission phase from the determinant for each frequency (See Chap. 2) IF(ZN1.NE.DCMPLX(0.D00,0.D00))THEN ZN2=CDLOG(ZN1) PII=1.D00/PI ETA(IM)=-PII*DIMAG(ZN2) ELSE ETA(IM)=0.D00 ENDIF C************************************************

C Calculation of the inverse matrix \( {\overleftrightarrow{\Delta}}^{-1}(MM) \)

C LUBKSB calculates the inverse from the LU decomposition (see reference [3]) DO J=1,NX CALL LUBKSB(YDEL,NX,NX,INDX,YDENT(1,J)) END DO

C the matrix YDENT now contains the matrix \( {\overleftrightarrow{\Delta}}^{-1}(MM) \)

C calculating \( \overleftrightarrow{A}\left(M,n\right) \)

DO I=1,NC IC=(I-1)*2 POS1=DIS(I) POWER=1.D0-POS1 ZTEMP=(AM1/BE1)*(ZT1**POWER)/(ZT1**2.D00-1.D00) YAMD(IC+1)=VI(IC+1,IC+1)*ZTEMP YAMD(IC+2)=VI(IC+2,IC+1)*ZTEMP ENDDO C calculating the transmission coefficient DO I=1,NX YDM1AMD(I)=DCMPLX(0.D0,0.D0) DO J=1,NX YDM1AMD(I)=YDM1AMD(I)+YDENT(I,J)*YAMD(J) ENDDO ENDDO DO I=1,NC IC=(I-1)*2 POS1=DIS(I) YU(IC+1)=ZT1**POS1 YU(IC+2)=DCMPLX(0.D0,0.D0) ENDDO YTR=DCMPLX(0.D0,0.D0) DO I=1,NX YTR=YTR+YU(I)*YDM1AMD(I) ENDDO YTR=DCMPLX(1.0D0,0.D0)-YTR RZTR=DREAL(YTR) SZTR=DIMAG(YTR) C Transmission coefficient TRANS=RZTR**2+SZTR**2 C Writing transmission coefficient , TRANS, transmission amplitude (RZTR, SZTR), and transmission phase ATAN(SZTR/RZTR) as functions of frequency to file WRITE(2,*)W(IM),TRANS, RZTR,SZTR,ATAN(SZTR/RZTR) 1 CONTINUE C######################### C Calculation of the derivative of the reflection phase with respect to the eigen value (square of frequency) to obtain the variation in density of state C######################### DO 2 I=1,NTOT-1 DIFF=ETA(I+1)-ETA(I) DEN(I)=DIFF/(W(I+1)**2.0D00-W(I)**2.0D00) IF((DEN(I).GT.100.D00).OR.(DEN(I).LT.-100.D00)) GOTO 2 C Write reflection phase ETA and density of states DEN as functions of frequency W. WRITE(3,*)W(I),ETA(I),DEN(I) 2 CONTINUE C************************************************************** STOP END C ********************************************************************** SUBROUTINE GR(ZT1,POS1,POS2,AM1,BE1,ZG0) IMPLICIT REAL*8(A-H,O-Y) IMPLICIT COMPLEX*16(Z) POWER=DABS(POS1-POS2)+1.D00 ZINT=(ZT1**POWER)/(ZT1**2.D00-1.D00) ZG0=(AM1/BE1)*ZINT RETURN END SUBROUTINE LUDCMP(Y,N,NP,INDX,D) IMPLICIT REAL*8(A-H,O-X,Z) IMPLICIT COMPLEX*16(Y) PARAMETER (NMAX=1000,YTINY=DCMPLX(1.0D-32,0.d00)) DIMENSION Y(NP,NP),VV(NMAX) DIMENSION INDX(N) D=1.D00 DO 12 I=1,N AAMAX=0.D00 DO 11 J=1,N IF (CDABS(Y(I,J)).GT.AAMAX) AAMAX=CDABS(Y(I,J)) 11 CONTINUE IF (AAMAX.EQ.0.) PAUSE 'Singular matrix.' VV(I)=1./AAMAX 12 CONTINUE DO 19 J=1,N IF (J.GT.1) THEN DO 14 I=1,J-1 YSUM=Y(I,J) IF (I.GT.1) THEN DO 13 K=1,I-1 YSUM=YSUM-Y(I,K)*Y(K,J) 13 CONTINUE Y(I,J)=YSUM ENDIF 14 CONTINUE ENDIF AAMAX=0.d00 DO 16 I=J,N YSUM=Y(I,J) IF (J.GT.1) THEN DO 15 K=1,J-1 YSUM=YSUM-Y(I,K)*Y(K,J) 15 CONTINUE Y(I,J)=YSUM ENDIF DUM=VV(I)*CDABS(YSUM) IF (DUM.GE.AAMAX) THEN IMAX=I AAMAX=DUM ENDIF 16 CONTINUE IF (J.NE.IMAX) THEN DO 17 K=1,N YUM=Y(IMAX,K) Y(IMAX,K)=Y(J,K) Y(J,K)=YUM 17 CONTINUE D=-D VV(IMAX)=VV(J) ENDIF INDX(J)=IMAX IF(CDABS(Y(J,J)).EQ.0.d00) Y(J,J)=YTINY IF(J.NE.N) THEN YUM=1.d00/Y(J,J) DO 18 I=J+1,N Y(I,J)=Y(I,J)*YUM 18 CONTINUE ENDIF 19 CONTINUE IF(CDABS(Y(N,N)).EQ.0.d00) Y(N,N)=YTINY RETURN END SUBROUTINE LUBKSB(Y,N,NP,INDX,YB) IMPLICIT REAL*8(A-H,O-X,Z) IMPLICIT COMPLEX*16(Y) DIMENSION Y(NP,NP),INDX(N),YB(N) II=0 DO 12 I=1,N LL=INDX(I) YSUM=YB(LL) YB(LL)=YB(I) IF(II.NE.0)THEN DO 11 J=II,I-1 YSUM=YSUM-Y(I,J)*YB(J) 11 CONTINUE ELSE IF (YSUM.NE.DCMPLX(0.D0,0.D0)) THEN II=I ENDIF YB(I)=YSUM 12 CONTINUE DO 14 I=N,1,-1 YSUM=YB(I) DO 13 J=I+1,N YSUM=YSUM-Y(I,J)*YB(J) 13 CONTINUE YB(I)=YSUM/Y(I,I) 14 CONTINUE RETURN END

Rights and permissions

Reprints and permissions

Copyright information

© 2017 Springer International Publishing AG

About this chapter

Cite this chapter

Deymier, P., Runge, K. (2017). Introduction to Spring Systems. In: Sound Topology, Duality, Coherence and Wave-Mixing. Springer Series in Solid-State Sciences, vol 188. Springer, Cham. https://doi.org/10.1007/978-3-319-62380-1_1

Download citation

Publish with us

Policies and ethics