Knowledge Transfer COBAP Mario J' Bryson 8192002 Revision 2 - PowerPoint PPT Presentation

1 / 42
About This Presentation
Title:

Knowledge Transfer COBAP Mario J' Bryson 8192002 Revision 2

Description:

Knowledge Transfer. COBAP. Mario J. Bryson (8/19/2002 Revision 2) ... There was a semblance of standard on the data definition, but there was no ... – PowerPoint PPT presentation

Number of Views:46
Avg rating:3.0/5.0
Slides: 43
Provided by: zqwk
Category:

less

Transcript and Presenter's Notes

Title: Knowledge Transfer COBAP Mario J' Bryson 8192002 Revision 2


1
Knowledge TransferCOBAPMario J. Bryson
(8/19/2002 Revision 2)
  • To insert your company logo on this slide
  • From the Insert Menu
  • Select Picture
  • Locate your logo file
  • Click OK
  • To resize the logo
  • Click anywhere inside the logo. The boxes that
    appear outside the logo are known as resize
    handles.
  • Use these to resize the object.
  • If you hold down the shift key before using the
    resize handles, you will maintain the proportions
    of the object you wish to resize.

2
COBOL to ABAP (COBAP)
  • 3RD GENERATION LANGUAGE
  • (Procedural Driven)
  • TO
  • 4TH GENERATION LANGUAGE
  • (Event Driven)

3
Identify Program
  • COBOL
  • IDENTIFICATION DIVISION
  • PROGRAM_ID. ZZL002T.
  • ABAP
  • REPORT ZMJB_ZZL002T_TABLE.

4
Define Files
  • COBOL
  • ENVIRONMENT DIVISION
  • INPUT-OUTPUT SECTION.
  • FILE-CONTROL.
  • SELECT ZZL002T-FILE ASSIGN TO ZZL002T.
  • SELECT REPORT-FILE ASSIGN TO PRINTER.
  • ABAP
  • REPORT ZMJB_ZZL002T_TABLE.
  • TABLES ZZL002T.

5
Define File/Record
  • COBOL
  • DATA DIVISION
  • FILE SECTION.
  • FD ZZL002T-FILE
  • LABEL RECORDS ARE STANDARD
  • RECORD CONTAINS 80 CHARACTERS
  • BLOCK CONTAINS 0 RECORDS
  • DATA RECORD IS ZZL002T-RECORD.
  • 01 ZZL002T-RECORD PIC X(80).
  • ABAP
  • TABLES ZZL002T.

6
Record Layout
  • COBOL
  • WORKING-STORAGE SECTION.
  • 01 ZZL002T-RECORD-SAVE.
  • 05 RBUKRS PIC X(04).
  • 05 RYYLOB PIC X(05).
  • 05 RPRCTR PIC X(10).
  • 05 RACCT PIC X(10).
  • 05 TSL05 PIC S9(05)V99 COMP-3.
  • 05 TSL05 PIC S9(05)V99 COMP-3.
  • 05 FILLER PIC X(10).
  • ABAP
  • DATA
  • Begin of v_zzl002t_it occurs 0,
  • rbukrs like zzl002t-rbukrs,
  • ryylob like zzl002t-ryylob,
  • rprctr like zzl002t-rprctr,
  • racct like zzl002t-racct,
  • tsl05 like zzl002t-tsl05,
  • tsl06 like zzl002t-tsl06,

7
Parameters
  • COBOL
  • FD / WORKING-STORAGE SECTION / LINKAGE SECTION
  • ABAP
  • SELECTION-SCREEN begin of block..
    Select-options
  • s_bukrs for zzl002t-rbukrs.
  • Parameters
  • p_rzzlgd like zzl002t-rzzlgid.
  • p_ryyamy like zzl002t-ryyamy.
  • SELECTION-SCREEN end of block ..

