United States Department of the Interior Geological … · Department of the Interior Geological...

24
United States Department of the Interior Geological Survey DITT: A Computer Program for Data Interpretation for ^Torsional Tests by Albert T. F. Chen OPEN-FILE REPORT 79-1463 This report is preliminary and has not been edited or reviewed for conformity with Geological Survey standards and nomenclature Menlo Park, California September 1979

Transcript of United States Department of the Interior Geological … · Department of the Interior Geological...

Page 1: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

United StatesDepartment of the Interior

Geological Survey

DITT: A Computer Program for Data Interpretation for ^Torsional Tests

by

Albert T. F. Chen

OPEN-FILE REPORT 79-1463

This report is preliminary and has not been edited or reviewed for conformity with Geological Survey standards and

nomenclature

Menlo Park, California

September 1979

Page 2: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

DITT: A Computer Program for Data Interpretation for Torsional Jests

by

Albert T. F. Chen

INTRODUCTION

Recent advances in testing technology have allowed soil samples to be

loaded in the torsional mode to the nonlinear strain range of most soils.

However, the effect of this nonlinearity on data interpretation from these

tests has been given only limited attention. In an effort to investigate

systematically this problem, the U. S. Geological Survey undertook a study

in which the torque-twist curves from various stress-strain relations for

soils were computed and the effective shear modulus and hysteretic

damping based on these torque-twist curves were examined. Results and

recommendations concerning data interpretation from that study were

presented in an earlier report (Chen and Stokoe, 1979). The computer

program, DITT, that was used to generate torque-twist curves and associated

results is the subject of this report.

DITT can be used for two purposes. It can be used to compute

torque-twist relations for torsional vibration analysis of cylindrical

test specimens of materials not restricted only to soils. DITT can also

be used to estimate correction factors of shear modulus and hysteretic

damping for interpreting torsional testing data. In the following sections,

a general description, the input requirements, and the listing of the

computer program are presented. In addition, results from a sample computer

run are shown.

1

Page 3: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

GENERAL DESCRIPTION

The program accepts any type of input stress-strain relation assigned

to the soil under consideration and considers both solid and hollow

cylindrical soil samples of circular cross-section. If the input

stress-strain relation is not the modified Hardin and Drnevich (H&D) type

with parameters a and b (Hardin and Drnevich, 1972) or the Ramberg-Osgood

(R&O) type with parameters o(, R and C1 (Richart, 1975), the stress-strain

relation is input in a p ie c ewi se- linear manner (the multi-linear case, Chen

and Joyner, 197*0.

To compute the torque, T, on a given circular cross-section due to a

given twist per unit length, 0, DITT divides the cross-section into a

specified number of concentric rings of equal areas, computes the average

strain and stress on each ring, and determines the sum of the torque on

each ring by using:

where T is the torque on the total cross-section, N is the number of

subdivisions, Tj is the average shear stress in the i ring, and A

. are the area and the average radius of the i ring, respectively, as

shown in Fig. 1. Note that Tj is specified by the input stress-strain

relation for an average shear strain of jf. which is

Vj fi £ (2)

Page 4: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

A -

Figure 1. Definition of terms used with a circular cross*section,

Page 5: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

For comparison purposes, shear stress and shear strain at the

periphery (the outermost ring from the center), "C» and tf» , are chosen

as reference values. Shear modulus, GO*), and damping ratio, !X(>w)» are

then computed with respect to these reference values. The use of these

reference values enables the investigator to relate quantities determined

from the T-V plane with those determined from the T-0 plane through

Eq.(2).

Normalized quantities associated with the r-V plane are defined as:

= X/TW* (normalized stress)

= 6f/ £fm*x (normalized modulus) (3)

= f/ y*)*x (normalized strain)

where Tm^and £fnw*K are, respectively, the maximum shear stress and the

maximum shear modulus, and ^Vrf- , the reference strain, is defined as:

J'ref = r^lm** W

