Next Previous Contents

1. Structure des programmes et instructions de base

1.1 Structure d'un programme

Un programme COBOL comporte quatre divisions qui contiennent des sections formées de paragraphes. Chaque paragraphe commence par une étiquette, et contient des phrases terminées par des points. Chaque phrase est composée d'instructions (ou de déclarations) commençant par un verbe et comportant éventuellement des clauses optionnelles.

identification division

Cette division fournit une documentation minimale du programme. Elle contient le nom du programme, et des commentaires divers : l'auteur, notice d'installation, la date d'écriture du programme, etc.

environment division

Décrit l'environnement dans lequel ce programme est exploité (configuration section). Par exemple : jeu de caractères utilisé, signe monétaire, signe décimal... Décrit aussi les fichiers (input-output section) que le programme utilisera (chemin d'accès, type, méthode d'accès,...).

data division

Décrit les variables en mémoire. Variables associées aux fichiers (file section), variables de travail (working-storage section), paramètres formels des sous-programmes (linkage section), variables de communication (communication section) et du générateur d'états (report section).

procedure division

Contient les instructions du programme.

1.2 Instructions

Arrêt

L'instruction stop run met fin au déroulement d'un programme COBOL.

Affectation

Exemples :

move 0 to total.
move spaces to ligne1, ligne 2.

Calcul

On peut employer des verbes spécifiques (add, subtract, multiply, divide) ou bien compute qui enchaîne plusieurs opérations.

Exemples :

add 1 to compteur.
add TOTAL-MATIN, TOTAL-SOIR giving TOTAL-JOURNEE.
add TOTAL-JOURNEE to TOTAL-MOIS, TOTAL-ANNEE.
subtract REMISE from PRIX.
multiply QUANTITE, PRix-UNITAIRE giving PRIX.
divide POIDS-GATEAU by NOMBRE-PARTS giving POIDS-PART.
divide NB-FROMAGE by NB-SOURIS giving PART-SOURIS remainder RESTE.
compute PRIX = (PRIX-UNITAIRE * QUANTITE) * (1 - POURCENT-REMISE / 100)
Des clauses optionnelles permettent de demander un arrondi, et de préciser ce qu'il faut faire si il y a (ou pas) débordement.

divide POIDS-GATEAU by NOMBRE-PARTS giving POIDS-PART rounded.

compute PRIX = (PRIX-UNITAIRE * QUANTITE) * (1 - POURCENT-REMISE / 100)
        on size error display "Debordement"
                      display "Donnees probablement incorrectes"
                      move 17 to CODE-ERREUR
        not on size error
                      move 0 to CODE-ERREUR
end-compute.

Conditionnelles

if ... then ... else ... end-if

if NOM = spaces then move 17 to CODE-ERREUR.

if TOTAL-JOURNEE > TOTAL-MEILLEURE-JOURNEE
then
   move TOTAL-JOURNEE to TOTAL-MEILLEURE-JOURNEE
   move JOUR to MEILLEUR-JOUR
end-if.

if A > B then 
   move A to MAX
   move B to MIN
else
   move A to MIN
   mode B to MAX
end-if.

Lorsque le délimiteur end-if est omis, le corps du if se prolonge jusqu'au prochain délimiteur, ou au point qui termine la phrase.

Evaluate

evaluate REPONSE
when "OUI"
when "oui"
      move 1 to CODE-REPONSE
when "NON"
when "non" 
      move 2 to CODE-REPONSE
when other
      move 99 to CODE-REPONSE
end-evaluate.

evaluate MOY-GENERALE 
when 10 thru 20 move "Recu"      to RESULTAT
when  8 thru 10 move "Repechage" to RESULTAT
when other      move "Colle"     to RESULTAT
end-evaluate

evaluate NOTE-EXAM  also NOTE-STAGE
when     10 thru 20 also 10 thru 20
                               move "recu" to DECISION
when     9  thru 10 also 12 thru 10
                               move "rattrape par le stage" to DECISION
when     14 thru 20 also  9 thru 10
                               move "rattrape par notes exam" to DECISION
when other
                               move "Elimine" to DECISION
end-evaluate.

Perform : appel de sous-programme et répétition