8
SELECTION-SCREEN - BEFORE
9
Selection Text - BEFORE
10
Selection Text - AFTER
11
SELECTION-SCREEN After
12
Headings
  • COBOL
  • ENVIRONMENT DIVISION.
  • SPECIAL-NAMES.
  • C01 IS TOP-OF-PAGE.
  • FD REPORT-FILE
  • DATA RECORD IS REPORT-RECORD.
  • WORKING-STORAGE SECTION.
  • 01 HEADING-LINE1.
  • 05 HL1-KAKA PIC X(132) value
    rbukrs ryylob rprctr..
  • PROCEDURE DIVISION.
  • WRITE REPORT-RECORD FROM
    HEADING-LINE1
  • ABAP
  • TOP-OF-PAGE.
  • write /01 rbukrs,
  • 10 ryylob,
  • 20 rprctr,
  • 30 racct,
  • 57 tsl05,
  • 75 tsl06.

13
TEXT Symbols
14
Using TEXT Symbols as constant
15
Example of TEXT Symbols usage
  • ABAP
  • TOP-OF-PAGE.
  • write /01 text-001,
  • 10 text-002,
  • 20 text-003,
  • 30 text-004,
  • 57 text-005,
  • 75 text-006.

16
Pictures / Data / Constants
  • Cobol
  • FD / Working-Storage
  • Type Description
  • A Alpha
  • N Numeric
  • X Alpha-numeric
  • S9 Comp Binary (Signed)
  • S9 Comp-3 Pack field (Signed)
  • ABAP
  • Data / Constants ( Data are variables that can
    be modified, while Constants cannot be modified)
  • Type Description DL Initial
    value
  • C Character 1
    Space
  • N Numeric text 1
    '00...0'
  • D Date YYYYMMDD 8 '00000000'
  • T Time HHMMSS 6
    '000000'
  • X Byte (heXadecimal) 1 X'00'
  • I Integer 4
    0
  • P Packed number 8 0
  • F Floating point number 8 '0.0'

17
Examples
  • Cobol
  • 05 Num pic 9 value
    1.
  • 05 Alpa pic a value
    A.
  • 05 Alphanum pic xx value 1A.
  • 05 Binsigned pic s9(04) comp.
  • 05 Packedsigned pic s9(05) comp-3.
  • ABAP
  • Num(1) type n value 1.
  • Alpa(1) type c value A.
  • Alphanum(2) type c value 1A.
  • Binaryx(1) type x value 27.
    value is quote
  • Packedfield(3) type p value 12345.

18
Cobol Program
  • Cobol is a third Generation Language (3 G/L) that
    is Procedural driven.
  • Example See attached document.

19
ABAP Program
  • ABAP Is a fourth Generation Language (4 G/L)
  • that is EVENT driven.

20
ABAP (1st phase) RAW
  • The first phase of ABAP is the way that I was
    taught. It emphasizes on how the EVENT driven
    compiler works, from the time we enter data on
    the screen to the end of job.
  • I learned the different EVENTS such as
    Initialization, selection-screen,
    start-of-selection, end-of-selection, and
    top-of-page.
  • The 1st phase was created with this in mind.

21
ABAP (1st phase) - Identify
  • REPORT
  • Zmjb_000_abap_raw
  • line-size 80
  • line-count 65(3)
  • message-id z01.

22
ABAP (1st phase) - Table
  • Tables
  • zzl002t. G/L Special Ledger

