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


Quellcode-Bibliothek

© Kompilation durch diese Firma

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

Datei: kette3.cob   Sprache: Cobol

Original von: verschiedene©

       identification division.
       program-id. mercury.
      * aus Dirk Hoffmann,
      * Software-Qualität
      * Kapitel 4, Springer 2008
       author"JD".
       date-written. 28.1.2009.
       date-compiled.
       data division.
       working-storage section.
        77 temp  pic S9(4)V9(4) comp-1.
        77 temp1 pic S9(4)V9(4) comp-1.
        77 temp2 pic S9(4)V9(4) comp-1.
     *
        77 TVAL  pic S9(4)V9(4) comp-1.
        77 M     pic 9(4) comp.
        77 K     pic 9(4) comp.
        77 N0    pic 9(4) comp.
        77 W0    pic S9(4)V9(4) comp-1.
        77 X     pic S9(4)V9(4) comp-1.
        77 H     pic S9(4)V9(4) comp-1.
        77 EPS   pic S9(4)V9(4) comp-1.
        77 B0    pic S9(4)V9(4) comp-1.
        77 IER   pic S9(4)V9(4) comp-1.
        77 T     pic S9(4)V9(4) comp-1 occurs 100.
        77 Z     pic S9(4)V9(4) comp-1.
        77 D     pic S9(4)V9(4) comp-1 occurs 100.
        77 Y     pic S9(4)V9(4) comp-1.
        77 BL    pic S9(4)V9(4) comp-1.
        77 E     pic S9(4)V9(4) comp-1 occurs 100.
        77 B1    pic S9(4)V9(4) comp-1.
       procedure division.
        if TVAL less 0.2e-2 goto L40.
        move 1 to M.
        CONTINUE40.
          if M>3 goto L40.
          compute W0=(M-1)*0.5
          compute X=H*1.74533E-2*W0
          move 1 to N0.
        CONTINUE20.
            if N0>8 GOTO L20.
      *     compute eps=5.0*10.0**(n0-7)
            subtract 7 from N0 giving temp
            compute temp=function exp(10.0,temp)
            compute eps=5.0*temp
            call besj using x 0 b0 eps ier
            if ier equal 0 goto l10 end-if
            add 1 to N0.
          GOTO CONTINUE20.
          MOVE 1 to K.
        L20. 
          continue.
        CONTINUE5.
          if  K>3 GOTO L5.
          move W0 to T(K)
      *   compute z=1.0/(x**2)*b1*
      *   2+3.0977e-4*b0**2
          compute temp1=function exp(X,2)
          compute temp2=function exp(B0,2)
          compute Z=1.0/temp1*BL*2+3.0977E-4*temp2
      *   compute d(k)=3.076Ee-1*2.0
      *   **(B0**2-X-B0ÜB1))/Z
          compute  temp1=B0*B0-X-B0*B1
          compute  temp2=function exp(2.0,temp1)
          compute  D(k)=3.076E-1*temp2/Z
          compute  temp=H**2
          compute  E(K)=temp*93.2943*W0/function sin(W0)*Z
          subtract E(k) from D(k) giving H
          add 1 to k.
          GOTO CONTINUE5.
        L5.
          continue.
          compute Y=H/W0-1.
          add 1 to M.
        GOTO CONTINUE40.
        L40.
          continue.
        end program mercury.

¤ Dauer der Verarbeitung: 0.16 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