L'instruction perform sert à la fois à faire des appels de sous-programmes et des boucles. Elle peut prendre deux formes :

L'usage du délimiteur de fin optionnel end-perform est recommandé pour la seconde forme (dite ``perform en ligne'').

Un appel simple de sous-programme s'écrit sans clauses:

perform CALCUL-REMISE.

La clause ``until condition'' permet de répéter une boucle jusqu'à ce qu'une condition devienne vraie. Si on la fait précéder par ``with test after'', la condition n'est pas testée à l'entrée dans la boucle, mais à la sortie. Exemples :

perform with test after until REPONSE = "OUI" or "NON"
   display QUESTION "(repondez par OUI ou NON) ? "
   accept  REPONSE
end-perform.

perform TRAITER-DONNEES 
until FIN-DONNEES = VRAI 
   or CODE-ERREUR not = 0. 

La clause n times répète n fois (boucle sans compteur):

perform SAUTER-LIGNE 10 times.
perform 3 times 
  display "Alerte !"
end-perform.

Une boucle avec compteurs s'obtient par la clause ``varying ... from ... by ... until ...''

perform varying I from 1 by 1 until I > 10
        move spaces to TABLEAU(I)
end-perform.

1.3 Entrées-sorties

Entrées-sorties interactives

display "Donnez un nombre entre " MIN " et " MAX " : ".
accept   REPONSE.

Entrées-sorties sur fichiers séquentiels

Les autres types de fichiers seront montrés ultérieurement.

Déclaration de fichier

environment division.
   input-output section.
   file-control.
       select FICHIER-CLIENTS assign to "/home/compta/clients"
       organization line sequential
       access sequential.

Déclaration d'enregistrement

data division.
   file section.
   fd FICHIER-CLIENT.
   01 F1-ENR.
      02 F1-NOM            pic X(30).
      02 F1-ADRESSE        pic X(40).
      02 F1-TELEPHONE      pic 9(10).

Ouverture de fichier

      open input FICHIER-CLIENT.
      open output FICHIER-CLIENT.
      open extend FICHIER-CLIENT.

Lecture, écriture

      read FICHIER-CLIENT
        at end move VRAI to FIN-FICHIER-CLIENT
        not at end perform TRAITER-ENREGISTREMENT-CLIENT
      end-read.
      
      write F1-ENR.

Fermeture de fichier

      close FICHIER-CLIENT.

1.4 Un exemple

Le programme

000001 IDENTIFICATION DIVISION.
       program-id. progtele.
       author. M. Billaud.
       date-written. 8/02/1998.
000005
      *
      * consultation du programme tele de la semaine.
      *
      * - realise avec Personal Cobol (Microfocus)
000010

       ENVIRONMENT DIVISION.
       INPUT-OUTPUT SECTION.
       file-control.
000015     select F-FILMS assign to "semaine.txt"
               organization line sequential.


       DATA DIVISION.
000020 FILE SECTION.

       fd F-FILMS.
       01 F-ENR.
           02 JOUR       pic XXX.
000025     02 CHAINE     pic XXXX.
      *    heure de debut et duree en minutes
           02 HHMM       pic 9999.
           02 DUREE      pic 999.
      *    titre
000030     02 TITRE      pic X(60).

       WORKING-STORAGE SECTION.

      * constantes definies par commodite.
000035 77  VRAI          pic X   value "V".
       77  FAUX          pic X   value "F".

       77  FIN-MENU      pic X.
       77  FIN-FICHIER   pic X.
000040
       77  CHOIX-MENU    pic X.

       01  LIGNE-AFFICHAGE.
           02            pic XX  value "* ".
000045     02 JOUR       pic XXX.
           02            pic X   value " ".
           02 CHAINE     pic X(4).
           02            pic XXX value " | ".
           02 HHMM       pic Z9B99.
000050     02            pic X   value " ".
           02 TITRE      pic X(30).
           02            pic XX  value " |".

       01  LIGNE-ETOILES pic X(50) value all "*".
000055
       77  JOUR-CHOISI   pic X(3).
       77  NB-FILMS      pic 999.


000060 PROCEDURE DIVISION.
       PRINCIPALE SECTION.
       DEBUT.
           display "hello".
           move FAUX to FIN-MENU.