23
ABAP (1st phase) - Variables
  • DATA
  • begin of v_zzl002t_it occurs 0, "Start
    of table
  • rbukrs like zzl002t-rbukrs,
    "Company code
  • ryylob like zzl002t-ryylob,
    "Line of Business
  • rprctr like zzl002t-rprctr,
    "Profit Center
  • racct like zzl002t-racct,
    "Account number
  • tsl05 like zzl002t-tsl05,
    "Total for period
  • tsl06 like zzl002t-tsl06,
    "Total for period
  • end of v_zzl002t_it.
    "End of table
  • DATA
  • t01_tsl05 like zzl002t-tsl05, "1st
    total
  • t02_tsl05 like zzl002t-tsl05, "2nd
    total
  • t03_tsl05 like zzl002t-tsl05, "3rd
    total
  • t04_tsl05 like zzl002t-tsl05. "4th
    total
  • DATA
  • t01_tsl06 like zzl002t-tsl06, "1st
    total
  • t02_tsl06 like zzl002t-tsl06, "2nd
    total
  • t03_tsl06 like zzl002t-tsl06, "3rd
    total
  • t04_tsl06 like zzl002t-tsl06. "4th
    total

24
ABAP (1st phase) - Constants
  • CONSTANTS
  • C_usd(3) value USD. Currency
  • C_quote(1) type x value 27. Quote

25
ABAP (1st phase) Selection Screen
  • selection-screen begin of block zzl002t_record
  • with frame title text-001.
  • select-options
  • s_rbukrs for zzl002t-rbukrs memory id sbkr.
    "Company code
  • parameters
  • p_rzzlgd like zzl002t-rzzlgid memory id przz,
    "Ledger ID
  • p_ryyamy like zzl002t-ryyamy memory id pryy.
    "Acc/mat year
  • selection-screen end of block zzl002t_record.

26
ABAP (1st phase) - EVENT
  • start-of-selection. Start
    of Selection
  • Select
    Step 1 Select records to process
  • rbukrs Company
    code
  • ryylob "Line of
    Business
  • rprctr "Profit
    Center
  • racct
    "Account number
  • tsl05 "Total
    for period
  • tsl06 "Total
    for period
  • from zzl002t
  • into table v_zzl002t_it
  • where ryyamy p_ryyamy "Acc/mat year
  • and rzzlgid p_rzzlgd "Ledger
    ID
  • and rbukrs in s_rbukrs.
    "Company code
  • sort v_zzl002t_it by rbukrs ryylob rprctr racct.
    Step 2 Sort by CC, LOB PRCTR

27
ABAP (1st phase) End-of-Selection Detail
  • end-of-selection.
  • loop at v_zzl002t_it.
    Start of the loop
  • write /01 v_zzl002t_it-rbukrs,
  • 10 v_zzl002t_it-ryylob,
  • 20 v_zzl002t_it-rprctr,
  • 30 v_zzl002t_it-racct,
  • 40 v_zzl002t_it-tsl05 currency c_usd,
  • 63 v_zzl002t_it-tsl06 currency c_usd.
  • t01_tsl05 t01_tsl05 v_zzl002t_it-tsl05.
    add detail to 1st total
  • t01_tsl06 t01_tsl06 v_zzl002t_it-tsl06.

28
ABAP (1st phase) End-of-Selection 1st Total
  • AT END OF rprctr.
    Total at rprctr
  • ULINE.
  • WRITE /10 ' rprctr total',
    Print 1st total
  • 40 t01_tsl05 currency c_usd,
  • 63 t01_tsl06 currency c_usd.
  • ULINE.
  • t02_tsl05 t02_tsl05 t01_tsl05.
    add 1st total to 2nd total
  • t02_tsl06 t02_tsl06 t01_tsl06.
  • clear
  • t01_tsl05, t01_tsl06.
  • ENDAT.

29
ABAP (1st phase) End-of-Selection 2nd Total
  • AT END OF ryylob.
    Total at ryylob
  • WRITE /10 ' ryylob total',
    Print 2nd total
  • 40 t02_tsl05 currency c_usd,
  • 63 t02_tsl06 currency c_usd.
  • ULINE.
  • t03_tsl05 t03_tsl05 t02_tsl05. add
    2nd total to 3rd total
  • t03_tsl06 t03_tsl06 t02_tsl06.
  • clear
  • t02_tsl05, t02_tsl06.
  • ENDAT.

