Anforderungen  |   Konzepte  |   Entwurf  |   Entwicklung  |   Qualitätssicherung  |   Lebenszyklus  |   Steuerung
 
 
 
 


Quellcode-Bibliothek

© Kompilation durch diese Firma

[Weder Korrektheit noch Funktionsfähigkeit der Software werden zugesichert.]

Datei: banksample.cob   Sprache: Cobol

Original von: verschiedene©

      IDENTIFICATION DIVISION
      PROGRAM-ID. BANKPROGRAM. 
      AUTHOR. Nick. 
      *This program is used to model the ATM at Orlove National Bank. 
      *The following lines are the variable information required to 
      *run BANKPROGRAM. 
      date-written. 5.5.2010.
      ENVIRONMENT DIVISION
      INPUT-OUTPUT SECTION
      FILE-CONTROL
      SELECT BankFile ASSIGN TO "BANKRECORDS.DAT" 
      ORGANIZATION IS LINE SEQUENTIAL
      
      DATA DIVISION
      FILE SECTION
      FD BankFile. 
      01 customerInfo PIC X(31). 
      
      WORKING-STORAGE SECTION
      01 userChoice PIC 9 VALUE ZEROS. 
      01 x PIC 9(2) VALUE 1. 
      01 y PIC 9(1) VALUE ZERO
      01 numChars PIC 9(2). 
      01 tempInputName PIC X(10). 
      01 tempInputPin PIC 9(4). 
      01 tempLoginCred PIC X(16). 
      01 tempUserName PIC X(13). 
      01 tempPin PIC X(7). 
      01 tempPin2 PIC X(7). 
      01 tempAccountBalance PIC X(18). 
      01 tempAccountBalance2 PIC X(18). 
      01 tempCustomerInfo PIC X(31). 
      01 userName PIC X(10). 
      01 pin PIC 9(4). 
      01 accountBalance PIC 9(15). 
      01 discoveredUser PIC X(10). 
      01 discoveredPin PIC 9(4). 
      01 tempDiscoveredBal PIC 9(15). 
      01 discoveredBal PIC 9(15). 
      01 easyReadBal PIC 9(15). 
      01 depositAmount PIC 9(15). 
      01 withdrawAmount PIC 9(15). 
      01 cusFull PIC X(31). 
      01 counter usage binary-long. 
      01 counter2 usage binary-long. 
      01 counter3 usage binary-long. 
      01 finalCount PIC 9(4). 
      01 file-eof PIC 9 VALUE low-value
      88 at-eof VALUE high-values. 
      01 customerList. 
      05 customer-table OCCURS 100000 TIMES 
      DEPENDING ON counter 
      ASCENDING KEY IS cusStr 
      INDEXED BY cus-index. 
      10 cusStr PIC X(10). 
      01 customerList2. 
      05 customer-table2 OCCURS 100000 TIMES 
      DEPENDING ON counter2 
      ASCENDING KEY IS cusPin 
      INDEXED BY cus-index2. 
      10 cusPin PIC X(16). 
      01 listForRewrite. 
      05 customer-table3 OCCURS 100000 TIMES 
      DEPENDING ON counter3 
      ASCENDING KEY IS cusSpot 
      INDEXED BY cus-index3. 
      10 cusSpot PIC X(16). 
      
      
      *This instance method begins BANKPROGRAM by calling the WelcomeMessage 
      *which is the primary instance method in this program. 
      PROCEDURE DIVISION
      Begin. 
      PERFORM WelcomeMessage. 
      STOP RUN
      
      *This instance method's role is to ask the user whether they are a 
      *new customer or an existing one. If they are new, NewUser is called 
      *and if they are existing, Login is called. 
      WelcomeMessage. 
      DISPLAY " "
      DISPLAY "Welcome to the Orlove National Bank."
      DISPLAY "What would you like to do?"
      DISPLAY "Log in? (please type 1)"
      DISPLAY "Or create a new account? (please type 2)"
      ACCEPT userChoice. 
      IF userChoice = 1 THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      PERFORM Login 
      ELSE 
      IF userChoice = 2 THEN 
      PERFORM NewUser 
      ELSE 
      PERFORM NewLine 
      MOVE ZERO TO x 
      DISPLAY "I'm sorry, that was an invalid" 
      - " command. Restarting." 
      PERFORM WelcomeMessage 
      END-IF
      
      *This is the primary instance method for the existing user part 
      *of the program. It accepts the username and pin number from the 
      *user attempting to log in and then searches through BankFile 
      *to see if their supplied credentials matches anything on file. 
      Login. 
      DISPLAY " "
      DISPLAY "Please enter in your User Name. "
      ACCEPT tempInputName. 
      DISPLAY "Please enter in your pin number."
      ACCEPT tempInputPin. 
      STRING tempInputName,"~",tempInputPin,"~" 
      DELIMITED BY SIZE INTO tempLoginCred 
      OPEN I-O BankFile 
      MOVE low-value TO file-eof 
      READ BankFile 
      AT END SET at-eof TO TRUE 
      END-READ 
      PERFORM 
      WITH TEST BEFORE 
      UNTIL at-eof OR (counter2 > 100000) 
      ADD 1 TO counter2 
      MOVE customerInfo TO cusPin(counter2) 
      IF cusPin(counter2) = tempLoginCred THEN 
      MOVE customerInfo TO cusFull 
      END-IF 
      READ BankFile 
      AT END SET at-eof TO TRUE 
      END-READ 
      END-PERFORM
      SORT customer-table2 on ascending key cusPin. 
      SET cus-index2 TO 1. 
      SEARCH ALL customer-table2 
      AT END PERFORM UserNameNotFound 
      WHEN cusPin(cus-index2) = tempLoginCred 
      PERFORM NewLine 
      MOVE ZERO TO x 
      DISPLAY "Log in successful!" 
      UNSTRING cusFull DELIMITED BY ALL "~" 
      INTO discoveredUser, discoveredPin, 
      tempDiscoveredBal 
      END-UNSTRING 
      PERFORM Menu 
      END-SEARCH
      
      *The UserNameNotFound instance method is called when the supplied 
      *user credentials don't match any records on file. 
      UserNameNotFound. 
      PERFORM NewLine. 
      MOVE ZERO TO x. 
      DISPLAY "I'm sorry, your username/password is incorrect. "
      - "Restarting"
      CLOSE BankFile. 
      PERFORM WelcomeMessage. 
      
      *The Menu instance method is used to display the choices available 
      *to the already logged in user. This method gets directed to either 
      *the CheckBalance, DepositMoney, WithdrawMoney, or WelcomeMessage 
      *methods. When the user chooses to log out, the users file is 
      *re-written to the BankFile and permanently saved by calling the 
      *SaveFile instance method. 
      Menu. 
      DISPLAY "You are logged in, what would you like to do?"
      DISPLAY "Check your balance (please type 1)"
      DISPLAY "Deposit money into your account " 
      - "(please type 2)"
      DISPLAY "Withdraw from your account (please type 3)"
      DISPLAY "Log out (please type 4)"
      ACCEPT userChoice. 
      IF userChoice = 1 THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      PERFORM CheckBalance 
      ELSE 
      IF userChoice = 2 THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      PERFORM DepositMoney 
      ELSE 
      IF userChoice = 3 THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      PERFORM WithdrawMoney 
      ELSE 
      IF userChoice = 4 THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      CLOSE BankFile 
      PERFORM SaveFile 
      ELSE 
      PERFORM NewLine 
      MOVE ZERO TO x 
      DISPLAY "I'm sorry, that was an" 
      - " invalid command. Restarting." 
      CLOSE BankFile 
      PERFORM WelcomeMessage 
      END-IF
      PERFORM Menu. 
      
      *This instance method has the task of saving the appropriate 
      *changes to the external BankFile. 
      SaveFile. 
      **************************************************** 
      DISPLAY "Now saving file..." 
      STRING discoveredUser,"~",discoveredPin,"~"
      discoveredBal DELIMITED BY SIZE INTO 
      customerInfo 
      END-STRING
      MOVE customerInfo TO tempCustomerInfo. 
      OPEN I-O BankFile. 
      MOVE low-value TO file-eof. 
      READ BankFile 
      AT END SET at-eof TO TRUE 
      END-READ
      MOVE y TO counter3. 
      PERFORM 
      WITH TEST BEFORE 
      UNTIL at-eof OR (counter3 > 100000) 
      ADD 1 TO counter3 
      MOVE customerInfo TO cusSpot(counter3) 
      IF cusSpot(counter3) = tempLoginCred THEN 
      DISPLAY "IN THE LOOP!!" 
      MOVE counter3 TO finalCount 
      DISPLAY "counter is: " finalCount 
      MOVE tempCustomerInfo TO customerInfo 
      DISPLAY "info to write: "customerInfo 
      REWRITE customerInfo 
      END-IF 
      READ BankFile 
      AT END SET at-eof TO TRUE 
      END-READ 
      END-PERFORM
      
      CLOSE BankFile. 
      PERFORM WelcomeMessage. 
      
      *This instance method simply checks the amount of money on 
      *file in the users account. 
      CheckBalance. 
       MOVE tempDiscoveredBal TO easyReadBal 
      INSPECT easyReadBal REPLACING LEADING "0" BY "*"
      DISPLAY "Your balance is: $" easyReadBal. 
      
      *The DepositMoney instance method accepts in an amount of money 
      *to add into the users account. 
      DepositMoney. 
      DISPLAY "How much money would you like to deposit? " 
      - "(please do not put a dollar sign or commas " 
      - "and keep the balance less than $9.99 Billion)"
      ACCEPT depositAmount. 
      MOVE ZERO TO numChars. 
      INSPECT FUNCTION REVERSE(depositAmount) TALLYING 
      numChars FOR TRAILING ZEROS. 
      COMPUTE numChars = numChars - 15. 
      IF numChars > 10 OR < 1 THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      DISPLAY "I'm sorry, the ammount of money you ent" 
      - "ered did not follow the requirements. Restarting." 
      PERFORM DepositMoney 
      ELSE 
      IF depositAmount NOT NUMERIC THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      DISPLAY "I'm sorry, the ammount of money you ent" 
      - "ered did not follow the requirements. Restarting." 
      PERFORM DepositMoney 
      ELSE 
      ADD depositAmount TO tempDiscoveredBal 
      MOVE tempDiscoveredBal TO discoveredBal 
      END-IF
      PERFORM NewLine. 
      MOVE ZERO TO x. 
      
      *The WithdrawMoney instance method accepts in an amount of money 
      *to subtract from the users account. 
      WithdrawMoney. 
      DISPLAY "How much money would you like to withdraw?"
      ACCEPT withdrawAmount. 
      MOVE ZERO TO numChars. 
      INSPECT FUNCTION REVERSE(withdrawAmount) TALLYING 
      numChars FOR TRAILING ZEROS. 
      COMPUTE numChars = numChars - 15. 
      IF numChars > 10 OR < 1 THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      DISPLAY "I'm sorry, the ammount of money you ent" 
      - "ered did not follow the requirements. Restarting." 
      PERFORM WithdrawMoney 
      ELSE 
      IF withdrawAmount NOT NUMERIC THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      DISPLAY "I'm sorry, the ammount of money you ent" 
      - "ered did not follow the requirements. Restarting." 
      PERFORM WithdrawMoney 
      ELSE 
      SUBTRACT withdrawAmount FROM 
      tempDiscoveredBal 
      MOVE tempDiscoveredBal TO discoveredBal 
      END-IF
      PERFORM NewLine. 
      MOVE ZERO TO x. 
      
      
      *The Newuser instance method asks the user to input specific data 
      *required to open a bank account. Once NewUser obtains a valid 
      *username, it calls ObtainPin. To be considered valid, the username 
      *must not already been taken, and must be between 1 and 10 characters. 
      NewUser. 
      DISPLAY " "
      DISPLAY "Please follow the simple instructions to " 
      - "open up an account with us." 
      DISPLAY "What would you like your username to be? " 
      - "(please limit to 10 characters but greater than 1)"
      ACCEPT tempUserName. 
      MOVE ZERO TO numChars 
      INSPECT FUNCTION REVERSE(tempUserName) TALLYING numChars 
      FOR LEADING SPACES
      COMPUTE numChars = LENGTH OF tempUserName - numChars. 
      IF numChars > 10 OR < 1 THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      DISPLAY "I'm sorry, your username did not follow" 
      - " the requirements. Restarting." 
      PERFORM NewUser 
      END-IF
      MOVE tempUserName TO userName. 
      OPEN INPUT BankFile 
      MOVE low-value TO file-eof 
      READ BankFile 
      AT END SET at-eof TO TRUE 
      END-READ 
      MOVE y TO counter 
      PERFORM 
      WITH TEST BEFORE 
      UNTIL at-eof OR (counter > 100000) 
      ADD 1 TO counter 
      MOVE customerInfo TO cusStr(counter) 
      READ BankFile 
      AT END SET at-eof TO TRUE 
      END-READ 
      END-PERFORM
      SORT customer-table on ascending key cusStr. 
      SET cus-index TO 1 
      SEARCH ALL customer-table 
      AT END PERFORM FinishUserName 
      WHEN cusStr(cus-index) = userName 
      PERFORM NewLine 
      MOVE ZERO TO x 
      DISPLAY "I'm sorry, your username has already" 
      - " been taken. Restarting." 
      CLOSE BankFile 
      PERFORM NewUser 
      END-SEARCH
      
      *The FinishUserName instance method is used to close the 
      *BankFile and move onto the next method which is to get the 
      *pin number from the user. 
      FinishUserName. 
            CLOSE BankFile. 
      DISPLAY "Your user name is: " userName. 
      PERFORM ObtainPin. 
      
      *The ObtainPin instance method asks for a valid pin from the user, 
      *once one is accepted, ObtainAccountBalance is called. A valid pin 
      *is any 4 digit number. 
      ObtainPin. 
      DISPLAY "What would your like your 4 digit pin to be?"
      ACCEPT tempPin. 
      MOVE ZERO TO numChars. 
      INSPECT FUNCTION REVERSE(tempPin) TALLYING numChars 
      FOR LEADING SPACES
      COMPUTE numChars = LENGTH OF tempPin - numChars. 
      IF numChars NOT EQUAL 04 THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      DISPLAY "I'm sorry, your pin did not follow" 
      - " the requirements. Restarting." 
      PERFORM ObtainPin 
      END-IF
      MOVE tempPin TO tempPin2. 
      INSPECT tempPin2 REPLACING ALL " " BY "1"
      IF tempPin2 NOT NUMERIC THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      DISPLAY "I'm sorry, your pin did not follow" 
      - " the requirements. Restarting." 
      PERFORM ObtainPin 
      END-IF
      MOVE tempPin TO pin. 
      DISPLAY "Your pin is: " pin. 
      PERFORM ObtainAccountBalance. 
      
      *The ObtainAccountBalance instance method asks for a valid sum 
      *of money from the user that the user is depositing into the 
      *bank. A valid sume of money is any numeric amount less than 9.99 
      *BillionOnce one is accepted, all the user specified information 
      *is written to the BANKRECORDS.DAT file. 
      ObtainAccountBalance. 
      DISPLAY "How much money are you depositing with us " 
      - "today? (please do not put a dollar sign or commas " 
      - "and keep the balance less than $9.99 Billion)"
      ACCEPT tempAccountBalance. 
      MOVE ZERO TO numChars. 
      INSPECT FUNCTION REVERSE(tempAccountBalance) TALLYING 
      numChars FOR LEADING SPACES
      COMPUTE numChars = LENGTH OF tempAccountBalance - 
      numChars. 
      IF numChars > 10 OR < 1 THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      DISPLAY "I'm sorry, the ammount of money you ent" 
      - "ered did not follow the requirements. Restarting." 
      PERFORM ObtainAccountBalance 
      END-IF
      MOVE tempAccountBalance TO tempAccountBalance2. 
      INSPECT tempAccountBalance2 REPLACING ALL " " BY "1"
      IF tempAccountBalance2 NOT NUMERIC THEN 
      PERFORM NewLine 
      MOVE ZERO TO x 
      DISPLAY "I'm sorry, the ammount of money you ent" 
      - "ered did not follow the requirements. Restarting." 
      PERFORM ObtainAccountBalance 
      END-IF
      MOVE tempAccountBalance TO accountBalance. 
      PERFORM NewLine. 
      MOVE ZERO TO x. 
      DISPLAY "The ammount of money you are depositing is $" 
      accountBalance. 
      STRING userName,"~",pin,"~",accountBalance 
      DELIMITED BY SIZE INTO customerInfo 
      END-STRING
      OPEN EXTEND BankFile. 
      WRITE customerInfo. 
      CLOSE BankFile. 
      DISPLAY "Thank you for opening a bank account with us!"
      DISPLAY "Please press enter to log in."
      ACCEPT userChoice. 
      PERFORM NewLine 
      MOVE ZERO TO x 
      PERFORM WelcomeMessage. 
      
      *The NewLine instance method creates a new line block to make 
      *the program easier to use and view. The empty block consists 
      *of 40 lines. 
      NewLine. 
      PERFORM UNTIL x > 40 
      DISPLAY " " 
      COMPUTE x = x + 1 
      END-PERFORM.

¤ Dauer der Verarbeitung: 0.31 Sekunden  (vorverarbeitet)  ¤





Download des
Quellennavigators
Download des
sprechenden Kalenders

in der Quellcodebibliothek suchen




Haftungshinweis

Die Informationen auf dieser Webseite wurden nach bestem Wissen sorgfältig zusammengestellt. Es wird jedoch weder Vollständigkeit, noch Richtigkeit, noch Qualität der bereit gestellten Informationen zugesichert.


Bemerkung:

Die farbliche Syntaxdarstellung ist noch experimentell.


Bot Zugriff



                                                                                                                                                                                                                                                                                                                                                                                                     


Neuigkeiten

     Aktuelles
     Motto des Tages

Software

     Produkte
     Quellcodebibliothek

Aktivitäten

     Artikel über Sicherheit
     Anleitung zur Aktivierung von SSL

Muße

     Gedichte
     Musik
     Bilder

Jenseits des Üblichen ....
    

Besucherstatistik

Besucherstatistik