* Justifier for Jobs Method of Composition-Determination close all clear all on escape cancel on shutdown quit set century on set confirm on if iscolor() set color on set color to n/bg,n/g,g clear else set color off endif clear set date german set decimals to 18 set exact on set heading on set safety off set status off set sysmenu to default set sysmenu off set talk off set typeahead to 3000 set color to bg+/bg,n/g,g @ 0,0 clear @ 0,10 say " Justifier for Jobs Method of Composition-Determination" set color to n/bg,n/g,g Set alternate to JobJ_Res set alternate on text
The Jobs Method of Determination of Complex-Composition is based on the concept that when equimolar solutions of the metal-ion and the ligand are mixed in gradually varying volume-ratios, the concentration of the complex is highest when the volume-ratio equals complex-composition stoic. (ratio)
For the reaction mM + nL = MmLn where M & L are metal & ligand respec-ly, let the two equimolar solutions each has molarity c0, so that for the volume fractions fM (=VM/(VM+VL)) & fL (=1-fM), the initial (post-mixing) molarities of M & L are c0*fM & c0*fL. If cC is the equilibrium molarity of complex, then equilibrium molarities of M & L are (c0*fM - m*cC) & (c0*fL - n*cC), and so the (complex-formation) equilibrium relation is: cC/((c0*fM- m*cC)**m)*((c0*fL - n*cC)**n) = K (K is stability constant). From this equilibrium relation, cC value may be found in a iterative way.
So to justify Jobs method, fM is allowed to vary from 0.01 to 0.99 for user-specified values of m, n, c0 & K, and the resulting cC values noted. (Outcome of above calculations WILL BE SAVED in the FILE 'JobJ_Res.txt')
endtext set alternate off store 1 to m store 4 to n store 0.10000000 to c0 store 20.000000 to K @ 20, 3 say "Metal-Ion Coefficient m:" get m @ 20,44 say "Ligand Coefficient n:" get n @ 22, 3 say "Common Initial Molarity:" get c0 @ 22,49 say "Const. K:" get K okbut = "" @ 24,38 get okbut function '* Continue' size 1,9 read cycle n = abs(n) m = abs(m) if n*m = 0 quit endif set alternate on ?" Metal-Ion Coefficient m:",m ??" Ligand Coefficient n:",n ?" Common Initial Molarity:",c0 ??" Const. K:",K ? ?" Volume Percentage Equilibrium Molarity" ?" of Metal-Ion Soln. of the Complex" ? * Evaluating q upto term < 0.000001*1 (1 is 1st term) fM = 0.01 fMm = 0.00 cC_last = 0.0 do while fM < 1.00 fL = 1.0 - fM store 1.0 to cC store 0.0 to cC2 cCmx = K*((c0*fM-0)**m)*((c0*fL-0)**n) I = 1 set alternate off if n*m = 1 ?" Percentage:",str(fM*100,3)," Solving quadratic equation for molarity of complex..." * quadratic eqn is K*(cC**2) -(K*c0 + 1)*cC + K*c0*c0*fM*fL = 0; cCmx = K*c0*fM*c0*fL soln1 = ((K*c0 + 1) - sqrt((K*c0 + 1)**2 - 4*K*K*c0*c0*fM*fL))/(2*K) soln2 = ((K*c0 + 1) + sqrt((K*c0 + 1)**2 - 4*K*K*c0*c0*fM*fL))/(2*K) if soln2 > cCmx cC = soln1 else ?" An controversial situation encountered - calculation doubtful!" cC = soln1 I = 1001 endif else ?" Percentage:",str(fM*100,3)," Proceeding with iterations for molarity of complex:" do while (round(cC,12) <> round(cC2,12) .and. I <= 1000) cC = cC2 cC2 = K*((c0*fM- m*cC)**m)*((c0*fL - n*cC)**n) ?" round:",str(I,4)," value:",cC2 I = I + 1 enddo endif ?" Checking correctness (the factor should be unity); factor is: " cC = round(cC,12) ??str(cC/(K*((c0*fM- m*cC)**m)*((c0*fL - n*cC)**n)),15,12) ?" Completed; resting for a second...." out = inkey(1,'ms') set alternate on if cC > cC_last fMm = fM endif cC_last = cC if I = 1001 ?round(fM*100,0)," Calculation Fails!" else ?round(fM*100,0)," ",round(cC,12) endif fM = fM + 0.01 enddo if fMm > 0.0 ? ?" So, the maximum of complex concentration occurs at the percentage: " ??ltrim(str(fMm*100))+"%" ?" (i.e., n/m will be experimentally found to be:",str(round((1-fMm)/fMm,2),5,2)+")" endif ? set alternate off close alternate close all clear all quit
* Molecular Speed Distribution Calculator close all clear all on escape cancel on shutdown quit set century on set confirm on if iscolor() set color on set color to n/bg,n/g,g clear else set color off endif clear set date german set decimals to 18 set exact on set heading on set safety off set status off set sysmenu to default set sysmenu off set talk off set typeahead to 3000 set color to bg+/bg,n/g,g @ 0,0 clear @ 0,10 say " Molecular Speed Distribution Calculator" set color to n/bg,n/g,g Set alternate to MlSp_Res set alternate on text The disribution of molecular speeds as described by Maxwell is a deserving case for computer-use because of the huge computational work involved. The molecules of the given gas-system (with a definite mass m for its molecule) obey a definite distribution for their speeds depending on the temp. T. The distribution is expressed in terms of the number of molecules dN (out of the total N molecules where N must be very large, say 10 to the power 18) with their speeds lying between v and v+dv, expressed as function of v & dv. Relations used are (pai is 3.14159; T is abs. temp.; k is Boltzmann const.): Mass of a molecule m = (Molar mass M)/(602200000000000000000000/mol) Number dN = N*4*pai*((m/(2*pai*k*T))**1.5)*(v**2)*exp(-m*(v**2)/(2*k*T))*dv Number N12 lying between speeds v1 & v2 = (Integral of dN from v=v1 to v=v2) (Outcome of aforesaid calculations WILL BE SAVED in the FILE 'MlSp_Res.txt') endtext set alternate off N = 6022.00000000 molmass = 32.000000 T = 298.150000 lowspeed = 380.000000 upspeed = 410.000000 SpeedIncrD = 1.000000 @ 16, 3 say "Number of molecules in gas, N:" get N ??" (into 10 to the power 20)" @ 18, 3 say "Molar Mass (g/mol):" get molmass @ 18,43 say "Temperature T (K):" get T @ 20, 3 say "Lower Speed (m/s):" get lowspeed @ 20,43 say "Upper Speed (m/s):" get upspeed @ 22, 3 say "Speed Increment (m/s) for Display:" get SpeedIncrD okbut = "" @ 24,37 get okbut function '* Continue' size 1,9 read cycle if upspeed <= lowspeed ?" The upper speed is smaller than (or equal to) the lower speed!" ?" Press any key or just wait to leave this program.... " out = inkey(60,'ms') quit endif * Evaluating integral and probability function m = (molmass/1000)/(6.022E23) v = lowspeed+0.0 pai = 3.14159 k = 1.381E-23 mpv = sqrt(2.0*8.314*T/(Molmass/1000.0)) SpeedIncrI = 0.000025*mpv && SpeedIncrI is around 0.01 for oxygen at 300 K integral = 0.0 set alternate on ?" Speed v (m/s) dN/dv value (10E+20 s/m)" ? do while v <= upspeed dNbydv = N*4*pai*sqrt((m/(2*pai*k*T))**3)*(v**2)*exp(-m*(v**2)/(2*k*T)) ?round(v,15),round(dNbydv,15) v = v + SpeedIncrD enddo set alternate off ?" Evaluating integral of dN from v=v1 to v=v2...." set alternate on dv = SpeedIncrI N12 = 0.0 v = lowspeed do while v < upspeed if (v + SpeedIncrI) > upspeed dv = upspeed - v && correcting dv for the last special case only endif v = v + 0.5*dv && taking middle-range speed v for calculation dN = N*4*pai*sqrt((m/(2*pai*k*T))**3)*(v**2)*exp(-m*(v**2)/(2*k*T))*dv N12 = N12+dN v = v - 0.5*dv + SpeedIncrI enddo clear ? ?" Molar Mass (g/mol):",molmass ??" Temperature T (K):", T ?" Total number of gas-molecules:",N,"(into 10 to the power 20)" ?" Most Probable speed (in m/s) of gas molecules:", round(mpv,15) ?" Lower Speed (m/s):",lowspeed ??" Upper Speed (m/s):", upspeed ?" Number in speed-range:",round(N12,15),"(into 10 to the power 20)" ? set alternate off ?" Outcome of above calculations WILL BE SAVED in the FILE 'MlSp_Res.txt'" ?" Press any key, click anywhere, or just wait to end the program...." out = inkey(30,'ms') close alternate close all clear all quit
* Rotational Probability Distribution Calculator close all clear all on escape cancel on shutdown quit set century on set confirm on if iscolor() set color on set color to n/bg,n/g,g clear else set color off endif clear set date german set decimals to 18 set exact on set heading on set safety off set status off set sysmenu to default set sysmenu off set talk off set typeahead to 3000 set color to bg+/bg,n/g,g @ 0,0 clear @ 0,10 say " Rotational Probablity Distribution Calculator" set color to n/bg,n/g,g Set alternate to RotP_Res set alternate on text
The probability disribution of heteronuclear diatomic rotational levels is an interesting simple case-study of molecular-level occupation patterns, as here the number of significantly occupied levels is limited, the energy- level degeneracies vary so as to cause maximum occupation at a non-ground level, the degeneracies & energies have manageable analytical expressions, and the partition function series converge manageably fast. The relations to be used here are (rotational level quantum number J = 0, 1, 2, .......; thetarot is char. rota. temp.; T is abs. temp.; k is Boltz. const.):
Degeneracy g (function of J) = 2*J+1 Energy E (function of J) = J*(J+1)*thetarot*k Partition-function q = g(0)*exp(-E(0)/(k*T)) + g(1)*exp(-E(1)/(k*T)) + ... Probability p (function of J) = g(J)*exp(-E(J)/(k*T))/q (Outcome of above calculations WILL BE SAVED in the FILE 'RotP_Res.txt')
endtext set alternate off thetarot = 15.020000 T = 298.150000 @ 17, 3 say "CRT theta-rot (K):" get thetarot @ 17,43 say "Temperature T (K):" get T okbut = "" @ 19,35 get okbut function '* Continue' size 1,9 read cycle set alternate on * Evaluating q upto term < 0.000001*1 (1 is 1st term) J = 0 q = 0.0 do while (2*J+1)*exp(-J*(J+1)*thetarot/T) > 0.000001 q = q + (2*J+1)*exp(-J*(J+1)*thetarot/T) J = J + 1 enddo * Evaluating p upto all these terms J = 0 sump = 0 Tbyt = T/thetarot ?" Char. Rota. Temp. =",thetarot,"K ; Temp. T =",T,"K" ? ?" Partition function calculated q =",round(q,15) ?" (value of T/theta-rot is:",round(Tbyt,15) ??")" ? ?" Level J pf-contribution Probability" ? do while (2*J+1)*exp(-J*(J+1)*thetarot/T) > 0.000001 term = (2*J+1)*exp(-J*(J+1)*thetarot/T) p = term/q ?str(J),round(term,15),round(p,15) sump = sump + p J = J + 1 enddo ? ?" Sum of these probabilities is (check!):", round(sump,15) ? set alternate off close alternate close all clear all quit
* Solving A Simple Non-Linear Equation Iteratively close all clear all set century on set confirm on set color to n/bg,n/g,g clear set date german set decimals to 18 set exact on set safety off set status off set sysmenu off set talk off set typeahead to 3000 on shutdown quit on escape quit set color to bg+/bg,b/g,g @ 2,8 say "Program for Solving Simple Equation of Type x = f(x) Iteratively" set color to b/bg,b/g,g com = stuff(space(55),1,len("5*(EXP(x)-1)/EXP(x)"),"5*(EXP(x)-1)/EXP(x)") X = 5.0000000000 Disagg = 0.0000010000 @ 5,3 say "The equation is: x =" get com @ 7,3 say "Initiating x value: " get X @ 9,3 say "Disagreement limit: " get Disagg @ 11,3 say "(Result of calculations will be stored in Iter_Res.txt)" okbut = "" @ 14,36 get okbut function '* Continue' size 1,9 read cycle set alternate to "Iter_Res.txt" set alternate on ?" The equation is: X =",com ?" Initiating X value: ",X ?" Disagreement limit: ",Disagg ? ? ICOUNT = 1 com = stuff( "y = ",5,len(ltrim(rtrim(com))),ltrim(rtrim(com)) ) DO while ICount < 1000.5 &com ?" Round:",ltrim(str(ICOUNT))," Started with x:",str(x,21,10)," Got x:",str(y,21,10) ERR = Y-X ERRABS = ABS(ERR) IF ERRABS < Disagg ? ?" The solution is X =",str(x,21,10)," (at",ltrim(str(ICOUNT))+"th round)" ICount = 1009 ELSE X = Y ICOUNT = ICOUNT + 1 ENDIF ENDDO IF ICOUNT < 1008.5 ? ?" 1000 iterations performed; not yet converging to a solution!" ENDIF ? set alternate off close alternate modify file "Iter_Res.txt" noedit close all clear all quit
* Internuclear potential energy calculation for H2+ ion ground level close all clear all set century on set confirm on clear set date german set decimals to 18 set exact on set safety off set status off set sysmenu off set talk off set typeahead to 3000 on shutdown quit on escape quit set alternate to "INPE_Res.txt" set alternate on TEXT
Internuclear potential energy (electronic energy including internuclear repulsion) for hydrogen molecular monovalent cation ground state (Calculation of the same for the first excited states is too error-prone)
Formulae used (Quantum Chemistry by Ira N. Levine, Chap. 13, Sec. MO theory of H2+):
Overlap integral Sab = (1 + k*R + k*k*R*R/3) * exp((-1)*k*R)
Coulomb integral Haa = 0.5*k*k - k - 1/R + (k+1/R) * exp((-2)*k*R)
Resonance Integral Hab = (-0.5)*k*k*Sab - k*(2-k)*(1+k*R)*exp((-1)*k*R)
Internuclear Potn. U = (Haa + Hab)/(1 + Sab) + 1/R (Electronic energy)
Value of the orbital exponent k for each value of R is obtained as the optimum value that gives the lowest value of U (variation theorem).
The results of this work will be stored in INPE_RES.TXT in this folder.
ENDTEXT SET ALTERNATE OFF wait " Would you include values of Sab, Haa, Hab & U in RES.TXT [Y,N]? "; to openness @ 1,0 clear R = 0.4 SET ALTERNATE ON If upper(openness) = "Y" TEXT
Internuclear Orbital Overlap Coulomb Resonance Electronic Distance R Exponent k Integral Integral Integral Energy U (AtomicUnit) (PureNumber) Sab(a.u.) Haa(a.u.) Hab(a.u.) (a. u.)
ENDTEXT Else TEXT
Internuclear Orbital Overlap Coulomb Resonance Electronic Distance R Exponent k Integral Integral Integral Energy U (AtomicUnit) (PureNumber) Sab(a.u.) Haa(a.u.) Hab(a.u.) (a. u.)
ENDTEXT Endif SET ALTERNATE OFF DO WHILE R <= 8.0 k = 0.1 EP_MIN = 1000 DO WHILE k <= 2 NUME = k*k - k - 1/R + (1+k*R)*EXP((-2)*k*R)/R + k*(k-2)*(1+k*R) ; *EXP((-1)*k*R) DENO = 1 + EXP((-1)*k*R)*(1+k*R+k*k*R*R/3) EP = (-0.5)*k*k + NUME/DENO + 1/R IF EP < EP_MIN k_min = k EP_MIN = EP ENDIF k = k + 0.01 ENDDO k = k_min - 0.01 k_lim = k_min + 0.01 DO WHILE k <= k_lim NUME = k*k - k - 1/R + (1 + k*R)*EXP((-2)*k*R)/R + k*(k-2)*(1 + k*R) ; *EXP((-1)*k*R) DENO = 1 + EXP((-1)*k*R)*(1 + k*R + k*k*R*R/3) EP = (-0.5)*k*k + NUME/DENO + 1/R IF EP < EP_MIN k_min = k EP_MIN = EP ENDIF k = k + 0.0001 ENDDO k = k_min EP = EP_MIN if k < 1.0 k = 1.0 endif Sab = (1 + k*R + k*k*R*R/3) * exp((-1)*k*R) Haa = 0.5*k*k - k - 1/R + (k+1/R) * exp((-2)*k*R) Hab = (-0.5)*k*k*Sab - k*(2-k)*(1+k*R) * exp((-1)*k*R) U = (Haa + Hab)/(1 + Sab) + 1/R SET ALTERNATE ON If upper(openness) = "Y" ?str(round(R,5),11,5),str(round(k,5),11,5),str(round(Sab,5),11,5),str(round(Haa,5),12,5), ; str(round(Hab,5),11,5),str(round(U,5),11,5) Else ?str(round(R,5),11,5),str(round(k,5),11,5) Endif SET ALTERNATE OFF R = R + 0.2 ENDDO SET ALTERNATE ON ? SET ALTERNATE OFF close alternate close all clear all quit