30
ABAP (1st phase) End-of-Selection 3rd Total
  • AT END OF rbukrs.
    Total at rbukrs
  • WRITE /10 ' rbukrs total',
    Print 3rd total
  • 40 t03_tsl05 currency c_usd,
  • 63 t03_tsl06 currency c_usd.
  • ULINE.
  • t04_tsl05 t04_tsl05 t03_tsl05.
    add 3rd total to 4th total
  • t04_tsl06 t04_tsl06 t03_tsl06.
  • clear
  • t03_tsl05, t03_tsl06.
  • new-page.
  • ENDAT.

31
ABAP (1st phase) Grand Total
  • AT LAST.
    Grand Total
  • ULINE.
  • WRITE /10 ' Grand Total',
    Print Grand Total
  • 40 t04_tsl05 currency c_usd,
  • 63 t04_tsl06 currency c_usd.
  • ULINE.
  • ENDAT.
  • endloop.
    End of the loop

32
ABAP (1st phase) Top-of-page
  • top-of-page. Heading
  • write 01 'rbukrs', Print heading
  • 10 'ryylob',
  • 20 'rprctr',
  • 30 'racct',
  • 57 'tsl05',
  • 75 'tsl06'.
  • uline.

33
ABAP (2nd phase) Structured
  • Panic sets when I saw the first ABAP program that
    I will have to maintain. There was a semblance
    of standard on the data definition, but there was
    no continuity to the flow of the program. The
    program was humongous. Looking at a certain
    sub-routine using a listing, I had problems
    locating the routine. Perusing through the
    listing, I found out that instead of using one
    (1) routine for identical routines, the routine
    was copied to other places in the program.
  • I decided that I will write my program similar to
    Cobol, structured and will be easy to maintain.
    I hope that by applying standards in defining the
    data and the main logic, will make it easier for
    anyone maintaining the program.

34
ABAP (2nd phase) - Constants
  • constants Constants
  • c_usd(3) value 'USD', Currency
  • c_d01 type i value 1, "rbukrs
  • c_d02 type i value 10, "ryylob
  • c_d03 type i value 20, "rprctr
  • c_d04 type i value 30, "racct
  • c_d05 type i value 40, "tsl05
  • c_d06 type i value 63, "tsl06
  • c_h01 type i value 1, "rbukrs
  • c_h02 type i value 10, "ryylob
  • c_h03 type i value 20, "rprctr
  • c_h04 type i value 30, "racct
  • c_h05 type i value 57, "tsl05
  • c_h06 type i value 75. "tsl06

35
ABAP (2ND phase) - Main Logic
  • initialization.
    "INITIALIZATION
  • perform a_ini_010_initialization.
    Initialize - date time
  • start-of-selection.
    START OF SELECTION
  • perform b_sos_010_retrieve_zzl002t_inp.
    "Retrieve data sort
  • end-of-selection.
    "END OF SELECTION
  • perform c_eos_010_input_report. "Input
    Report
  • top-of-page.
    TOP OF PAGE
  • perform t_top_010_top_of_page. Heading

36
ABAP (2ND phase) - Sub-routines
  • form a_ini_010_initialization.
  • nothing for now
  • endform.
    "a_ini_010_initialization
  • form b_sos_010_retrieve_zzl002t_inp.
    "Retrieve ZZL002T
  • Select
  • rbukrs
    "Company code
  • ryylob "Line
    of Business
  • rprctr
    "Profit Center
  • racct
    "Account number
  • tsl05
    "Total for period
  • tsl06
    "Total for period
  • from zzl002t
  • into table v_zzl002t_it
  • where ryyamy p_ryyamy "Acc/mat
    year
  • and rzzlgid p_rzzlgd
    "Ledger ID
  • and rbukrs in s_rbukrs.
    "Company code
  • endform.
    "b_sos_010_retrieve_zzl002t_inp