On the T-0 plane, effective shear modulus, 6[cj» * is defined as:

6f^y = T/(J»0) (5)

where

Page 6: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

is the polar moment of inertia of the cross section.

Normalized quantities associated with the T-0 plane are:

"I* = T/~fr*f (normalized torque)

= $/$?*( (normalized twist) (7)

6f f t ~ e (normalized effective modulus)

where, taking tf as the outside radius of the specimen,

is the reference twist, and

(8)

= J '<W >r* (9)

is the reference torque.

Damping ratios are determined on the basis of the energy lost per

strain (twist) cycle as a result of the hysteresis loop generated on the

T-V (or T-0) plane. The damping ratio, X(T») (°r A*ft &s in the case of

T-0 plane), is computed according to:

(10)

where /|fc and At ar*e> respectively, areas of the loop and the triangle as

Page 7: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

shown in Fig. 2. The shape of the loop is assumed to follow Masing's

criterion (Masing, 1926). It should be noted that, for small strains, most

input stress-strain relations are essentially linear and the value of >^ in

Eq.(10) becomes very small or zero. Any computation involving the damping

in this small strain range may thus become unreliable. When this situation

occurs, the program replaces these unreliable values by 9.99 or 9.9999 to

alert the user.

The equivalent radius for modulus or damping is defined as the radius

at which the shear strain corresponds to a shear modulus or damping ratio

on the T-y plane which is equal to G^* or ̂ e# Equivalent radii are

determined by iteration in DITT and their use is presented elsewhere

together with the advantages of using normalized quantities (Chen and

Stokoe, 1979).

Quantities defined so far are all dependent on the variable 0. To

assure that the proper range of interest in 0 is covered while computing,

0 is assigned such that its normalized value has 20 equal increments per-3 -»3

logarithmic cycle that ranges from 0*=10 to 0*=10 . The results are

stored in a 16x121 matrix which is used for printer output or plotting.

DITT is coded in FORTRAN IV for the IBM 370 system. The program

contains 281 source statements and requires a storage allocation of 50K

bytes. Execution time for each run is less than 6 seconds. Without the

addition of subroutines, the program can be easily modified to suit special

individual needs or other computing devices.

Page 8: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

Figure 2. Definition of hysteretic damping

Page 9: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

INPUT REQUIREMENTS

In most cases, DITT requires three input data cards. In the multi­

linear case, however, the third input data card is replaced by M cards

where M is the number of linear segments in the input multi-linear stress-

strain relation.

Card 1 FORMAT(18A4)

col 1-72 Title of computation for identification.

Card 2 FORMAT(4F12.0,216)

col 1-12 Outside sample radius in cm.col 13-24 Inside sample radius in cm (=0.0, for solid samples).col 25-36 Gmax in KPa.col 37-48 Tmax in KPa.col 49-54 KTYPE^O, an index to specify type of stress-strain input,col 58-60 N 101, the number of subdivisions needed (see Eq. 1).

If KTYPE=0, the use of modified H&D relation is specified and the

program reads:

Card 3 FORMAT(2F12.0)

col 1-12 Parameter a of the modified H&D relation, col 13-24 Parameter b of the modified H&D relation.

If KTYPE=1, the use of the R&O relation is specified and the program

reads:

Card 3 FORMAT(3F12.0)

col 1-12 Parameter c< of the R&O relation,col 13-24 Parameter R of the R&O relation,col 25-36 Parameter C1 of the R&O relation.

Page 10: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

If KTYPE=M, and M is greater than 1, the multi-linear relation is

specified and the program reads M pairs of non-zero, normalized strain,

y f , and normalized stress, tl f » in the order of increasing strain:

Cards 3(1) 1=1,M FORMAT(2F12.0)

col 1-12 The I normalized strain value, col 13-24 The Ith normalized stress value.

REFERENCES CITED

Chen, A. T. F., and Stokoe, K. H., II, 1979, Interpretation of strain- dependent modulus and damping from torsional soil tests: Report No. USGS-GS-79-002, NTIS, Clearinghouse, Springfield, VA 22151, 45 pages.

Chen, A. T. F., and Joyner, W. B., 1974, Multi-linear analysis for ground motion studies of layered systems: Report No. USGS-GD- 74-020, NTIS No. PB232-704/AS, Clearinghouse, Springfield, VA 22151, 48 pages.

Hardin, B. 0., and Drnevich, V. P., 1972, Shear modulus and damping in soils design equations and curves: Journal of the Soil Mechanics and Foundations Division, ASCE, vol. 98, no. SM7, Proc. Paper 9006, July, pp. 667-692.

Masing, G., 1926, Eigenspannugen und verfestigung beim messing: Proceedings of the Second International Congress of Applied Mechanics, pp. 160-195

Richart F. E., Jr., 1975, Some effects of dynamic properties on soil- structure interaction: Journal of the Geotechnical Engineering Division, ASCE, vol. 101, no. GT12, Proc. Paper 11764, December, pp. 1193-1240.

Page 11: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

SOURCE LISTING

c«C* DITT: DATA INTERPRETATION FOR TORSIONAL TESTSC»C« 6/79, BY ALBERT T. F. CHEN, U. S. GEOLOGICAL SURVEY, MS?1*C« 345 MIDDLEFIELD ROADC* MENLO PARK, CA 94025C«

CCC REQUIRED .UNITS FOR 1-0 PARAMETERS:CC RADIUS, AREAS CM, CM*CMC ALL G'S, ALL TAU'S KPA (1 PA = 10 DYNES/CM/CM)C PHY, ANGLE OF TWIST/UNIT LENGTH RAD/CMC TORQUE -- NEWTONS-CMC

REAL*8 YINT, RODIMENSION R(201), RB(101), RC(101), XQ(16,126), TITLE(18),

&ICOUNT(101), SIGY(103), EM(103), XX(127), YY(12?)C

2 FORMAT('1'///5X, 'TORQUE, TWIST AND RELATED CALCULATIONS * * *'//)4 FORMAT (18A4)6 FORMAT(4F12.0, 216)8 FORMAT(3F12.0)

10 FORMAT(2F12.0)12 FORMAT(5X,18A4)14 FORMATC//10X, ' OUTSIDE SAMPLE RADIUS, RO=',F7.3,' CM. 1&/10X,' INSIDE SAMPLE RADIUS, RI=',F7.3,' CM. 1&/10X, ' NUMBER OF DIVISIONS, N = ,14&/10X, ' OUTER MOST RADIUS, RC(N) = ,F8.5,' CM 1&//10X, 'TOTAL CROSS-SECTIONAL AREA, ATOTAL = ,F9.3,' SQ.CM. '&/10X, ' POLAR MOMENT OF INERTIA, PMI = ,F9.3,' CM**4.'&//10X, INPUT MAX. SHEAR MODULUS, GMAX = ,E11.4, KPA 1&/10X, INPUT MAX. SHEAR STRESS, TAUMAX = ,E11.4, KPA 1&//10X, REFERENCE STRAIN, GMAREF = ,E11.4, ABSOLUTE 1&/10X, REFERENCE TWIST/LENGTH, PHYREF = ,E11.4, RAD/CM'&/10X, f REFERENCE TORQUE, TRQREF = ,E11.4, NEWTONS-CM 1 )

16 FORMATC/5X, »HARDIN-DRNEVICH RELATION, A^FIO.e, 1 B=»,F9.6)18 FORMAT(/5X,'RAMBERG-OSGOOD PARAMETERS ARE (A,R,C1 ) : ,3F8.3//)20 FORMATC 1 INPUT FOR N-LINEAR RELATION: I YIELD STRAIN ',

& 'YIELD STRESS'/(30X,I3,2E14.5))22 FORMAT( 12X, ' 1 ' , 13X, '2' , 13X, '3 f , 13X, '4' , 13X, '5 f , 13X, »6' , 13X, '7 f ,

& 13X,'8')24 FORMAT (8X, ' STRAIN AT' ,5X, 'STRESS AT' ,4X, 'SECANT SHEAR', 4X

& ' HYSTERETIC ' , 4X , ' TWIST PER ' , 1 8X , ' EFFECTIVE ' , 5X , ' EFFECTIVE ' /8X& ' PERIPHER Y ', 5X,' PERIPHERY ',6X,' MODULUS ',5X,» DAMPING RATIO ',2X& 'UNIT LENGTH ',5X, f TORQUE ',7X,' MODULUS ',7X, 'DAMPING'/' I',5X,& ' (ABSOLUTE) ' ,6X, » (KPA) ' ,9X, ' (KPA) ' ,7X, ' (ABSOLUTE) ' , 5X,

DITT001DITT002DITT003DITT004DITT005DITT006DITT007DITT008DITT009DITTO 10DITTO 11DITTO 12DITTO 13DITT014DITT0 15DITTO 16DITTO 17DITTO 18DITTO 19DITT020DITT021DITT022DITT023DITT024DITT025DITT026DITT027DITT028DITT029DITT030DITT031DITT032DITT033DITT034DITT035 /DITTO 36DITT037DITT038DITT039DITT040DITT041DITT042DITT043DITT044DITT045DITT046DITT047DITT048DITT049DITT050

10

Page 12: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

& ' (RAD/CM) ', 4X,' (NEWTONS-CM) ', 5X,' (KPA) ' ,7X, ' (ABSOLUTE) IV) 26 FORMAT(8X,'NORMALIZED',4X,'NORMALIZED',4X,'NORMALIZED',4X,

& 'NORMALIZED',5X,'EFFECTIVE',4X,'EQUIVALENT',5X,'RATIO IN',5X, 'EQUIVALENTV9X, 'STRAIN',9X, 'STRESS 1 ,8X, 'TWIST',8X, 'TORQUE',6X, 'MODULUS RATIO',' RADIUS RATIO',5X,'DAMPING',4X,'RADIUS RATIO'/

I (1)/REF.STRAIN',3X,'(2)/TAUMAX',3X,'(5)/REF.TWIST' tr ,5X,

& && '

& &

' (6)/REF.TORQ',5X,'(3)/(7)',6X,'(MODULUS)',6X,' '(DAMPING)',3X,'I'/)

28 FORMAT(13X,'9*,12X,'10',12X,'11',12X,'12',12X,'13 f ,12X,'& '15 f ,12X,'l6')

30 FORMAT(I4,8E14.5,I4) 42 FORMATC1 ') 44 FORMAT(' ')

READ ALL INPUT DATA

50 READ(5,4,END=2000) TITLEREAD(5,6) RADOU, RADIN, GMAX, TAUMAX, KTYPE, NIF(KTYPE .EQ. 0) READ(5,8) AHD, BHDIF(KTYPE .EQ. 1) READ(5,8) AAA, BBB, CCCIF(KTYPE .GT. 1) READ(5,10) (EM(I), SIGY(I), 1=1,KTYPE)

WRITE(6,2)WRITE(6,12) TITLE

PI = 3.1415927ISTOP = 121B1 = BBB - 1.0ATOTAL = PI*(RADOU**2-RADIN**2)PMI = 0.5*PI*(RADOU**4-RADIN**4)AREAIN = PI*RADIN*RADINN2 = 2 * NDA = ATOTAL/NDO 100 1=1,N2ATEMP = AREAIN + 0.50*DA*IR(I) = SQRT(ATEMP/PI)

100 CONTINUERB(1) = RADINRADIUS = RADOUDO 200 1=1,NJ = 2*1 - 1K = 2*1RC(I) = R(J) * 1.RBU+1) = R(K)*1.ICOUNT(I) = 1

200 CONTINUEGMAREF = TAUMAX/GMAXPHYREF = GMAREF/RADIUSTRQREF = GMAX*PMI*PHYREF/10.PHYSTR = 0.001*PHYREF

, 12X,

DITTOS1DITT052DITT053DITT054DITT055DITT056DITT057DITT058DITT059DITT060DITT061DITT062DITT063DITTO64DITT065DITT066DITT067DITT068DITT069DITT070DITT071DITT072DITT073DITT074DITT075DITT076DITT077DITT078DITT079DITT080DITTOS1DITT082DITT083DITT084DITT085DITT086DITT087DITT088DITT089DITTO90DITT091DITT092DITT093DITT094DITT095DITT096DITT097DITT098DITT099DITT100

11

Page 13: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

380390

400

420

450

PHYSTP = 10000.*PHYREF

WRITEC6, 14) RADOD,RADIN,N,RC(N) ,ATOTAL,PMI,GMAX,TADMAX,GMAREF, & PHYREF,TRQREF WRITE(6,44)IF(KTYPE .EQ. 0) WRITE(6,16) AHD, BHD IFCKTYPE .EQ. 1) WRITE(6,18) AAA, BBB, CCC IFCKTYPE .GT. 1) WRITE(6,20) (EM(I), SIGY(I), I=1,KTYPE)

