Page 1 of 2

Absolute value operation

PostPosted: Tue Nov 08, 2011 6:46 pm
by pulcinella
Good morning.

first of all apologize if I do not write English properly

I have a customer file of 153 positions whose structure is as follows:

Client type = PIC X (1)
customer number = PIC S9 (9) COMP-3
annual balance = PIC S9 (13) V99 COMP-3
monthly balance = PIC S9 (13) V99 COMP-3
customer information = PIC X (94)
Code 1 = PIC X (3)
Code 2 = PIC X (4)
other fields = PIC X (30)

The file is sorted by "client type", "customer number" and the field "code 2". The customer may have hired more than one product (field "code 1"). Depending on the product purchased, the balance can come in positive or negative.

I need to get a file of 18 positions with the following structure

type person = pic x (1)
customer number = PIC S9 (9) COMP-3
annual balance = PIC S9 (13) V99 COMP-3


To calculate the annual balance we build client-level "code 1". Keep in mind that when the product is J01 or J02 type shall be computed in positive (absolute value)

Really only need to know if there is a command (besides making the MULT -1) that automatically calculates the absolute value

Thanks

Re: Absolute value operation

PostPosted: Tue Nov 08, 2011 7:21 pm
by BillyBoyo
I don't think so, but have you checked in the DFSORT documentation?

Re: Absolute value operation

PostPosted: Tue Nov 08, 2011 10:44 pm
by pulcinella
Hi BillyBoyo
I have read the documentation. I know putting the MUL, -1 to get put absolute value but I can not respect the length of the source field

Re: Absolute value operation

PostPosted: Tue Nov 08, 2011 10:47 pm
by dick scherrer
Hello,

but I can not respect the length of the source field
I do not understand this - please clarify. Possibly an example would help?

Re: Absolute value operation

PostPosted: Wed Nov 09, 2011 12:16 am
by Frank Yaeger
DFSORT does not have a built-in absolute value function. The trick to get an absolute value is to multiply each negative value by -1. I don't understand why you can't do that.

If you need more help figuring out how to do what you want, give a better explanation of what you want to do. Show an example of input records and expected output records. Explain the rules for getting from input to output. Give the RECFM and LRECL of your input file.

Re: Absolute value operation

PostPosted: Thu Nov 10, 2011 5:50 pm
by pulcinella
Hi Frank, Dick

Thanks for your response. I try to explain better.
Frank, not that I want to use the MUL -1; just wanted to know if there was another way to do it.
Dick, when I said "but I can not Respect the length of the source field" meant that I do not want to change the format, that is, if the balance I have is an S9 (13) V99 COMP-3 I get the same format .

