1000 REM  LOAN CALCULATION PROGRAM (WRITTEN TO RUN WITH BASIC-80 v5.21)
1020 REM  WRITTEN BY MARK MCKIBBEN, WOLD COMMUNICATIONS
1040 REM  THIS PROGRAM WAS WRITTEN IN STAGES AND NEVER REALLY STRAIGHTENED
1060 REM  OUT, SO IT IS A BIT OF A MESS.  
1080 REM  THE PROGRAM IS MENU-DRIVEN AND MORE OR LESS SELF-DOCUMENTING.
1100 REM  ONLY ONE STATEMENT NEEDS TO BE CORRECTED (IF RUN UNDER MBASIC)
1120 REM  FOR SPECIFIC TERMINALS:  ONE OF THE FIRST STATEMENTS BELOW
1140 REM  DEFINES CLS$, WHICH IS SENT TO THE CONSOLE TO CLEAR SCREEN AND
1160 REM  HOME CURSOR.  
1180 REM  THERE IS ONE UNDOCUMENTED MENU ITEM:  "L", WHICH LOADS SAMPLE
1200 REM  VALUES INTO THE VARIABLES FOR TESTING.
1220 REM
1240 DEFDBL D:DEFSNG S:DEFSTR A-C:DEFINT I:REM GLOBAL VARIABLE DEFINITIONS
1260 REM CHANGE THE STATMENT BELOW FOR YOUR CLEAR SCREEN SEQUENCE
1280 CLEAR
1300 CLS$=CHR$(27)+CHR$(42):REM THIS VARIABLE WILL CLEAR THE SCREEN
1320 ON ERROR GOTO 1360
1340 GOTO 1480
1360 PRINT CLS$
1380 PRINT:PRINT:PRINT:PRINT "      AN ENTRY HAS BEEN MADE WHICH CANNOT BE USED FOR LOAN CALCULATIONS.":PRINT:PRINT
1400 PRINT " PLEASE DOUBLE CHECK YOUR ENTRIES AND TRY AGAIN.  PRESS ANY KEY TO CONTINUE. ";
1420 ANS$=INPUT$(1)
1440 RESUME 1280
1460 REM
1480 WIDTH 79:REM SET WIDTH TO 79 ON SCREEN
1500 REM
1520 GOTO 2660
1540 REM MENU PROCESSING SUBROUTINE
1560 PRINT
1580 PRINT "      >>>>>>>>>>>>> NOW WAITING FOR YOUR SELECTION >>>>> ";
1600 ANS$=INPUT$(1)
1620 IF ANS$<"a" OR ANS$>"z" THEN GOTO 1660
1640 ANS$=CHR$(ASC(ANS$)-32)
1660 FOR MENUNUM%=1 TO LEN(MENULIST$) 
1680 IF ANS$=MID$(MENULIST$,MENUNUM%,1) THEN PRINT ANS$;CHR$(13);SPC(70);CHR$(13);:RETURN
1700 NEXT
1720 GOTO 1600
1740 REM ***** YES/NO SUBROUTINE ****** (MENUNUM% = 1 FOR YES, 2 FOR NO)
1760 ANS$ = INPUT$(1)
1780 IF ANS$ = "Y" OR ANS$ = "y" THEN MENUNUM% = 1 : PRINT "Yes" : RETURN
1800 IF ANS$ = "N" OR ANS$ = "n" THEN MENUNUM% = 2 : PRINT "No" : RETURN
1820 GOTO 1760
1840 REM *******  SUBROUTINE FOR PRINTING REUSED MESSAGE #1
1860 PRINT:PRINT " The calculated amount above will be automatically recalculated anytime you":PRINT " change one of the VARIABLES.  Use the menu to select.":RETURN
1880 REM *******  SUBROUTINE FOR PRINTING REUSED MESSAGE #2
1900 PRINT " Please enter each missing variable using the menu to select each item.":RETURN
1920 REM ******* SUBROUTINE FOR PRINTING REUSED MESSAGE #3
1940 PRINT:PRINT " Variables needed for calculation:":PRINT:PRINT "       VARIABLE                         CURRENT VALUE":RETURN
1960 REM ******* SUBROUTINE FOR PRINTING REUSED MESSAGE #4
1980 PRINT:PRINT " PRESS (H) for HELP."
2000 PRINT " PRESS (M) to return to the MAIN MENU.":RETURN
2020 REM ****** SUBROUTINE FOR PRINTING REUSED MESSAGE #5
2040 PRINT " NEGATIVE numbers are not allowed in loan calculations.  HIT ANY KEY.";ANS$=INPUT$(1);
2060 PRINT CHR$(13);SPC(75);CHR$(13);
2080 RETURN
2100 REM  ORIGINAL TERM LOAN PRINICIPAL USING INTEREST RATE, THE AMOUNT
2120 REM  OF REGULAR PAYMENTS, NUMBER OF PAYMENTS PER YEAR AND TERM OF THE
2140 REM  LOAN.
2160 REM  
2180 REM  REGULAR PAYMENT ON A LOAN USING ORIGINAL LOAN PRINCIPAL, INTEREST
2200 REM  RATE, NUMBER OF PAYMENTS PER YEAR, AND NUMBER OF YEARS TO PAY.
2220 REM  ASSUMES ALL PAYMENTS WILL BE EQUAL.
2240 REM
2260 REM  LAST PAYMENT ON A LOAN USING AMOUNT OF THE LOAN, THE AMOUNT OF
2280 REM  THE PAYMENTS, INTEREST RATE CHARGED, NUMBER OF PAYMENTS PER YEAR
2300 REM  AND THE TERM OF THE PAYMENTS
2320 REM
2340 REM  REMAINING BALANCE ON A LOAN AFTER A SPECIFIC NUMBER OF PAYMENTS
2360 REM  USING PAYMENT AMOUNT, NUMBER OF PAYMENTS PER YEAR, AMOUNT OF THE
2380 REM  PRINCIPAL, ANNUAL INTEREST RATE, AND THE PAYMENTS NUMBER.  THERE
2400 REM  ALSO A SUBROUTINE THAT WILL CALCULATE THE PAYMENT NUMBER GIVEN
2420 REM  THE FIRST PAYMENT DATE AND THE CURRENT OR PROJECTED DATE.
2440 REM
2460 REM  TERM OF A LOAN (PERIOD NEEDED TO REPAY) USING PAYMENT AMOUNTS,
2480 REM  NUMBER OF PAYMENTS, ANNUAL INTEREST RATE AND ORIGINAL LOAN AMOUNT.
2500 REM  ALL PAYMENTS ARE ASSUMED TO BE EQUAL.
2520 REM  
2540 REM  ANNUAL INTEREST RATE ON A LOAN USING AMOUNT OF LOAN, AMOUNT OF
2560 REM  PAYMENT, NUMBER OF PAYMENTS PER YEAR, AND TERM OF LOAN.
2580 REM 
2600 REM  MORTGAGE AMORTIZATION TABLE USING PAYMENT AMOUNT, TERM OF PAYMENT
2620 REM  NUMBER OF PAYMENTS PER YEAR, PRINCIPAL AMOUNT AND INTEREST RATE.
2640 REM
2660 REM  ****************************************************************
2680 REM  BEGINNING OF PROGRAM
2700 REM  ***************************************************************
2720 REM FIRST COMES THE STARTUP MENU
2740 REM
2760 PRINT CLS$
2780 REM
2800 REM
2820 PRINT:PRINT"           *************** MAIN MENU ***************" 
2840 PRINT "   This is a program for LOAN CALCULATIONS.  Please select the "
2860 PRINT "             module you would like to run below."
2880 PRINT
2900 PRINT "      (Press the corresponding letter from the menu.)"
2920 PRINT
2940 PRINT "  (A)  LOAN PRINCIPAL AMOUNT"
2960 PRINT "  (B)  REGULAR LOAN PAYMENT AMOUNT"
2980 PRINT "  (C)  LAST PAYMENT ON A LOAN"
3000 PRINT "  (D)  REMAINING BALANCE ON A LOAN"
3020 PRINT "  (E)  TERM OF A LOAN"
3040 PRINT "  (F)  ANNUAL INTEREST RATE ON A LOAN"
3060 PRINT "  (G)  LOAN AMORTIZATION TABLE"
3080 PRINT
3100 PRINT "  (H)ELP-- Choose this for an explanation of the modules above."
3120 PRINT
3140 PRINT "  (X)  EXIT BACK TO THE OPERATING SYSTEM"
3160 REM
3180 MENULIST$="ABCDEFGHXL"
3200 GOSUB 1540
3220 ON MENUNUM% GOTO 3240,4380,4960,5660,6600,7440,8180,13240,15580,15880
3240 REM *******************MENU CHOICE A*****************************
3260 PRINT CLS$;
3280 PRINT "            PRINCIPAL ON A LOAN "
3300 PRINT "      Calculates an initial amount borrowed."
3320 GOSUB 1920
3340 PRINT " (A) ";:GOSUB 3360:GOTO 3400
3360 PRINT "Amount of Regular Payment: ";
3380 PRINT USING "$$#########.##";DPAYMENT:RETURN
3400 PRINT " (B) ";:GOSUB 3420:GOTO 3480
3420 PRINT "Annual Interest rate:      ";
3440 PRINT USING "        ###.##";SINTEREST;
3460 PRINT "%":RETURN
3480 PRINT " (C) ";:GOSUB 3500:GOTO 3540
3500 PRINT "Payments per Year:         ";
3520 PRINT USING "        ###";IPAYMENTNUM:RETURN
3540 PRINT " (D) ";:GOSUB 3560:GOTO 3600
3560 PRINT "Number of Years:           ";
3580 PRINT USING "        ###.#";SYEARS:RETURN
3600 PRINT:PRINT
3620 IF (DPAYMENT*SINTEREST*IPAYMENTNUM*SYEARS)<>0 THEN GOSUB 4180 ELSE LET DPRINCIPAL=0
3640 IF DPRINCIPAL=0 THEN GOTO 3720
3660 PRINT " The calculated PRINCIPAL amount is: ";
3680 PRINT USING "$$###########.##";DPRINCIPAL
3700 GOSUB 1840:GOTO 3740
3720 GOSUB 1880
3740 GOSUB 1960
3760 MENULIST$="MABCDH"
3780 GOSUB 1540
3800 IF MENUNUM%=1 THEN GOTO 2660 ELSE LET MENUNUM%=MENUNUM%-1
3820 ON MENUNUM% GOSUB 3860,3940,4020,4100,13360
3840 GOTO 3240
3860 REM ************************** ROUTINE TO GET DPAYMENT ***
3880 INPUT " Please enter the amount of regular payment.... ",DPAYMENT
3900 IF DPAYMENT<0 THEN GOSUB 2020:GOTO 3880
3920 RETURN
3940 REM ************************** ROUTINE TO GET SINTEREST ***
3960 INPUT " Please enter the annual interest rate.... ",SINTEREST
3980 IF SINTEREST<0 THEN GOSUB 2020:GOTO 3960
4000 RETURN
4020 REM ************************** ROUTINE TO GET IPAYMENTNUM ***
4040 INPUT " Please enter the number of payments per year.... ",IPAYMENTNUM
4060 IF IPAYMENTNUM<0 THEN GOSUB 2020:GOTO 4040
4080 RETURN
4100 REM ************************** ROUTINE TO GET SYEARS ***
4120 INPUT " Please enter the term of the loan in years.... ",SYEARS
4140 IF SYEARS<0 THEN GOSUB 2020:GOTO 4120
4160 RETURN
4180 REM ************************** ROUTINE TO CALCULATE PRINCIPAL *******
4200 REM
4220 REM
4240 DTEMPSTORE=DPAYMENT*IPAYMENTNUM*(1-1/((SINTEREST/100)/IPAYMENTNUM+1)^(IPAYMENTNUM*SYEARS))/(SINTEREST/100)
4260 DPRINCIPAL=INT(DTEMPSTORE*100+.5)/100
4280 RETURN
4300 REM ************************** ROUTINE TO GET DPRINCIPAL ***
4320 INPUT " Please enter the loan principal.... ",DPRINCIPAL
4340 IF DPRINCIPAL<0 THEN GOSUB 2020:GOTO 4320
4360 RETURN
4380 REM *******************MENU CHOICE B*****************************
4400 PRINT CLS$;
4420 PRINT "          REGULAR PAYMENT"
4440 PRINT "    Calculates the amount of each payment."
4460 GOSUB 1920
4480 PRINT " (A) ";:GOSUB 3420
4500 PRINT " (B) ";:GOSUB 4520:GOTO 4560
4520 PRINT "Amount of Principal:       ";
4540 PRINT USING "$$#########.##";DPRINCIPAL:RETURN
4560 PRINT " (C) ";:GOSUB 3500
4580 PRINT " (D) ";:GOSUB 3560
4600 PRINT:PRINT
4620 IF (SINTEREST*DPRINCIPAL*IPAYMENTNUM*SYEARS)<>0 THEN GOSUB 4860 ELSE LET DPAYMENT=0
4640 IF DPAYMENT=0 THEN GOTO 4720
4660 PRINT " The calculated PAYMENT amount is: ";
4680 PRINT USING "$$############.##";DPAYMENT
4700 GOSUB 1840:GOTO 4740
4720 GOSUB 1880
4740 GOSUB 1960
4760 MENULIST$="MABCDH"
4780 GOSUB 1540
4800 IF MENUNUM%=1 THEN GOTO 2660 ELSE LET MENUNUM%=MENUNUM%-1
4820 ON MENUNUM% GOSUB 3940,4300,4020,4100,13760
4840 GOTO 4380
4860 REM ************************** ROUTINE TO CALCULATE DPAYMENT ***
4880 DTEMPSTORE=((SINTEREST/100)*DPRINCIPAL/IPAYMENTNUM)/(1-1/((SINTEREST/100)/IPAYMENTNUM+1)^(IPAYMENTNUM*SYEARS))
4900 DPAYMENT=INT(DTEMPSTORE*100+.5)/100
4920 RETURN
4940 STOP
4960 REM *******************MENU CHOICE C*****************************
4980 PRINT CLS$;
5000 PRINT "          LAST PAYMENT ON A LOAN"
5020 PRINT "   Finds the final payment at the end of the term."
5040 GOSUB 1920
5060 PRINT " (A) ";:GOSUB 3360
5080 PRINT " (B) ";:GOSUB 4520
5100 PRINT " (C) ";:GOSUB 3560
5120 PRINT " (D) ";:GOSUB 3420
5140 PRINT " (E) ";:GOSUB 3500
5160 PRINT:PRINT
5180 IF (DPAYMENT*DPRINCIPAL*SYEARS*SINTEREST*IPAYMENTNUM)<>0 THEN GOSUB 5400 ELSE LET DLASTPAYMENT=0
5200 IF DLASTPAYMENT=0 THEN GOTO 5280
5220 PRINT " The calculated LAST PAYMENT amount is: ";
5240 PRINT USING "$$#############.##";DLASTPAYMENT
5260 GOSUB 1840:GOSUB 1960:GOTO 5300
5280 GOSUB 1880:GOSUB 1960
5300 MENULIST$="MABCDEH"
5320 GOSUB 1540
5340 IF MENUNUM%=1 THEN GOTO 2660 ELSE LET MENUNUM%=MENUNUM%-1
5360 ON MENUNUM% GOSUB 3860,4300,4100,3940,4020,13980
5380 GOTO 4960
5400 REM  *************************  CALCULATION OF DLASTPAYMENT ***
5420 PRINT " Please wait.  This calculation can take quite a while to run.";
5440 DBO=DPRINCIPAL
5460 SI=((SINTEREST/100)/IPAYMENTNUM)*100
5480 IJ2=IPAYMENTNUM*SYEARS
5500 FOR IJ1=1 TO IJ2
5520 IF DBO<0 THEN PRINT CHR$(13);SPC(75);CHR$(13);" The payment entered is too large.  Press any key to RECALCULATE. ";:ANS$=INPUT$(1):GOSUB 4860:GOTO 4960
5540 DBO=DBO-DPAYMENT+INT(DBO*SI+.5)*.01
5560 NEXT IJ1
5580 TEMPSTORE=INT((DPAYMENT+DBO)*100+.5)/100
5600 DLASTPAYMENT=TEMPSTORE
5620 PRINT CHR$(13);SPC(70);CHR$(13);
5640 RETURN
5660 REM *******************MENU CHOICE D*****************************
5680 PRINT CLS$;
5700 PRINT "             REMAINING BALANCE ON A LOAN"
5720 PRINT "  Finds the balance after a specified number of payments."
5740 GOSUB 1920
5760 PRINT " (A) ";:GOSUB 3360
5780 PRINT " (B) ";:GOSUB 4520
5800 PRINT " (C) ";:GOSUB 3500
5820 PRINT " (D) ";:GOSUB 3420
5840 PRINT " (E) ";:GOSUB 5900
5860 PRINT " --- ";:GOSUB 3560
5880 GOTO 5980
5900 PRINT "Last Payment made (#,year):";
5920 PRINT USING "        ###";SLSTPAYMENT;
5940 PRINT ",";SLSTPAYMENTYEAR
5960 RETURN
5980 PRINT:PRINT
6000 IF (DPAYMENT*DPRINCIPAL*IPAYMENTNUM*SINTEREST*SLSTPAYMENT*SLSTPAYMENTYEAR)<>0 THEN GOSUB 6360 ELSE LET DREMAINING=0:GOTO 6080
6020 PRINT " The calculated REMAINING BALANCE amount is: ";
6040 PRINT USING "$$#############.##";DREMAINING
6060 GOSUB 1840:GOSUB 1960:GOTO 6100
6080 GOSUB 1880:GOSUB 1960
6100 MENULIST$="MABCDEH"
6120 GOSUB 1540
6140 IF MENUNUM%=1 THEN GOTO 2660 ELSE LET MENUNUM%=MENUNUM%-1
6160 ON MENUNUM% GOSUB 3860,4300,4020,3940,6200,14260
6180 GOTO 5660
6200 REM ********************** ROUTINE TO GET SLSTPAYMENT & SLSTPAYMENTYEAR ***
6220 INPUT " Enter the number of the last payment made for this year.... ",SLSTPAYMENT
6240 IF SLSTPAYMENT<0 THEN GOSUB 2020:GOTO 6220
6260 IF SLSTPAYMENT>IPAYMENTNUM THEN PRINT CHR$(7);:PRINT "    This value cannot be greater than the number of payments per year.  ":GOTO 6220
6280 INPUT " Now enter the year number to calculate remaining balance.... ",SLSTPAYMENTYEAR
6300 IF SLSTPAYMENTYEAR<0 THEN GOSUB 2020:GOTO 6280
6320 IF SLSTPAYMENTYEAR>SYEARS THEN PRINT CHR$(7);:PRINT "    This value cannot be greater than the loan term.  ":GOTO 6280
6340 RETURN
6360 REM ******************* ROUTINE TO CALCULATE DREMAINING ***
6380 PRINT " Please wait.  This calculation can take quite a while to run.";
6400 DBO=DPRINCIPAL
6420 SI=SINTEREST/100
6440 SJ2=IPAYMENTNUM*(SLSTPAYMENTYEAR-1)+SLSTPAYMENT
6460 SI2=(SI/IPAYMENTNUM)*100
6480 FOR SJ1=1 TO SJ2
6500 DBO=DBO-DPAYMENT+INT(DBO*SI2+.5)*.01
6520 NEXT SJ1
6540 DREMAINING=INT(DBO*100+.5)/100
6560 PRINT CHR$(13);SPC(75);CHR$(13);
6580 RETURN
6600 REM *******************MENU CHOICE E*****************************
6620 PRINT CLS$;
6640 PRINT "           TERM OF A LOAN"
6660 PRINT "   Finds the period of time needed to repay."
6680 GOSUB 1920
6700 PRINT " (A) ";:GOSUB 3360
6720 PRINT " (B) ";:GOSUB 4520
6740 PRINT " (C) ";:GOSUB 3420
6760 PRINT " (D) ";:GOSUB 3500
6780 PRINT:PRINT
6800 IF (DPAYMENT*DPRINCIPAL*SINTEREST*IPAYMENTNUM)<>0 THEN GOSUB 7040 ELSE LET SYEARS=0:GOTO 6900
6820 PRINT " The calculated TERM OF LOAN is: ";
6840 PRINT USING "####.#";SYEARS;
6860 PRINT " years"
6880 GOSUB 1840:GOSUB 1960:GOTO 6920
6900 GOSUB 1880:GOSUB 1960
6920 MENULIST$="MABCDH"
6940 GOSUB 1540
6960 IF MENUNUM%=1 THEN GOTO 2660 ELSE LET MENUNUM%=MENUNUM%-1
6980 ON MENUNUM% GOSUB 3860,4300,3940,4020,14520
7000 GOTO 6600
7020 STOP
7040 REM ********************** ROUTINE TO CALCULATE SYEARS ***
7060 DTEMPSTORE=DPAYMENT-(DPRINCIPAL*((SINTEREST*.01)/IPAYMENTNUM))
7080 IF DTEMPSTORE<0 THEN 7160
7100 SYEAR1=-(LOG(1-(DPRINCIPAL*(SINTEREST/100))/(IPAYMENTNUM*DPAYMENT))/(LOG(1+SINTEREST/100/IPAYMENTNUM)*IPAYMENTNUM))
7120 SYEARS=INT(SYEAR1*10+.5)/10
7140 RETURN
7160 REM --- COMPLAIN IF PAYMENT WILL NOT AMORTIZE LOAN
7180 PRINT CLS$:PRINT:PRINT:PRINT:PRINT
7200 DPAYMENT=(INT((DPRINCIPAL*((SINTEREST*.01)/IPAYMENTNUM))*100+.5)*.01)+.01
7220 PRINT "                           WARNING"
7240 PRINT " THE PAYMENT ENTERED IS NOT SUFFICIENT TO AMORTIZE THIS LOAN."
7260 PRINT " THE MINIMUM PAYMENT NEEDED HAS BEEN CALCULATED AND ENTERED"
7280 PRINT " FOR YOU.  IT IS: "; 
7300 PRINT USING "$$###########.##";DPAYMENT
7320 PRINT
7340 PRINT " USE THE MAIN MENU IF YOU WANT TO CALCULATE A DIFFERENT AMOUNT."
7360 PRINT
7380 PRINT "          PRESS ANY KEY TO CONTINUE....... ";
7400 ANS$=INPUT$(1)
7420 GOTO 6600
7440 REM *******************MENU CHOICE F*****************************
7460 PRINT CLS$
7480 PRINT "                ANNUAL INTEREST RATE"
7500 PRINT "   Finds the interest rate on a specific loan."
7520 GOSUB 1920
7540 PRINT " (A) ";:GOSUB 3360
7560 PRINT " (B) ";:GOSUB 3560
7580 PRINT " (C) ";:GOSUB 4520
7600 PRINT " (D) ";:GOSUB 3500
7620 PRINT:PRINT
7640 IF (DPAYMENT*SYEARS*DPRINCIPAL*IPAYMENTNUM)<>0 THEN GOSUB 7860 ELSE LET SINTEREST=0:GOTO 7740
7660 PRINT " The calculated INTEREST RATE is: ";
7680 PRINT USING "   ###.##";SINTEREST;
7700 PRINT "%"
7720 GOSUB 1840:GOSUB 1960:GOTO 7760
7740 GOSUB 1880:GOSUB 1960
7760 MENULIST$="MABCDH"
7780 GOSUB 1540
7800 IF MENUNUM%=1 THEN GOTO 2660 ELSE LET MENUNUM%=MENUNUM%-1
7820 ON MENUNUM% GOSUB 3860,4100,4300,4020,14760
7840 GOTO 7440
7860 REM *******************  ROUTINE TO CALCULATE SINTEREST ***
7880 SINTEREST=13
7900 PRINT " Please wait.  This calculation can take a while to run.";
7920 SI2=0
7940 DR1=(SINTEREST*.01*DPRINCIPAL/IPAYMENTNUM)/(1-1/((SINTEREST*.01/IPAYMENTNUM+1)^(IPAYMENTNUM*SYEARS)))
7960 DR1=INT(DR1*100+.5)/100
7980 DI3=ABS(SINTEREST-SI2)/2
8000 SI2=SINTEREST
8020 IF SINTEREST>=25.9 THEN PRINT CHR$(13);SPC(70);CHR$(13);:PRINT:PRINT:PRINT "  The calculated INTEREST rate is in excess of 25%.  This program cannot":PRINT "  determine the exact rate.  Press any key to return to the MAIN MENU. ";
8040 IF SINTEREST>=25.9 THEN ANS$=INPUT$(1):SINTEREST=25.5:GOTO 2720
8060 IF (DR1-DPAYMENT)<.02 AND (DR1-DPAYMENT)>-.02 THEN PRINT CHR$(13);SPC(70);CHR$(13);:RETURN
8080 IF DR1>DPAYMENT THEN 8140
8100 SINTEREST=SINTEREST+DI3
8120 GOTO 7940
8140 SINTEREST=SINTEREST-DI3
8160 GOTO 7940
8180 REM *******************MENU CHOICE G*****************************
8200 IF PRINTER=1 THEN LPRINT CHR$(12):PRINTER=0
8220 TEST=0:DINTTOTAL=0:DPRINTOTAL=0:DINTYEAR=0:DPRINYEAR=0
8240 PRINT CLS$
8260 PRINT "      LOAN AMORTIZATION TABLE"
8280 PRINT "  Provides complete loan progress chart."
8300 GOSUB 1920
8320 PRINT " (A) ";:GOSUB 3360
8340 PRINT " (B) ";:GOSUB 3560
8360 PRINT " (C) ";:GOSUB 4520
8380 PRINT " (D) ";:GOSUB 3420
8400 PRINT " --- ";:GOSUB 3500
8420 REM
8440 PRINT:PRINT
8460 IF TEST=1 THEN GOTO 8500
8480 IF (DPAYMENT*SYEARS*DPRINCIPAL*SINTEREST*IPAYMENTNUM)<>0 THEN GOTO 8640 ELSE LET TEST=0
8500 PRINT " Choose from the above menu the item that you would like to change.":GOSUB 1960
8520 MENULIST$="MABCDH"
8540 GOSUB 1540
8560 IF MENUNUM%=6 THEN GOSUB 15000:GOTO 8180
8580 IF MENUNUM%=1 THEN GOTO 2660 ELSE LET MENUNUM%=MENUNUM%-1
8600 ON MENUNUM% GOTO 4380,6600,3240,7440
8620 LET TEST=0:GOTO 8180
8640 REM
8660 PRINT " THE VARIABLES MUST BE PRECISELY CALCULATED FOR THE TABLE TO BE CORRECT."
8680 PRINT : PRINT " Do you want to change any of the above VARIABLES?"
8700 PRINT " ENTER (Y)ES or (N)O or ..."; : PRINT
8720 MENULIST$="MYNH"
8740 GOSUB 1960
8760 GOSUB 1540
8780 IF MENUNUM%=4 THEN GOSUB 15000:GOTO 8180
8800 IF MENUNUM%=1 THEN GOTO 2660 ELSE LET MENUNUM%=MENUNUM%-1
8820 ON MENUNUM% GOTO 8840,8900
8840 LET TEST=1:GOTO 8240
8860 REM
8880 REM
8900 REM ********************BEGINNING OF AMORTIZATION ROUTINE *****
8920 PRINT CLS$
8940 SCOUNTER=0
8960 LET TEST=0
8980 PRINT " Do you want this run to go to the printer?  (Enter Y or N) ";
9000 GOSUB 1740
9020 ON MENUNUM% GOTO 9040,9080
9040 LET PRINTER=1:REM-- SET PRINTER FLAG TO ON
9060 GOTO 9100
9080 LET PRINTER=0:REM-- SET PRINTER FLAG OFF
9100 PRINT:PRINT:PRINT " Do you want to display annual totals only?  (Enter Y or N) ";:GOSUB 1740:ON MENUNUM% GOTO 9120,9160
9120 LET IDISPLAY=1
9140 GOTO 9180
9160 LET IDISPLAY=0
9180 REM - INITIALIZE VARIABLES
9200 GOSUB 13100
9220 SI=(SINTEREST*.01)/IPAYMENTNUM:REM CONVERT INTEREST TO DECIMAL         
9240 IPAGE=0
9260 GOSUB 10020
9280 DBO=DPRINCIPAL
9300 DPAY=(INT(DPAYMENT*100+.5))*.01
9320 SJ2=IPAYMENTNUM*SYEARS
9340 SI2=(SINTEREST/IPAYMENTNUM)
9360 SCURRENTYEAR=1
9380 MENUNUM%=0
9400 REM **************************  HERE'S THE LOOP *********
9420 FOR SJ1=1 TO SJ2
9440 DI3=(INT(DBO*SI2+.5))*.01
9460 IF DBO<DPAYMENT THEN DPAY=DBO+DI3
9480 DBO=DBO-DPAY+DI3
9500 DBI=DPAY-DI3
9520 IF MENUNUM%=3 THEN GOTO 9580
9540 IF SCOUNTER>=21 THEN GOSUB 10740:ON MENUNUM% GOTO 9620,8180,9580
9560 GOTO 9620
9580 IF SCOUNTER>=21 THEN GOSUB 12100
9600 IF MENUNUM%=2 GOTO 8180
9620 DINTYEAR=DINTYEAR+DI3:DPRINYEAR=DPRINYEAR+DBI
9640 GOSUB 10400
9660 IF SJ1=SCURRENTYEAR*IPAYMENTNUM THEN DINTTOTAL=DINTTOTAL+DINTYEAR:DPRINTOTAL=DPRINTOTAL+DPRINYEAR:GOSUB 11780:SCURRENTYEAR=SCURRENTYEAR+1
9680 IF PRINTER=1 AND SLCOUNTER>=60 THEN GOSUB 12940:GOSUB 12460
9700 NEXT SJ1:REM ***************** END OF LOOP  ************************
9720 IF SJ1<>SCURRENTYEAR*IPAYMENTNUM THEN DINTTOTAL=DINTTOTAL+DINTYEAR:DPRINTOTAL=DPRINTOTAL+DPRINYEAR
9740 IF SCOUNTER>=21 THEN GOSUB 10740:ON MENUNUM% GOTO 9760,8180,9760 ESLE GOSUB 12100
9760 PRINT:PRINT "*TOTALS: ";
9780 IF PRINTER=0 THEN GOTO 9840
9800 IF SLCOUNTER>=60 THEN GOSUB 12940:GOSUB 12460
9820 LPRINT "*TOTALS: ";
9840 PRINT USING "$$###########.##";DINTTOTAL;
9860 IF PRINTER=0 THEN GOTO 9900
9880 LPRINT USING "$$###########.##";DINTTOTAL;
9900 SCOUNTER=SCOUNTER+2
9920 PRINT USING "  $$###########.##";DPRINTOTAL
9940 IF PRINTER=0 THEN GOTO 10000
9960 LPRINT USING "  $$###########.##";DPRINTOTAL
9980 SLCOUNTER=SLCOUNTER+2
10000 GOTO 11480
10020 REM - ROUTINE TO SET UP SCREEN DISPLAY
10040 IF PRINTER=1 THEN GOSUB 10960
10060 PRINT CLS$;
10080 PRINT " *********************  LOAN AMORTIZATION TABLE  ***********************"
10100 SCOUNTER=SCOUNTER+4
10120 PRINT " PRINCIPAL AMOUNT: ";
10140 PRINT USING "$$###########.##";DPRINCIPAL;
10160 PRINT "  PAYMENT AMOUNT: ";
10180 PRINT USING "$$#########.##";DPAYMENT
10200 PRINT " TERM IN YEARS: ";
10220 PRINT USING "             ###.# ";SYEARS;
10240 PRINT "  INTEREST RATE: ";
10260 PRINT USING "         ###.##";SINTEREST;:PRINT "%"
10280 PRINT " ***********************************************************************"
10300 REM - HEADER FOR SCREEN DISPLAY PAGE
10320 PRINT " PAYMENT #       INTEREST         PRINCIPAL        BALANCE AFTER PAYMENT"
10340 PRINT " -----------------------------------------------------------------------"
10360 LET SCOUNTER=SCOUNTER+2
10380 RETURN
10400 REM - SCREEN DISPLAY FOR EACH PAYMENT
10420 IF IDISPLAY=1 OR SCURRENTYEAR<ISTART THEN RETURN
10440 PRINT USING "  ####   ";SJ1;
10460 IF PRINTER=0 THEN GOTO 10500
10480 LPRINT USING "  ####   ";SJ1;
10500 PRINT USING "$$###########.##";DI3;
10520 IF PRINTER=0 THEN GOTO 10560
10540 LPRINT USING "$$###########.##";DI3;
10560 PRINT USING "$$#############.##";DBI;
10580 IF PRINTER=0 THEN GOTO 10620
10600 LPRINT USING "$$#############.##";DBI;
10620 PRINT USING "     $$#############.##";DBO
10640 IF PRINTER=0 THEN GOTO 10700
10660 LPRINT USING "     $$#############.##";DBO
10680 LET SLCOUNTER=SLCOUNTER+1
10700 SCOUNTER=SCOUNTER+1
10720 RETURN
10740 REM ---  ******************** SCREEN DISPLAY PAUSE ROUTINE
10760 ITEMPSTORE=22-SCOUNTER
10780 FOR ICOUNT=1 TO ITEMPSTORE
10800 PRINT
10820 NEXT ICOUNT
10840 PRINT "DISPLAY HAS BEEN PAUSED.  SELECT: (D)ISABLE PAUSE, (C)ONTINUE, OR (A)BORT."
10860 SCOUNTER=0
10880 MENULIST$="CAD"
10900 GOSUB 1540
10920 IF MENUNUM%<>2 THEN GOSUB 10060
10940 RETURN
10960 REM - SUBROUTINE TO SET UP PRINTER AND CHECK TO SEE IF IT'S READY
10980 PRINT 
11000 PRINT "    NOW CHECKING TO SEE IF THE PRINTER IS READY TO ACCEPT PRINTOUT."
11020 PRINT
11040 PRINT "PRINTER IS NOT READY.... PLEASE CHECK IT.  PROCESSING CANNOT CONTINUE.";:LPRINT CHR$(13);
11060 PRINT CHR$(13);SPC(70);
11080 PRINT:PRINT "             THE PRINTER IS NOW READY.....  HERE WE GO!"
11100 FOR HI=1 TO 300
11120 NEXT HI
11140 PRINT CLS$:PRINT:PRINT
11160 PRINT "WHEN ENTERING THE ITEMS BELOW, DO NOT USE COMMAS.  PRESS RETURN WHEN DONE.":PRINT
11180 PRINT "          PRESS THE RETURN TO LEAVE AN ENTRY WITHOUT CHANGING IT.":PRINT:PRINT
11200 PRINT "       (These entries are for the title block on the printout only.":PRINT "    You may enter anything you like, but there must be something entered.)":PRINT
11220 PRINT " Enter a title for this report..... ";:PRINT LABEL$;:PRINT CHR$(13);:PRINT " Enter a title for this report..... ";:INPUT "",LABEL1$
11240 IF LABEL1$="" THEN GOTO 11260 ELSE LABEL$=LABEL1$
11260 PRINT:PRINT " Enter today's date..... ";:PRINT DATE$;:PRINT CHR$(13);:PRINT " Enter today's date..... ";:INPUT "",DATE1$
11280 IF DATE1$="" THEN GOTO 11300 ELSE DATE$=DATE1$
11300 PRINT:PRINT " Enter the name of the recipient of this report... ";:PRINT PERSON$;:PRINT CHR$(13);:PRINT " Enter the name of the recipient of this report... ";:INPUT "",PERSON1$
11320 IF PERSON1$="" THEN GOTO 11340 ELSE PERSON$=PERSON1$
11340 PRINT:PRINT  " Are the above entries correct? (Y or N) ";:GOSUB 1740:ON MENUNUM% GOTO 11360,11140
11360 REM
11380 LPRINT:PRINT CLS$:PRINT:PRINT:PRINT " NOW SENDING TITLE BLOCK TO PRINTER.... PLEASE STAND BY."
11400 LPRINT "                          ";LABEL$
11420 LPRINT:LPRINT "         ";" prepared for: ";PERSON$;" on ";DATE$
11440 LPRINT:GOSUB 12460:SLCOUNTER=11  
11460 RETURN
11480 REM
11500 ITEMPSTORE=22-SCOUNTER
11520 FOR ICOUNT=1 TO ITEMPSTORE
11540 PRINT
11560 NEXT ICOUNT
11580 IF PRINTER=1 THEN GOSUB 12940
11600 PRINT " PRESS (Y) TO RETURN TO MENU."
11620 MENULIST$="Y"
11640 GOSUB 1540
11660 REM
11680 GOTO 8180
11700 STOP
11720 REM
11740 REM
11760 REM
11780 REM - SUBROUTINE FOR PRINTING YEARLY TOTALS
11800 IF SCURRENTYEAR<ISTART THEN GOTO 12060
11820 IF SCOUNTER>=21 AND MENUNUM%<>3 THEN GOSUB 10740
11840 IF PRINTER=1 THEN GOSUB 12760
11860 IF SCOUNTER>=21 AND MENUNUM%=3 THEN GOSUB 12100
11880 IF IDISPLAY<>1 THEN PRINT:SCOUNTER=SCOUNTER+1
11900 PRINT "*YEAR:";
11920 PRINT USING "###";SCURRENTYEAR;
11940 PRINT USING "$$###########.##";DINTYEAR;
11960 PRINT USING "  $$###########.##";DPRINYEAR;
11980 PRINT USING "     $$#############.##";DBO
12000 SCOUNTER=SCOUNTER+1
12020 IF SCOUNTER<21 AND IDISPLAY<>1 THEN PRINT:SCOUNTER=SCOUNTER+1
12040 IF SJ1<>SJ2 AND SCOUNTER<21 THEN PRINT:SCOUNTER=SCOUNTER+1
12060 DINTYEAR=0:DPRINYEAR=0
12080 RETURN
12100 REM ********************  ROUTINE TO DISABLE SCREEN PAUSE  ***********
12120 TEST$=INKEY$
12140 IF TEST$=CHR$(13) THEN GOTO 12300
12160 PRINT CHR$(13);SPC(75);CHR$(13);
12180 SCOUNTER=0
12200 PRINT " ********  SCREEN PAUSE DISABLED.  PRESS RETURN TO ENABLE.  *******";
12220 FOR ILOOP=1 TO 800
12240 NEXT ILOOP
12260 TEST$=INKEY$
12280 IF TEST$<>CHR$(13) THEN GOSUB 10060:RETURN
12300 SCOUNTER=0
12320 PRINT CHR$(13);SPC(75);CHR$(13);
12340 PRINT "                SELECT (C)ONTINUE OR (A)BORT "
12360 MENULIST$="CA"
12380 GOSUB 1540
12400 IF MENUNUM%=1 THEN GOSUB 10060:MENUNUM%=0:RETURN
12420 IF MENUNUM%=2 THEN RETURN
12440 STOP
12460 REM ----------------ROUTINE FOR PRINTER PAGE HEADER-----------------
12480 LPRINT " *********************  LOAN AMORTIZATION TABLE  ***********************"
12500 LPRINT " PRINCIPAL AMOUNT: ";
12520 LPRINT USING "$$###########.##";DPRINCIPAL;
12540 LPRINT "  PAYMENT AMOUNT: ";
12560 LPRINT USING "$$#########.##";DPAYMENT
12580 LPRINT " TERM IN YEARS: ";
12600 LPRINT USING "             ###.# ";SYEARS;
12620 LPRINT "  INTEREST RATE: ";
12640 LPRINT USING "         ###.##";SINTEREST;:LPRINT "%"
12660 LPRINT " ***********************************************************************"
12680 LPRINT " PAYMENT #       INTEREST         PRINCIPAL        BALANCE AFTER PAYMENT"
12700 LPRINT " -----------------------------------------------------------------------"
12720 LET SLCOUNTER=6
12740 RETURN
12760 REM --------------------------- ROUTINE TO LPRINT YEARLY TOTALS -----
12780 IF IDISPLAY=1 THEN LPRINT:SLCOUNTER=SLCOUNTER+1
12800 LPRINT "*YEAR:";
12820 LPRINT USING "###";SCURRENTYEAR;
12840 LPRINT USING "$$###########.##";DINTYEAR;
12860 LPRINT USING "  $$###########.##";DPRINYEAR;
12880 LPRINT USING "     $$#############.##";DBO
12900 LPRINT:SLCOUNTER=SLCOUNTER+2
12920 RETURN
12940 REM ----------  ROUTINE TO PUT PAGE NUMBERS ON PRINTOUT
12960 REM
12980 IPAGE=IPAGE+1
13000 FOR PAGECOUNT=1 TO (62-SLCOUNTER)
13020 LPRINT:NEXT PAGECOUNT
13040 LPRINT "                             ";IPAGE
13060 LPRINT CHR$(12)
13080 RETURN
13100 REM    SUBROUTINE FOR SETTING FLAG FOR FIRST YEAR OF PRINTOUT
13120 PRINT:PRINT:PRINT " Do you want to start with a year other than 1?  (Y or N) "; 
13140 GOSUB 1740
13160 IF MENUNUM%=2 THEN ISTART=0:RETURN
13180 INPUT " Please enter the year you want to start with..... ",ISTART
13200 IF ISTART>SYEARS THEN LET ISTART=SYEARS
13220 RETURN
13240 REM *******************MENU CHOICE H*****************************
13260 PRINT "   From the above menu, please select the item you need help with."
13280 MENULIST$="ABCDEFGX"
13300 GOSUB 1540
13320 ON MENUNUM% GOSUB 13360,13760,13980,14260,14520,14760,15000,15500
13340 GOTO 1320
13360 REM ----  MENU SELECTION A
13380 PRINT CLS$
13400 PRINT
13420 PRINT "       *** LOAN PRINCIPAL AMOUNT ***"
13440 PRINT
13460 PRINT " This module will calculate the amount of money initially borrowed."
13480 PRINT " You must enter the amount of the payments, the interest rate, the"
13500 PRINT " number of payments within a year and the number of years over which"
13520 PRINT " the loan is going to be amortized."
13540 PRINT:GOSUB 13560:RETURN
13560 PRINT " Using the menu, select each item that needs to be entered.  As soon"
13580 PRINT " as you've entered the needed variables, the program will perform the"
13600 PRINT " calculation and display the results.  To try a different variable,"
13620 PRINT " use the menu to select which one you want to change.  Enter the new"
13640 PRINT " value and the calculation will be redone automatically for you."
13660 PRINT
13680 PRINT " You cannot enter a negative number for any variable in this program."
13700 PRINT " Do not use any commas when entering variables.  Press the return"
13720 PRINT " after entering each variable."
13740 GOSUB 15540:RETURN
13760 REM      HELP FOR MENU CHOICE B
13780 PRINT CLS$;
13800 PRINT
13820 PRINT "         ** REGULAR PAYMENT **"
13840 PRINT 
13860 PRINT " This module will calculate the amount of the regular payment needed to"
13880 PRINT " pay off a loan over a given time.  You must enter the amount borrowed,"
13900 PRINT " the interest rate, the number of payments per year and the number of years"
13920 PRINT " or term of the loan."
13940 PRINT
13960 GOSUB 13560:RETURN
13980 REM    HELP FOR ITEM C
14000 PRINT CLS$;
14020 PRINT
14040 PRINT "        **  LAST PAYMENT ON A LOAN  **"
14060 PRINT
14080 PRINT " Because of rounding errors, the last payment on a loan is usually slightly"
14100 PRINT " different than the regular payment.  This module actually does a com-"
14120 PRINT " plete loan amortization table in memory and calculates the exact amount"
14140 PRINT " of the final payment.  You must enter the regular payment, the principal,"
14160 PRINT " the term (in years) the interest rate and the number of payments per"
14180 PRINT " year.  If any of these variables need to be calculated, use the other"
14200 PRINT " modules first and then select this module from the MAIN MENU."
14220 PRINT
14240 GOSUB 13560:RETURN
14260 REM     HELP FOR MENU ITEM D
14280 PRINT CLS$
14300 PRINT
14320 PRINT "      **  REMAINING BALANCE ON A LOAN  **"
14340 PRINT
14360 PRINT " This module will calculate the amount remaining on the principal of a"
14380 PRINT " loan after a specific number of payments have been made.  Typically,"
14400 PRINT " this would be needed in the event that it was desired to pay off a loan"
14420 PRINT " early.  The module actually does a loan amortization table in memory"
14440 PRINT " and stops at the payment you have specified.  The balance of the
14460 PRINT " PRINCIPAL is then displayed.
14480 PRINT
14500 GOSUB 13560:RETURN
14520 REM      HELP FOR MENU ITEM E
14540 PRINT CLS$
14560 PRINT
14580 PRINT "     **  TERM OF A LOAN  **
14600 PRINT
14620 PRINT " This module will determine the time (in years) needed to repay a loan"
14640 PRINT " for a given set of variables.  For example, this could be used to see
14660 PRINT " what effect changing the payment or the interest would have on the
14680 PRINT " period required to repay the loan.  The program will not allow an entry
14700 PRINT " that would result in the loan being under-amortized such as would happen
14720 PRINT " in the event that the payment was too small to ever repay the loan.
14740 PRINT:GOSUB 13560:RETURN
14760 REM       HELP FOR MENU ITEM F
14780 PRINT CLS$
14800 PRINT
14820 PRINT "      **  ANNUAL INTEREST RATE ON A LOAN  **
14840 PRINT 
14860 PRINT " This module will calculate the interest rate on a loan given a specific
14880 PRINT " set of variables.  This is useful if the interest rate is unknown or if
14900 PRINT " it is desired to determine the impact on interest of changes in other
14920 PRINT " variables.  The program cannot calculate interest rates that are greater
14940 PRINT " than 25%.
14960 PRINT
14980 GOSUB 13560:RETURN
15000 REM           HELP FOR ITEM G
15020 PRINT CLS$;
15040 PRINT "       **  LOAN AMORTIZATION TABLE  **
15060 PRINT 
15080 PRINT " This module will show the amount of interest and principal paid for
15100 PRINT " each payment on a loan.  This listing can be displayed on the console
15120 PRINT " screen only or it can be listed to a printer simultaneously.  Since
15140 PRINT " the table can only be accurate if the variables are precisely calculated,
15160 PRINT " you have to use other modules to make changes to the variables before
15180 PRINT " you can run the amortization table module.  Selecting an item from
15200 PRINT " the menu to be changed will automatically chain you into the appropriate
15220 PRINT " module.
15240 PRINT
15260 PRINT " If the printer is selected, you will be asked for information to go
15280 PRINT " on the title block on the printer.  This information will be saved
15300 PRINT " and does not have to be reentered if you go to another module and then
15320 PRINT " return to the amortization module.
15340 PRINT 
15360 PRINT " You should check the printer to be sure it is ready prior to trying 
15380 PRINT " to send a listing to the printer.  If the printer is not ready, the
15400 PRINT " program will display a message and the program will stop.  If the"
15420 PRINT " printer cannot be made ready, you will have to abort the program using"
15440 PRINT " the ^C key."
15460 PRINT
15480 GOSUB 15540:RETURN
15500 REM
15520 REM
15540 PRINT:PRINT " PRESS ANY KEY TO RETURN TO THE MENU. ";:ANS$=INPUT$(1):RETURN
15560 REM
15580 REM *******************MENU CHOICE X*****************************
15600 PRINT CLS$
15620 PRINT
15640 PRINT 
15660 PRINT " RETURN TO OPERATING SYSTEM?  (Y OR N)"
15680 MENULIST$="YN"
15700 GOSUB 1540
15720 ON MENUNUM% GOTO 15760,2660
15740 REM
15760 PRINT
15780 PRINT
15800 PRINT
15820 PRINT " Now returning control to the operating system."
15840 PRINT
15860 SYSTEM
15880 REM   "L" TEST LOAD OPTION
15900 DPRINCIPAL=15000
15920 SINTEREST=8
15940 DPAYMENT=263
15960 SYEARS=6
15980 IPAYMENTNUM=12
16000 PRINT "      ********  NOW LOADING TEST VALUES INTO VARIABLES  *******";
16020 FOR G=1 TO 200
16040 NEXT G
16060 PRINT CHR$(13);SPC(70);CHR$(13);
16080 MENULIST$="ABCDEFGHX"
16100 GOSUB 1580
16120 GOTO 3220
 TO 200
16040 NEXT G
16060 PRINT CHR$(13);SPC(70);CHR$(13);
16080 MENUL