IFCKTYPE .NE. 0) GO TO 450

KTYPE = 0, CASE OF H&D DO 420 I=1,ISTOP PHYEXP = 0.05*(I-1) PHYO = PHYSTR*10.0**PHYEXP SUM =0.0 DO 400 J=1,N GMA = PHYO * RC(J) ARG = BHD*GMA/GMAREF IFCARG .GT. 88.0) GO TO 380 HYGMA = GMA*(1.+AHD*EXP(-ARG))/GMAREF GO TO 390HYGMA = GMA/GMAREF TAU = GMAX*GMA/(1.+HYGMA) DM = TAU*DA*RC(J)/10. SUM = SUM + DM

GMATAUTAU/GMAPHYOSUM10.*SUM/PHYO/PMIGMA/GMAREF

; TAU/TAUMAX: PHYO/PHYREF: SUM/TRQREF-. XQ(3,D/XQ(7,D

XQ(2,I) XQ(3,D XQ(5,I) XQ(6,I) XQ(7,D XQ(9,D XQ(10,I)

XQ(12,I) : XQ(13,D : CONTINUE GO TO 600

FOR R&O, OR MULTI-LINEAR CASES IFCKTYPE .GT. 1) GO TO 465 SIGYC1) =0.0 EM(1) = 0.0 DO 460 J=2,102 RAEXP = 0.02*(J-2) RATIO = 0.01*10.0**RAEXP ARG = RATIO/CCC SIGY(J) = RATIO*TAUMAX

DITT101DITT102DITT103DITT104DITT105DITT106DITT107DITT108DITT109DITT110DITT111DITT112DITT113DITT114DITT115DITT116DITT117DITT118DITT119DITT120DITT121DITT122DITT123DITT124DITT125DITT126DITT127DITT128DITT129DITT130DITT131DITT132DITT133DITT134DITT135DITT136DITT137DITT138 ;DITT139-DITT140DITT141DITT142DITT143DITT144DITT145DITT146DITT147DITT148DITT149DITT150

12

Page 14: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

460

465

470475

510

520

530540560

580

600

EM(J) = CCC»GMAREF»ARG*(1.+AAA«ARG««B1)CONTINUEIMAX = 102GO TO 475IMAX = KTYPEEM(1) = 0.0SIGYC1) = 0.0DO 470 1=2, IMAXSIGY(I) = SIGY(I)*TAUMAXEM(I) = EM(I)«GMAREFCONTINUECONTINUEDO 580 I=1,ISTOPPHYEXP = 0.05*(I-1)PHYO = PHYSTR«10.0««PHYEXPSUM = 0.0DO 560 J=1,NGMA = PHYO « RC(J)JC = ICOUNT(J)IF(JC .GE. IMAX) GO TO 530IF(GMA .LE. EMCJC+1)) GO TO 520ICOUNT(J) = JC+1GO TO 510TAU=SIGY(JC)-i-(GMA-EM(JC))«(SIGY(JC+1)-SIGY(JC))/(EM(JC+1)-EM(JC))GO TO 540TAU = TAUMAXDM = TAU«DA*RC(J)/10.SUM = SUM + DM

DM IS THE TORQUE TAKEN BY ITH RING, IN NEWTONS-CM

: GMA

: TAU

: TAU/GMA : PHYO: SUM

: 10.«SUM/PHYO/PMI : GMA/GMAREF = TAU/TAUMAX = PHYO/PHYREF = SUM/TRQREF = XQ(3,D/XQ(7,D

XQ(2,I) XQ(3,D XQ(5,I) XQ(6,I) XQ(7,D XQ(9,D XQ(10,I)

XQ(12,I) XQ(13,D CONTINUE

650

CONTINUEDO 850 I=1,ISTOPGPK = XQ(7,DDO 650 LOOP=1,IJM = I-LOOPIFCGPK .LE. XQ(3,JM)) GO TO 700CONTINUE

DITT151DITT152DITT153DITT154DITT155DITT156DITT157DITT158DITT159DITT160DITT161DITT162DITT163DITT164DITT165DITT166DITT167DITT168DITT169DITT170DITT171DITT172DITT173DITT174DITT175DITT176DITT177DITT178DITT179DITT180DITT181DITT182DITT183DITT184DITT185DITT186DITT187DITT188.'DITT189DITT190DITT191DITT192DITT193DITT194DITT195DITT196DITT197DITT198DITT199DITT200

13

Page 15: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

700 JSET = JMIF(JSET .EQ. 0) GO TO 750DENO = XQ(3,JSET+1)-XQ(3,JSET)IFCDENO .GE. 0.0) GO TO 750DGRT = (GPK-XQ(3,JSET))/DENORHS = ALOG(XQ(1,JSET)) + 0.05*DGRT»2.302585GMAEQ = EXP(RHS)XQ(14,I) = GMAEQ/XQ(1,I)GO TO 800

750 XQ(14,I) = 1.0 800 CONTINUE850 CONTINUE »

: FOR DAMPING COMPUTATION *

DO 1200 11=1,21=211 = 1IF(II .EQ. 2) 1=6IF(II .EQ. 2) 11=5DO 1000 JLOOP=2,ISTOPXX(1) = -XQ(I1,JLOOP)XO = XX(1)YO = -XQU.JLOOP)YY(1) = 0.0RO = YO/XODO 900 J=1,JLOOPXXCJ+1) = XO + 2.*XQ(I1,J)YINT = RO*XX(J+1)YYCJ+1) = YO + 2.*XQ(I,J) - YINT

900 CONTINUESUM =0.0DO 950 J=1,JLOOPDSUM = 0.5*(YY(J)+YY(J+1))*(XX(J+1)-XX(J))SUM = SUM + DSUM

950 CONTINUEJJJ=JLOOP+1XQ(II*4,JLOOP) = SUM/(1.*PI*XO*YO)

1000 CONTINUEXQ(II*4,1) = 0.0

1200 CONTINUE«

XQ(15,1) = 9.9999XQ(16,1) = 9.99DO 1600 J=2,ISTOPIF(XQ(8,J) .EQ. 0.0) GO TO 1300XQ(15,J) = XQ(*I,J)/XQ(8,J)GO TO 1350

1300 XQ(15,J) = 9.9999 1350 DPK = XQ(8,J)

DITT201DITT202DITT203DITT20*!DITT205DITT206DITT207DITT208DITT209DITT210DITT211DITT212DITT213DITT214DITT215DITT216DITT217DITT218DITT219DITT220DITT221DITT222DITT223DITT224DITT225DITT226DITT227DITT228DITT229DITT230DITT231DITT232DITT233DITT234DITT235DITT236DITT237DITT238DITT239DITT240DITT241DITT242DITT243DITT244DITT2M5DITT246DITT247DITT248DITT249DITT250

14

Page 16: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

IF(DPK .LE. 0.0) GO TO 1500DO 1400 LOOP = 1,JJM = J - LOOPIF(DPK .LE. 0.0) GO TO 1500IF(DPK .GE. XQ(4,JM)) GO TO 1450

1400 CONTINUE 1450 JSET = JM

IF(XQ(4,JSET) .LE. 0.0) GO TO 1500DDRT = (DPK-XQ(4,JSET))/(XQ(4,JSET+1)-XQ(4,JSET))RHS = ALOG(XQ(1,JSET)) + 0.05*DDRT*2.302585GMAEQ = EXP(RHS)XQ(16,J) = GMAEQ/XQ(1,J)GO TO 1550

1500 XQ(16,J) = 9.99 1550 CONTINUE1600 CONTINUE

*

WRITE(6,42)WRITE(6,22)WRITE(6,24)DO 1700 I=1,ISTOPWRITE(6,30) I,(XQ(JK,I),JK=1,8),I

1700 CONTINUEWRITE(6,42)WRITE(6,28)WRITE(6,26)DO 1800 I =1,ISTOPWRITE(6,30) I,(XQ(JK,I),JK=9,16),I

1800 CONTINUEGO TO 50

2000 STOPEND

DITT251 DITT252DITT253DITT254DITT255DITT256DITT257DITT258DITT259DITT260DITT261DITT262DITT263DITT264DITT265DITT266DITT267DITT268DITT269DITT270DITT271DITT272DITT273DITT274DITT275DITT276DITT277DITT278DITT279DITT280DITT281DITT282

15

Page 17: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

SAMPLE PROBLEM

To illustrate the use of DITT, a sample problem is prepared and

presented in this section. The problem considers a solid cylindrical soil

specimen with an outside radius of 4.0 cm. The soil has a maximum shear

modulus of 50000 KPa, a maximum shear stress of 100KPa, and is described by

the H&D hyperbolic relation (KTYPE=0 with both parameters, a and b, equal

to 0.0). The number of subdivisions, N, is set at 50. Input data cards

for this problem thus are:

Column 1234567 1234567890123456789012345678901234567890123456789012345678901234567890

DITT: SAMPLE RUN, 7/07/79 (Card 1)

4.0 0.0 50000.0 100.0 0 50 (Card 2)

0.0 0.0 (Card 3)

The computer output for this problem is included next. Since the

output is quite self-explanatory, no further remarks are necessary.

16

Page 18: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

TORU

UE*

TWIS

T AND

RELATED CALCULATIONS

oiTTi

SAMPLE R

UN*

7/07

/79'

OUTSIDE SAMPLE RADIUS* R0

» 4.000 CM

.IN

SIDE

SAMPLE RADIUS, RI

» 0.

0 CM

.NUMBER OF

DIVISIONS, N

a bO

OUTER MO

ST RADIUS, RC(N)

» 3.97995 CM

TOTAL CROSS-SECTIONAL AREA*

ATOTAL »

SO.265 SO

.CM.

POLAR MOMENT OF INERTIA. PM

I

«»02.124

INPU

T MA

X. SHEAR MODULUS* GMAX »

0.5000E OS

KP

AINPUT

MAX. SHEAR

STRESS* TAUMAX

0.1000E 03 KP

A

REFEHENCE STRAIN* GMAREF »

0.2000E-02 ABSOLUTE

REFERENCE TWIST/LENGTH* PHYREF »

0.5000E-03 RAD/CM

REFERENCE TORQUE* TRQREF »

0.1005E 04

NEWTONb-CM

HARDIN-DRNEVICH RELATION* Am

0.0

R« 0,

0

Page 19: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

fwivi<xiivifxi<\f(Wfwivifwr)r>r>r>r><*)<*)r><*)r)««