000065     perform MENU until FIN-MENU = VRAI.
           stop run.

       MENU.
             display "Films de la semaine"
000070       display " ".
             display "T. Tous les films"
             display "J. Films d'un jour"
             display "C. Films d'une chaine"
             display "H. Recherche par heure de debut"
000075       display "Q. Quitter".
             display " "
             display "Votre choix ?"
             accept CHOIX-MENU
             evaluate CHOIX-MENU
000080       when "T"
             when "t"
                   perform EDITER-TOUS-FILMS
             when "J"
             when "j"
000085             perform EDITER-JOUR
             when "C"
             when "c"
                   perform EDITER-CHAINE
             when "H"
000090       when "h"
                   perform RECHERCHER-HORAIRE
             when "Q"
             when "q"
                   move VRAI to FIN-MENU
000095       when other
                   display "Choix invalide"
             end-evaluate.

       EDITER-TOUS-FILMS.
000100     move FAUX to FIN-FICHIER.
           open input F-FILMS.
           display LIGNE-ETOILES.
           move 0 to NB-FILMS.
           perform until FIN-FICHIER = VRAI
000105        move SPACES to F-ENR
              read F-FILMS
              at end
                 move VRAI to FIN-FICHIER
              not at end
000110           add 1 to NB-FILMS
                 perform AFFICHER-ENREGISTREMENT
              end-read
           end-perform.
           close F-FILMS.
000115     display LIGNE-ETOILES.
           display NB-FILMS " films trouves.".
           display " ".

       AFFICHER-ENREGISTREMENT.
000120     move CHAINE of F-ENR to CHAINE of LIGNE-AFFICHAGE.
           move JOUR   of F-ENR to JOUR   of LIGNE-AFFICHAGE.
           move HHMM   of F-ENR to HHMM   of LIGNE-AFFICHAGE.
           move TITRE  of F-ENR to TITRE  of LIGNE-AFFICHAGE.

000125     display LIGNE-AFFICHAGE.

       EDITER-JOUR.
           display "Quel Jour ? (3 premieres lettres majuscules)".
           accept JOUR-CHOISI.
000130
           move FAUX to FIN-FICHIER.
           open input F-FILMS.
           move 0 to NB-FILMS.
           display LIGNE-ETOILES.
000135     perform until FIN-FICHIER = VRAI
              move SPACES to F-ENR
              read F-FILMS
              at end
                 move VRAI to FIN-FICHIER
000140        not at end
                 if JOUR-CHOISI = JOUR of F-ENR
                 then
                   add 1 to NB-FILMS
                   perform AFFICHER-ENREGISTREMENT
000145           end-if
              end-read
           end-perform.
           close F-FILMS.
           display LIGNE-ETOILES.
000150     display NB-FILMS " films trouves pour le jour "
                   JOUR-CHOISI.
           display " ".

        EDITER-CHAINE.
000155           display "* EDITER-CHAINE : A completer".

        RECHERCHER-HORAIRE.
           display "* RECHERCHER-HORAIRE : A completer".

Les données : le fichier semaine.txt

SAMC+  0850095Touche pas a mon periscope
DIMC+  1800095Touche pas a mon periscope
JEUC+  1655095Touche pas a mon periscope
DIMC+  0225095Touche pas a mon periscope (VO)
LUNC+  1335095Touche pas a mon periscope
SAMC+  1020108Planete hurlante
LUNC+  1335108Planete hurlante
SAMC+  0335108La septieme demeure
DIMC+  0745087Dans les griffes de la momie
DIMC+  0920087Bienvenue dans l'age ingrat
DIMC+  1045097Esprits rebelles
LUNC+  2035097Esprits rebelles
DIMC+  1035124Carlas's song
MERC+  2230124Carlas's song (VO)
DIMARTE2045100The Horror Picture Show (VO)
DIMF2  2055140L. 627
DIMTF1 2250100La veuve noire
LUNF3  0020081La chanson d'une nuit
LUNF3  0140120Mais ne te promenes donc pas toute nue !
LUNC+  0354103Salut cousin
LUNC+  0525091Flipper
LUNLA5 1430100Knock

Travail à faire


Next Previous Contents