I have it built in the next two steps (I've found it works)

//SORT001  EXEC PGM=SORT
//SYSOUT   DD SYSOUT=A
//SORTIN   DD DSN=&&,DISP=SHR
//OUT1     DD DSN=OUT1,
//            DISP=(,CATLG,DELETE),
//            SPACE=(TRK,(200,100),RLSE)
//OUT2     DD DSN=OUT2,
//            DISP=(,CATLG,DELETE),
//            SPACE=(TRK,(1000,500),RLSE)
//SYSIN    DD *
  OPTION COPY
  OUTFIL FNAMES=OUT1,
         INCLUDE=((117,3,CH,EQ,C'J01',OR,117,3,CH,EQ,C'J02'),AND,
                     7,8,PD,LT,0),
         OUTREC=(1,6,7,8,PD,MUL,-1,TO=PD,LENGTH=8,15,139)
  OUTFIL FNAMES=OUT2,
         INCLUDE=(((117,3,CH,EQ,C'J01',OR,117,3,CH,EQ,C'J02'),AND,
                      7,8,PD,GE,0),OR,
                   (117,3,CH,NE,C'J01',AND,117,3,CH,NE,C'J02')),
         OUTREC=(1,153)
/*
//*
//SORT002  EXEC PGM=SORT,REGION=6M,COND=(0,LT)
//SYSOUT   DD SYSOUT=A
//SORTIN   DD DSN=OUT1,DISP=SHR
//         DD DSN=OUT2,DISP=SHR
//SORTOUT  DD DSN=&&...,
//            DISP=(,CATLG,DELETE),
//            SPACE=(TRK,(100,100),RLSE)
//SYSIN    DD *
  OPTION DYNALLOC=(,25)
  SORT FIELDS=(1,6,CH,A,120,4,CH,A),EQUALS
  SUM FIELDS=(15,8,PD)
  OUTREC FIELDS=(1,6,120,4,15,8)
/*


I don't know if I can do in one step using instructions such as IfThen, INREC, OUTREC, BUILD ...

I do not think it necessary to put such as, with what I have coded, you can get an idea of the specifications. I need to know if what I have, I can do in one step. Anyway if you really need, I put a clear example

Re: Absolute value operation

PostPosted: Thu Nov 10, 2011 8:13 pm
by Akatsukami
Although I'm not a DFSORT maven, is there a function for forcing the sign nybble of the annual balance to X'F'?

Re: Absolute value operation

PostPosted: Thu Nov 10, 2011 10:25 pm
by BillyBoyo
Sort of, to coin a phrase. I doubt it'll be needed once the above is tidied-up a little.

The description shows a signed Cobol field, so C would be better than F. No logical OR/AND that I have seen so far. So, a test for less than zero, then, defining the sign-byte as BI length one, subtract one from it. D becomes C. All Cs, unless file is already messed-up with Fs - in which case a mix.

Perhaps to blat eveything, divide by 16, multiply by 16 and add 12?

To get to all Fs (repeat, not good for signed Cobol field) TO=ZDF. I suppose that, then back to ZD might get the Cs, I'd have to check in the manual.

Re: Absolute value operation

PostPosted: Thu Nov 10, 2011 11:09 pm
by skolusu
pulcinella wrote:
Your first step sysin :

//SYSIN DD *
OPTION COPY
OUTFIL FNAMES=OUT1,
INCLUDE=((117,3,CH,EQ,C'J01',OR,117,3,CH,EQ,C'J02'),AND,
7,8,PD,LT,0),
OUTREC=(1,6,7,8,PD,MUL,-1,TO=PD,LENGTH=8,15,139)
OUTFIL FNAMES=OUT2,
INCLUDE=(((117,3,CH,EQ,C'J01',OR,117,3,CH,EQ,C'J02'),AND,
7,8,PD,GE,0),OR,
(117,3,CH,NE,C'J01',AND,117,3,CH,NE,C'J02')),
OUTREC=(1,153)
/*
//*

your second step sysin:

//SYSIN DD *
OPTION DYNALLOC=(,25)
SORT FIELDS=(1,6,CH,A,120,4,CH,A),EQUALS
SUM FIELDS=(15,8,PD)
OUTREC FIELDS=(1,6,120,4,15,8)
/*



pulcinella,

Something doesn't make sense here.

In your first step you are changing the PD field at Pos 7 for 8 bytes if it is less than 0. However you are NOT even using that field anywhere later in your second step. In the second step you are sorting on the first 6 bytes and 4 bytes from pos 120. You are summing on a field at pos 15 for 8 bytes. You don't even write the modified field to your output. So why even bother changing the field to an absolute value when you don't even need it?

Re: Absolute value operation

PostPosted: Fri Nov 11, 2011 2:13 am
by Frank Yaeger
Pulcinella,

As Kolusu points out, your example makes no sense.

If you just want to change your 15,8,PD field to positive when its negative and sum the 15,8,PD field, you can do it in one pass with DFSORT control statements like this:

    INREC IFTHEN=(WHEN=((117,3,CH,EQ,C'J01',OR,117,3,CH,EQ,C'J02'),AND,
                     15,8,PD,LT,0),OVERLAY=(15:15,8,PD,MUL,-1,TO=PD))
    SORT FIELDS=(1,6,CH,A,120,4,CH,A),EQUALS
    SUM FIELDS=(15,8,PD)
    OUTREC FIELDS=(1,6,120,4,15,8)


If that's not what you want to do, then you need to provide a much better description of what it is you are trying to do, with a good example of input and expected output.