> o>-

^

^ ^) 1,1 UJ UJ |tl m 1,1 l,f i,t ^,1 i.l U,» UJ UJ 1,1 1,1 1,1 1m* ^,1 t»l UJ UJ 1,1 llj llj 1,1 1,1 |^J 1.1 1,1 i,l 1,1 1,1 !,« |j,| 1^1 llj 1,1 I^J l^t 1,1 1,1 ^ I^J 1,1 |^ ItJ ^* 1,1 IjJ 1,' |jj |^l ^|l ^J 1,1

CZ mof. jr^tvc* ocao *^4«,

in « * r- ec o _ . »v rv tv ix r-,

o. 2 3 i

> Ji c oo»f\j^ . IT -»fr

-. cv.iv

. «

1 UJ ^i ^i *« t 1,1 m uj i f i uj u;

ooooooooooooooc -^ »- .- »- fv;

U. «». 1,1 i f i u; iij uf *f_* IA! i*» uj bJ bJ U>' '** iu tfl* UJ hj UJinz « o c IT. IT. fv.1 " iri j fo^irao tc

ru IT. a. a oir « -.»< «vn<c<^»n-«»\.-9<t.j o-

«r -x * f Z T _< o

_ioicir(Cf^ryo-iro« c»-*o«rivcfi>t^tno^iroc

i i i i i « i i i i i i i i i i i

18

Page 20: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

t * IUJ U' UJ UJ UJ Ul U.' UJ UJ UJ U> UJ UJ U) UJ UJ U,' UJ UJ U.1 UJ UJ UJ UJ UJ UJ U.' U,- UJ UJ UJ UJ UJ UJ UJ UJ UJ UJ U.' UJ UJ UJ U" U,' It" U.' U.1 W UJ U.' U.' U-' U-' u.' U.' U> U> U' U.1 U,' U.