37
ABAP (2ND phase) Top-of-Page
  • form t_top_010_top_of_page.
  • write at c_h01 text-h01, "rbukrs
  • at c_h02 text-h02,
    "ryylob
  • at c_h03 text-h03,
    "rprctr
  • at c_h04 text-h04, "racct
  • at c_h05 text-h05, "tsl05
  • at c_h06 text-h06. "tsl06
  • uline.
  • endform.
    "t_top_010_top_of_page

38
ABAP (3rd phase) 4 G/L
  • Upon completing a somewhat structured ABAP
    program, I concentrated in making the program a
    truly 4th G/L program. I want ABAP to do the
    driving for me.
  • In this example, I used the ABAP verb SUM for
    every control break the program encounters. In
    the old way, I added the fields to different
    variables, a way of the 3rd G/L programs. With
    this verb SUM, I don't have to define a
    different variable for each total break. By
    doing this, I dont have to maintain the
    different variables and it will make it a lot
    easier to follow the program.

39
ABAP (3rd phase) Main Logic
  • form c_eos_010_input_report.
    "Input Report
  • loop at v_zzl002t_it.
    "Begin of first loop (1)
  • new-line.
  • write at c_d01 v_zzl002t_it-rbukrs,
  • at c_d02 v_zzl002t_it-ryylob,
  • at c_d03 v_zzl002t_it-rprctr,
  • at c_d04 v_zzl002t_it-racct,
  • at c_d05 v_zzl002t_it-tsl05
    currency c_usd,
  • at c_d06 v_zzl002t_it-tsl06
    currency c_usd.
  • new-line.
  • AT END OF rprctr.
    total at rprctr
  • ULINE.
  • SUM.
    Total numeric fields
  • WRITE at c_d02 text-t01,
    rprctr total
  • at c_d05 v_zzl002t_it-tsl05
    currency c_usd,
  • at c_d06 v_zzl002t_it-tsl06
    currency c_usd.
  • ULINE.
  • ENDAT.

40
ABAP (3rd phase) Grand Total
  • AT END OF rbukrs.
    total at rbukrs
  • SUM.
  • WRITE at c_d02 text-t03,
    " rbukrs total
  • at c_d05 v_zzl002t_it-tsl05 currency
    c_usd,
  • at c_d06 v_zzl002t_it-tsl06 currency
    c_usd.
  • ULINE.
  • new-page.
  • ENDAT.
  • AT last.
    GRAND TOTAL
  • ULINE.
  • SUM.
  • WRITE at c_d02 text-t04,
    " Grand Total
  • at c_d05 v_zzl002t_it-tsl05 currency
    c_usd,
  • at c_d06 v_zzl002t_it-tsl06 currency
    c_usd.
  • ULINE.
  • ENDAT.
  • endloop.
    "End of First
    loop (1)
  • endform.
    end of
    c_eos_010_input_report

41
Miscellaneous
  • System fields System-defined data object
    Naming convention is SY-ltnamegt where ltnamegt
    denotes the field.
  • Example sy-uname (user name), sy-subrc (return
    code), sy-datum (current date)
  • Keywords ABAP reserved words.
  • Example if, endif, message, read, write,
    stop, compute
  • Messages Table where pre-defined error
    messages are kept.
  • Example 067 User 1 not authorized
    for 2 3 4
  • text-004 this transaction
  • if sy-subrc ne 0.
  • message E067 with sy-uname
    text-004.
  • stop.
  • endif. user
    acp74 not authorized for this transaction.
  • Function Modules External sub-routines written
    in ABAP
  • Example date_get_week (will return the week
    that a date is in)
  • Transaction code Sequence of four (4)
    alphanumeric characters
    that identify a transaction in the R/3 System.
  • Example se38, se80, se12

42
NOSTRADAMUS HE AINT
  • DOS will be with us forever. Weve learned how
    passionate people are about DOS.
  • MicrosoftVice-President Brad Silverberg
Write a Comment
User Comments (0)
About PowerShow.com