lUJUJUjUJUJUJUJU.'UJUJU.'bJUJU.'U.'U,

«C f- « «V

I> llltlllllltlllltltllllllllltltllll 1llllll~~~~~~~~

coo

I

no f\»«t.»jn«a>ff' *"

i(vifMrvruiMrunjiMrwfMixiMrvjnjfVfv<fvirt.(\.iM(virurwrv.

I UJ UJ U." UJ UJ UJ UJ UJ LC t*J UJ UJ UJ UJ Titf ' UJ UJ UJ bj UJ ' ' UJ UJ Ijj UJ UJ UJ UJ UJ U» UJ UJ UJ UJ UJ * * U^ UJ UJ UJ Ul UJ UJ fet? UJ UJ UJ UJ UJ UJ UJ UJ i ' UJ UJ UJ UJ UJ U.

intr«««C«^r<-r>-BXXXB:x9-9'O-9-9'Off9O?»999> O-7

! UJ UJ U! UJ U; Ut UJ UJ U.' U.' U.1 UJ UJ UJ UJ \li U

19

Page 21: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

O 9 S3 O O

C -O * « -O O £. f, £ -C. « 3 D X X » J> -» f « 3 ^4 « X

3 O O O O

.A. X "' X IV.^ 31 ^ » Xa v» « X r

o « ox C. J1 -^ J^e ? * *

OD 33 ! -4 ~J -J J1 X « > PI *n fl PI fl

» -4 J9 « > « Ul U< O J1 » ~« <O -SI Jf 4> « <O * LJ « -<*

'

nj rvi (\> fu "vi » .ji » -vj (V (VI OB J«* rvi o < \f .-»i p» m m rn

Page 22: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

Z W« b.1 l^i b.' IjJ UJ b; bJ bJ b-' U-' bj b.' IjJ Ul UJ bJ bj U' bJ UJ bj bj UJ bJ U.' U' bJ b.< bJ bJ bJ bj bJ U.' bj bJ b.' U' UJ 1C b.' bJ U

tn O a. <v ^

_> (T _J w bj bJ bJ UJ U.1 UJ UJ W U.' It1 bJ b.' bJ W bJ UJ W W UJ bJ UJ b.' UJ UJ UJ U' W UI UJ W U.1 W UJ W U.' UJ UJ UJ UJ bj b.' U; It' bJ UJ W« 3 oor>nt^»^O'Ckn«<*o«*UMr>< ff *rw«o-n^»^O'»irO'*eO'n^K^«-io- - >-ce«f-r»ir>tvno'pe> tn c oesr^

ooooooooooooooooooooooeoooQ-eo-o-cyo-es-o-cc*

V - Illllllllllllllllllllllllllllllllllllllll

O "- fvj cvfVjcvcMM re fucvivruivjrxjfvjfvjcMturMrvirv)ltlltlttllllltlllllltlllllllllll

i * ' bj b.' ^i* dj UJ b.* bJ UJ bj UJ ul bJ ' ' bJ M' **' bJ I*/ I*/ l*> bJ ul bJ Uk) ivf bJ I*/ UJ b.* b.' uj I*/ bJ liJ b^ u* U.' bJ bJ v ! y-* bj * bJ UJ u.-- »^r- «rc

C x r>f\;evr«iviMiv«\j»Vfui\»iMi\iivnv.iMr«r\)»v;ru«v -.-. ̂ .^ i _ _ oooooooocoooocMinx iiiiiiiiiiiiii»iiiiitiiiiit«iiiiii»iiiiii.^ V» O l*» liv W bJ \A' UJ UJ tj* bj bJ '^1 * ' Uj - '_ib^ « o

r; « »i\mir. ctt^ «r«ctto «- «v«\irw iv- -r

O * * n Mru ru l\j ru CM M ru (\j »<j CM M M ru r\< CM nj M rvuvj o o o o o o o o o o o o o oN a § i i 7 »» i i » i i » i i § i i i t i i § i i i i i i i i i i ij»-w er * * IT. ^«r-.«« . fr^cMir^airX a b. 4 ircf--wj<cB»-u; o- «x)*ifif-^O tn rr a 2 N. .......

».» » ».» » » » »

21

Page 23: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

ooooe

c c o c o c

UJUJ«fcJUJUJIlJUJUJ|jJuJuJ«A)UJUJ|jJ|jJ|jJLU

com ;

UJ tl_ U.' U/ ^ tjj \±_< ItJ \i_ *i ti* \*J ^r' V liJ '" 'ft' ^' * * **' ^1' 'i* ^i 1 '" u ' *** *** **' t* 1 **' ttl * * fc ' * t" 'l 1 t.i t«< ui ut I..- t*i 1^1 iu i.i i.: i»i Ifrl t^i |^' i>i Lt ' Ul Ul t^i t«' 1^1 it t.i i.i ^* y«n**c!v*i\»x-"ff.niv»^o*«ivimff-«(r'^'M«ir>of» ̂ ^-O1 "-'^!--* t»^«xiryff ^.o e^-i\;in^x«** ̂ f\,^-»

i 1,1 i.t |jj yj |jj t«i i^l i. i t«i 1. 1 yj i.i yj t^i yj yj t«i 1^1 tyi t«i yj |jj l t i yj (4,1 1^1 yj |jj ||J yj yj 1^1 y^ i.i yj yj t»lyj yj t»l \jj *^| yj yj yj lit yj i.l yj yj yj yj yj yj 1*1 ! I yj l«i yj yj t«i t.i yjn ->««*ip*ni/»^oO'ir»rin^a*n «(r«

t ^f yj t. yj yj yj yj y yj UJ UJ te> UJ UJ UJ UJ UJ UJ UJ yj V4J V ' U* UJ UJ UJ U» w> UJ UJ UJ U» UJ k« l*» UJ UJ

22

Page 24: United States Department of the Interior Geological … · Department of the Interior Geological ... mode to the nonlinear strain range of most soils. ... of the Soil Mechanics and

o o o o o O « -J -J O .O 3> -O O fVJ » o * *4 «* < ! ul >! SB O> * O «

C X X X To x -- u: *o ^. « a.

o o o o o ^ a: -4 -< ».O -O -O O -J J3 « -4 O

o o o o o

o o o o o

u * « « « ^ O 3 - ^ y x -a

o o o c o

o o o o o * * our > jt -c « -c vm ,^ m r* m

O" 9 » 9 9 * X JB » O> « » IT Jl */«