Ignore:
Timestamp:
Dec 4, 2009, 8:26:01 PM (14 years ago)
Author:
George Lilly
Message:

WorldVistAEHR overlayed on FOIAVistA

Location:
FOIAVistA/tag/r
Files:
1 edited
1 copied

Legend:

Unmodified
Added
Removed
  • FOIAVistA/tag/r/INTEGRATED_BILLING-IB-PRQ--IBD--IBQ--PRQS/IBCE277.m

    r628 r636  
    11IBCE277 ;ALB/TMP - 277 EDI CLAIM STATUS MESSAGE PROCESSING ;15-JUL-98
    2  ;;2.0;INTEGRATED BILLING;**137,155,368**;21-MAR-94;Build 21
    3  ;;Per VHA Directive 2004-038, this routine should not be modified.
     2 ;;2.0;INTEGRATED BILLING;**137,155**;21-MAR-94
    43 Q
    54 ; MESSAGE HEADER DATA STRING =
     
    87HDR(ENTITY,ENTVAL,IBTYPE,IBD) ;Process header data
    98 ; INPUT:
    10  ;   ENTITY = "BATCH" or "CLAIM" for batch/claim level messages respectively
    11  ;   ENTVAL = claim #
     9 ;   ENTITY = "BATCH" if batch level message
     10 ;            "CLAIM" if claim level message
     11 ;   ENTVAL = batch # or claim #
    1212 ;   IBTYPE = the type of status msg this piece of the message represents
    1313 ;             (837REC1, 837REJ1)
     
    1616 ; OUTPUT:
    1717 ;   IBD array returned with processed data
     18 ;      "LINE" = The last line # populated in the message
    1819 ;      "DATE" = Date/Time of status (Fileman format)
    1920 ;      "MRA" =  1 if MRA, 0 if not         "X12" = 1 if X12, 0 if not
     
    2223 ;
    2324 ;   ^TMP("IBMSG",$J,"BATCH",batch #,0)=MESSAGE HEADER DATA STRING
    24  ;                                      if batch level message
     25 ;                                      if called from batch level
    2526 ;                                  ,"D",0,1)=header record raw data
    2627 ;                                  ,line #)=batch status message lines
    2728 ;
    2829 ;   ^TMP("IBMSG",$J,"CLAIM",claim #,0)=MESSAGE HEADER DATA STRING
    29  ;                                      if claim level message
     30 ;                                      if called from claim level
    3031 ;                                  ,"D",0,1)=header record raw data
    3132 ;                                  ,line #)=claim status message lines
    3233 ;
    33  N DATA,IBD0,L,PC,X,Y
    34  S IBD0=$G(^TMP("IBMSGH",$J,0)) Q:IBD0=""
    35  S Y=0,L=1
    36  ; Convert claim date/time
    37  S X=$$DATE($P(IBD0,U,3))_"@"_$E($P(IBD0,U,4)_"0000",1,4) I X S %DT="XTS" D ^%DT
    38  ; populate IBD array
    39  S IBD("DATE")=$S(Y>0:Y,1:""),IBD("MRA")=$P(IBD0,U,5),IBD("X12")=($P(IBD0,U,2)="X")
    40  S IBD("SOURCE")=$P(IBD0,U,12,13),IBD("BATCH")=$P(IBD0,U,14)
    41  I +$TR($P(IBD0,U,6,9),U) F PC=6:1:9 D
    42  .I $P(IBD0,U,PC)'="" S DATA=$P("# Claims Submitted^# Claims Rejected^Total Charges Submitted^Total Charges Rejected",U,PC-5)_": "_$S(PC<8:+$P(IBD0,U,PC),1:$FNUMBER($P(IBD0,U,PC)/100,"",2))_"  "
    43  .I $L($G(^TMP("IBMSG-H",$J,ENTITY,ENTVAL,L)))+$L(DATA)>70 S L=L+1 ; if data doesn't fit into current line, go to the next line
    44  .S ^TMP("IBMSG-H",$J,ENTITY,ENTVAL,L)=$G(^TMP("IBMSG-H",$J,ENTITY,ENTVAL,L))_DATA ; file this piece of data
    45  .Q
    46  ; file batch ref. number
    47  S:IBD("BATCH")'="" L=L+1,^TMP("IBMSG-H",$J,ENTITY,ENTVAL,L)="Batch Reference Number: "_IBD("BATCH")
    48  I $TR($P(IBD0,U,10,13),U)'="" D
    49  .S L=L+1
    50  .; generate and file Payer Name / Payer Id line
    51  .S DATA="Payer Name: "_$S($P(IBD0,U,10)'="":$P(IBD0,U,10),1:"N/A")_"  Payer ID: "_$S($P(IBD0,U,11)'="":$P(IBD0,U,11),1:"N/A")
    52  .S ^TMP("IBMSG-H",$J,ENTITY,ENTVAL,L)=DATA
    53  .I $P(IBD0,U,12)'=""!($P(IBD0,U,13)'="") D
    54  ..; generate and file Message Source line
    55  ..S DATA="Source: "_$S($P(IBD0,U,12)="Y":"Sent by payer",$P(IBD0,U,13)'="":"Sent by non-payer ("_$P(IBD0,U,13)_")",1:"UNKNOWN")
    56  ..S L=L+1,^TMP("IBMSG-H",$J,ENTITY,ENTVAL,L)=DATA
    57  ..Q
    58  .Q
    59  S ^TMP("IBMSG",$J,ENTITY,ENTVAL,0)=IBTYPE_U_$G(IBD("MSG#"))_U_$G(IBD("SUBJ"))_U_$$GETBILL(ENTVAL)_U_U_IBD("DATE")_U_IBD("SOURCE")
    60  ; file raw data
     34 N CT,CT1,IBBILL,IBD0,L,LINE,PC,Z,X,Y
     35 S IBD0=$G(^TMP("IBMSGH",$J,0)),IBD("LINE")=0
     36 Q:IBD0=""
     37 S Y=0,X=$$DATE($P(IBD0,U,3))_"@"_$E($P(IBD0,U,4)_"0000",1,4)
     38 I X S %DT="XTS" D ^%DT
     39 S IBD("DATE")=$S(Y>0:Y,1:"")
     40 S IBD("MRA")=$P(IBD0,U,5),IBD("X12")=($P(IBD0,U,2)="X")
     41 S IBD("SOURCE")=$P(IBD0,U,12,13)
     42 S CT=0
     43 ;
     44 I ENTITY="BATCH",ENTVAL'="" D  ;Only pertinent for batch level extract
     45 . S IBD("BATCH")=$O(^IBA(364.1,"B",ENTVAL,0))
     46 . F PC=6:1:9 D
     47 .. I $P(IBD0,U,PC)'="" S DATA=$P("# Claims Submitted^# Claims Rejected^Total Charges Submitted^Total Charges Rejected",U,PC-5)_": "_$S(PC<8:+$P(IBD0,U,PC),1:$FNUMBER($P(IBD0,U,PC)/100,"",2))_"  "
     48 .. I CT,$L($G(LINE(CT)))+$L(DATA)>80 S CT=CT+1
     49 .. S:'CT CT=1 S LINE(CT)=$G(LINE(CT))_DATA
     50 ;
     51 I ENTVAL'="",$TR($P(IBD0,U,10,13),U)'="" S CT1=CT,CT=CT+1 F PC=10,11,12 D  ;Both batch, claim levels extract
     52 . Q:$P(IBD0,U,PC)=""
     53 . I PC<12 S LINE(CT)=$G(LINE(CT))_$P("Payer Name^Payer ID",U,PC-9)_": "_$P(IBD0,U,PC)_"  ",CT1=CT Q
     54 . I $P(IBD0,U,12)'=""!($P(IBD0,U,13)'="") S:$P(IBD0,U,10)'=""!($P(IBD0,U,11)'="") CT=CT+1 S LINE(CT)="Source: "_$S($P(IBD0,U,12)="Y":"Sent by payer",$P(IBD0,U,13)'="":"Sent by non-payer ("_$P(IBD0,U,13)_")",1:"UNKNOWN")_"  "
     55 ;
     56 I CT D
     57 . S (L,Z)=0
     58 . F  S Z=$O(LINE(Z)) Q:'Z  S L=L+1,^TMP("IBMSG-H",$J,ENTITY,ENTVAL,L)=LINE(Z)
     59 . ;S IBD("LINE")=$G(IBD("LINE"))+CT
     60 ;
     61 I ENTITY="CLAIM" D
     62 . N Z0
     63 . S Z0=+$O(^DGCR(399,"B",ENTVAL,0))
     64 . I $G(IBD("BATCH")) S IBBILL=$O(^IBA(364,"ABABI",+$G(IBD("BATCH")),Z0,""),-1) Q
     65 . S IBBILL=$$LAST364^IBCEF4(Z0)
     66 S ^TMP("IBMSG",$J,ENTITY,ENTVAL,0)=IBTYPE_U_$G(IBD("MSG#"))_U_$G(IBD("SUBJ"))_U_$S(ENTITY="CLAIM":IBBILL,1:"")_U_$S(ENTITY="BATCH":ENTVAL,1:"")_U_IBD("DATE")_U_IBD("SOURCE")
     67 ;
    6168 S ^TMP("IBMSG",$J,ENTITY,ENTVAL,"D",0,1)="##RAW DATA: "_IBD0
    6269 Q
    6370 ;
    64 9(IBD) ; Process Message Header record
    65  ; INPUT:
    66  ;   IBD must be passed by reference = entire message line
    67  ; OUTPUT:
    68  ;   IBD array returned with processed data
    69  ;      "CLAIM" = claim #
    70  ;      "LINE" = last line # populated in the message
    71  ;
    72  ;   ^TMP("IBMSG",$J,"CLAIM",claim #,line#)= message data lines
    73  ;                                  ,"D",9,msg seq #)= raw data
    74  N ENTITY,ERR,FLD,IBCLM,IBIFN,L
    75  D STRTREC Q:IBCLM=""  ; if no claim/batch number, bail out
    76  ; make sure that we have data to file
    77  S ERR=$P(IBD,U,4) Q:ERR=""
    78  ; file error along with corresponding field number (if available)
    79  S L=L+1,FLD=$P(IBD,U,5),^TMP("IBMSG",$J,ENTITY,IBCLM,L)="Error"_$S(FLD'="":" in field "_FLD,1:"")_":"
    80  S L=L+1,^TMP("IBMSG",$J,ENTITY,IBCLM,L)=ERR
    81  D ENDREC(9)
    82  Q
    83  ;
    84 10(IBD) ; Process message data
    85  ; INPUT:
    86  ;   IBD must be passed by reference = entire message line
    87  ; OUTPUT:
    88  ;   IBD array returned with processed data
    89  ;      "CLAIM" = claim #
    90  ;      "LINE" = last line # populated in the message
    91  ;
    92  ;   ^TMP("IBMSG",$J,"CLAIM",claim #,line#)= message data lines
    93  ;                                  ,"D",10,msg seq #)= raw data
     715(IBD) ; Process batch status data
     72 ; INPUT:
     73 ;   IBD must be passed by reference = entire message line
     74 ; OUTPUT:
     75 ;   IBD array returned with processed data
     76 ;      "LINE" = The last line # populated in the message
     77 ;
     78 ;   ^TMP("IBMSG",$J,"BATCH",batch #,line#)=batch status message lines
     79 ;                                  ,"D",5,msg seq #)=
     80 ;                                       batch status message raw data
     81 ;
     82 N CT,DATA,IBBTCH,IBTYPE,L,LINE,Z
     83 K ^TMP("IBCONF",$J)
     84 S IBBTCH=+$P(IBD,U,2)
     85 S IBTYPE=$S($P(IBD,U,3)="R":"837REJ1",1:"837REC1")
     86 I '$D(^TMP("IBMSG",$J,"BATCH",IBBTCH)) D HDR("BATCH",IBBTCH,IBTYPE,.IBD) ;Process header data if not already done for batch
     87 S CT=0,LINE(1)=""
     88 S DATA=$P(IBD,U,4)
     89 I DATA'="",$TR($P(IBD,U,5,7),U)'="" D
     90 . Q:$G(^TMP("IBMSG",$J,"BATCH",IBBTCH))=DATA
     91 . S:'CT CT=CT+1 S LINE(CT)=$G(LINE(CT))_$S(DATA="W":"Warning",DATA="E":"Error",1:"Informational")_"  "
     92 S ^TMP("IBMSG",$J,"BATCH",IBBTCH)=DATA
     93 I $P(IBD,U,5)'="" S:'CT CT=CT+1 S LINE(CT)=$G(LINE(CT))_"Code: "_$P(IBD,U,5)
     94 I $P(IBD,U,6)'="" S:'CT CT=CT+1 S LINE(CT)=$G(LINE(CT))_"  "_$P(IBD,U,6),CT=CT+1
     95 I $P(IBD,U,7)'="" S:'CT CT=CT+1 S LINE(CT)=$G(LINE(CT))_"  "_$P(IBD,U,7)
     96 I CT D
     97 . S L=$G(IBD("LINE")),Z=0
     98 . F  S Z=$O(LINE(Z)) Q:'Z  S L=L+1,^TMP("IBMSG",$J,"BATCH",IBBTCH,L)=LINE(Z)
     99 . S ^TMP("IBMSG",$J,"BATCH",IBBTCH,"D",5,$O(^TMP("IBMSG",$J,"BATCH",IBBTCH,"D",5,""),-1)+1)="##RAW DATA: "_IBD
     100 . S IBD("LINE")=$G(IBD("LINE"))+CT
     101 Q
     102 ;
     10310(IBD) ; Process claim status data
     104 ; INPUT:
     105 ;   IBD must be passed by reference = entire message line
     106 ; OUTPUT:
     107 ;   IBD array returned with processed data
     108 ;      "CLAIM" = The claim #
     109 ;      "LINE" = The last line # populated in the message
     110 ;
     111 ;   ^TMP("IBMSG",$J,"CLAIM",claim #,line#)=claim status message lines
     112 ;                                  ,"D",10,msg seq #)=
     113 ;                                       claim status raw data
    94114 ;   ^TMP("IBCONF",$J,claim #")="" for invalid claims within the batch
    95115 ;
    96  N CODE,DATA,ENTITY,IBCLM,IBIFN,IBTYPE,L,Z
    97  D STRTREC Q:IBCLM=""  ; if no claim number, bail out
    98  S:$P(IBD,U,3)="R" ^TMP("IBCONF",$J,IBIFN)=""
     116 N CT,DATA,IBCLM,IBTYPE,L,LINE,Z
     117 S IBCLM=$$GETCLM($P(IBD,U,2))
     118 Q:IBCLM=""
     119 S:$P(IBD,U,3)="R" ^TMP("IBCONF",$J,+$O(^DGCR(399,"B",IBCLM,0)))=""
    99120 S IBTYPE=$S($P(IBD,U,3)="R":"837REJ1",1:"837REC1")
    100  ;Process header data if not already done
    101  I '$D(^TMP("IBMSG",$J,ENTITY,IBCLM,0)) D HDR(ENTITY,IBCLM,IBTYPE,.IBD)
    102  I IBTYPE="837REJ1",$P($G(^TMP("IBMSG",$J,ENTITY,IBCLM,0)),U,1)'="837REJ1" D HDR(ENTITY,IBCLM,IBTYPE,.IBD)
    103  S CODE=$P(IBD,U,4) I CODE'="",$TR($P(IBD,U,5,6),U)'="" D
    104  .S Z=CODE_$P(IBD,U,5) I Z'=$G(IBD("SCODE")) D
    105  ..; determine type of status code and file it
    106  ..S L=L+1,DATA=$S(CODE="W":"Warning",CODE="E":"Error",1:"Informational")_" "
    107  ..I $P(IBD,U,5)'="" S ^TMP("IBMSG",$J,ENTITY,IBCLM,L)=DATA_"Code: "_$P(IBD,U,5)
    108  ..I $P(IBD,U,6)'="" S:$P(IBD,U,5)'="" L=L+1 S ^TMP("IBMSG",$J,ENTITY,IBCLM,L)=DATA_"Message:",L=L+1
    109  ..S IBD("SCODE")=Z
    110  ..Q
    111  .; file status message
    112  .I $P(IBD,U,6)'="" S ^TMP("IBMSG",$J,ENTITY,IBCLM,L)=$P(IBD,U,6),L=L+1,^TMP("IBMSG",$J,ENTITY,IBCLM,L)=" "
    113  .Q
    114  D ENDREC(10)
    115  Q
    116  ;
    117 13(IBD) ; Process claim data
    118  ; Claim must have been referenced by a previous '10' level
    119  ; INPUT:
    120  ;   IBD must be passed by reference = entire message line
    121  ;
    122  ; OUTPUT:
    123  ;      IBD("LINE") = The last line # populated in the message
    124  ;
    125  ;     ^TMP("IBMSG",$J,"CLAIM",claim #,line#)=claim data lines
    126  ;                                    ,"D",13,msg seq #)=raw data
    127  ;
    128  N CTYPE,ENTITY,IBCLM,IBIFN,L,Z1,Z2
    129  D STRTREC
    130  ; quit if no claim number or no previous 'line 10' record
    131  Q:$S(IBCLM="":1,1:'$D(^TMP("IBMSG",$J,"CLAIM",IBCLM)))
    132  ; file clearinghouse trace number
    133  I $P(IBD,U,3)'="" S L=L+1,^TMP("IBMSG",$J,ENTITY,IBCLM,L)="Clearinghouse Trace Number: "_$P(IBD,U,3)
    134  ; file payer status date
    135  I $P(IBD,U,4)'="" S L=L+1,^TMP("IBMSG",$J,ENTITY,IBCLM,L)="         Payer Status Date: "_$$DATE($P(IBD,U,4))
    136  ; file payer claim number
    137  I $P(IBD,U,5)'="" S L=L+1,^TMP("IBMSG",$J,ENTITY,IBCLM,L)="        Payer Claim Number: "_$P(IBD,U,5)
    138  ; file split claim indicator
    139  I +$P(IBD,U,6)'=0 S L=L+1,^TMP("IBMSG",$J,ENTITY,IBCLM,L)="               Split Claim: "_$S(+$P(IBD,U,6)=1:"No",1:"Yes ("_+$P(IBD,U,6)_" parts)")
    140  ; file claim type if it either doesn't match value in VistA or if it's a dental claim
    141  S Z1=$P(IBD,U,7),Z2=$$FT^IBCEF(IBIFN),CTYPE=$S(Z1="P"&(Z2'=2):"Professional",Z1="I"&(Z2'=3):"Institutional",Z1="D":"Dental",1:"")
    142  S:CTYPE'="" L=L+1,^TMP("IBMSG",$J,ENTITY,IBCLM,L)="                Claim Type: "_CTYPE
    143  D ENDREC(13)
     121 I '$D(^TMP("IBMSG",$J,"CLAIM",IBCLM)) D HDR("CLAIM",IBCLM,IBTYPE,.IBD) ;Process header data if not already done for claim
     122 I IBTYPE="837REJ1",$P($G(^TMP("IBMSG",$J,"CLAIM",IBCLM,0)),U,1)'="837REJ1" D HDR("CLAIM",IBCLM,IBTYPE,.IBD)
     123 S CT=0,DATA=$P(IBD,U,4)
     124 I DATA'="",$TR($P(IBD,U,5,7),U)'="" D
     125 . Q:$G(^TMP("IBMSG",$J,"CLAIM",IBCLM))=DATA
     126 . S ^TMP("IBMSG",$J,"CLAIM",IBCLM)=DATA
     127 . S CT=CT+1,LINE(CT)=$G(LINE(CT))_$S(DATA="W":"Warning",DATA="E":"Error",1:"Informational")_"  "
     128 I $P(IBD,U,5)'="" S CT=$S('CT:1,1:CT),LINE(CT)=$G(LINE(CT))_"Code: "_$P(IBD,U,5)
     129 I $P(IBD,U,6)'="" S CT=$S('CT:1,1:CT),LINE(CT)=$G(LINE(CT))_"  "_$P(IBD,U,6)
     130 I $P(IBD,U,7)'="" S CT=CT+1,LINE(CT)="  "_$P(IBD,U,7)
     131 I CT D
     132 . S L=$G(IBD("LINE")),Z=0
     133 . F  S Z=$O(LINE(Z)) Q:'Z  S L=L+1,^TMP("IBMSG",$J,"CLAIM",IBCLM,L)=LINE(Z)
     134 . S ^TMP("IBMSG",$J,"CLAIM",IBCLM,"D",10,$O(^TMP("IBMSG",$J,"CLAIM",IBCLM,"D",10,""),-1)+1)="##RAW DATA: "_IBD
     135 . S IBD("LINE")=$G(IBD("LINE"))+CT
    144136 Q
    145137 ;
     
    156148 ;                                         subscr/patient raw data
    157149 ;
    158  N ENTITY,DATA,IBCLM,IBIFN,IBNM,IBNUM,IBDFN,L
    159  D STRTREC
    160  ; quit if no claim number or no previous 'line 10' record
     150 N CT,Z,L,LINE,DATA,IBCLM,IBNM,IBNUM,IBDFN
     151 S IBCLM=$$GETCLM($P(IBD,U,2)),CT=0,L=$G(IBD("LINE"))
    161152 Q:$S(IBCLM="":1,1:'$D(^TMP("IBMSG",$J,"CLAIM",IBCLM)))
    162  S IBDFN=+$P(^DGCR(399,IBIFN,0),U,2)
     153 S IBDFN=+$G(^DGCR(+$O(^DGCR(399,"B",IBCLM,0)),0))
    163154 S IBNM=$S($P(IBD,U,3)'="":$P(IBD,U,3)_","_$P(IBD,U,4)_$S($P(IBD,U,5)'="":" "_$P(IBD,U,5),1:""),1:$P($G(^DPT(IBDFN,0)),U))
    164155 S IBNUM=$S($P(IBD,U,6)'="":$P(IBD,U,6),1:$P($G(^DPT(IBDFN,0)),U,9))
    165  S L=L+1,^TMP("IBMSG",$J,ENTITY,IBCLM,L)="Patient: "_IBNM_"   "_IBNUM
     156 S CT=CT+1,LINE(CT)="Patient: "_IBNM_"   "_IBNUM
    166157 I $P(IBD,U,11) D
    167  .S DATA=$$DATE($P(IBD,U,11)),L=L+1
    168  .S ^TMP("IBMSG",$J,ENTITY,IBCLM,L)="Service Dates: "_DATA_" - "_$S($P(IBD,U,12):$$DATE($P(IBD,U,12)),1:DATA)
    169  .Q
    170  D ENDREC(15)
    171  Q
    172  ;
    173 STRTREC ; start processing of the record
    174  ;           
    175  ; OUTPUT:
    176  ;   sets the following variables
    177  ;   IBCLM = claim #
    178  ;   ENTITY = "CLAIM" (all 277STAT messages are on claim level)
    179  ;   L = last populated line number
    180  ;
    181  S IBCLM=$$GETCLM($P(IBD,U,2)),ENTITY="CLAIM",L=+$G(IBD("LINE"))
    182  S IBIFN=+$O(^DGCR(399,"B",IBCLM,0))
    183  Q
    184  ;
    185 ENDREC(TYPE) ; finish processing of the record
    186  ; INPUT:
    187  ;   TYPE = record type (line type)
    188  ;   
    189  ; OUTPUT:
    190  ;   IBD("LINE") = is updated with last populated line number
    191  ;
    192  ;make sure all variables are set properly
    193  Q:$G(ENTITY)=""
    194  Q:$G(IBCLM)=""
    195  Q:$G(TYPE)=""
    196  ; file raw data
    197  S ^TMP("IBMSG",$J,ENTITY,IBCLM,"D",TYPE,$O(^TMP("IBMSG",$J,ENTITY,IBCLM,"D",TYPE,""),-1)+1)="##RAW DATA: "_IBD
    198  ; update line count
    199  S IBD("LINE")=$G(IBD("LINE"))+L
    200  Q
    201  ;
    202 GETBILL(CLAIM) ; Extract transmission #
    203  N TRANS
    204  S TRANS=$$LAST364^IBCEF4(IBIFN)
    205  ; if status of the last transmission is "X" or "P", keep searching backwards through file 364 until record
    206  ; with different status is found
    207  I TRANS F  Q:"XP"'[$P(^IBA(364,TRANS,0),U,3)  S TRANS=$O(^IBA(364,"B",IBIFN,TRANS),-1) Q:TRANS=""  ;
    208  Q +TRANS
     158 . S DATA=$$DATE($P(IBD,U,11)),CT=CT+1
     159 . S LINE(CT)="Service Dates: "_DATA_" - "_$S($P(IBD,U,12):$$DATE($P(IBD,U,12)),1:DATA)_"  "
     160 . ; Add additional lines of display data here for record 15
     161 S Z=0 F  S Z=$O(LINE(Z)) Q:'Z  S L=L+1,^TMP("IBMSG",$J,"CLAIM",IBCLM,L)=LINE(Z)
     162 S ^TMP("IBMSG",$J,"CLAIM",IBCLM,"D",15,$O(^TMP("IBMSG",$J,"CLAIM",IBCLM,"D",15,""),-1)+1)="##RAW DATA: "_IBD
     163 S IBD("LINE")=$G(IBD("LINE"))+CT
     164 Q
     165 ;
     16620(IBD) ; Process service line status data
     167 ; Claim must have been referenced by a previous '10' level
     168 ; INPUT:
     169 ;   IBD must be passed by reference = entire message line
     170 ; OUTPUT:
     171 ;   IBD array returned with processed data
     172 ;      "LINE" = The last line # populated in the message
     173 ;      "TYPE" = The msg type of status record (Confirmation/rejection)
     174 ;             Note: returned if not already set at batch or claim level
     175 ;
     176 ;   ^TMP("IBMSG",$J,"CLAIM",claim #)=""
     177 ;                                  ,line#)=service line status msg lines
     178 ;                                  ,"D",20,msg seq #)=
     179 ;                                       service line status raw data
     180 ;
     181 N CT,DATA,L,LINE,Z,IBCLM,IBLNUM
     182 S IBCLM=$$GETCLM($P(IBD,U,2)),IBLNUM=$P(IBD,U,8)
     183 Q:'$D(^TMP("IBMSG",$J,"CLAIM",IBCLM))
     184 S CT=0
     185 I IBLNUM'="" S CT=CT+1,LINE(CT)="Claim Line: "_IBLNUM,^TMP("IBMSG",$J,"LINE",IBCLM,IBLNUM)=""
     186 S DATA=$P(IBD,U,4)
     187 I DATA'="",$TR($P(IBD,U,5,7),U)'="" S:'CT CT=CT+1 S LINE(CT)=$S(DATA="W":"Warning",DATA="E":"Error",1:"Informational")_"  "_$G(LINE(CT))
     188 S:$G(IBD("TYPE"))="" IBD("TYPE")=$S(DATA="E":"837REJ1",1:"837REC1")
     189 I $P(IBD,U,5)'="" S:'CT CT=CT+1 S LINE(CT)=LINE(CT)_$P(IBD,U,5)
     190 I $P(IBD,U,6)'="" S CT=CT+1,LINE(CT)="  "_$P(IBD,U,6)
     191 I $P(IBD,U,7)'="" S CT=CT+1,LINE(CT)="  "_$P(IBD,U,7)
     192 I CT D
     193 . S L=$G(IBD("LINE")),Z=0
     194 . F  S Z=$O(LINE(Z)) Q:'Z  S L=L+1,^TMP("IBMSG",$J,"CLAIM",IBCLM,L)=LINE(Z)
     195 . S ^TMP("IBMSG",$J,"CLAIM",IBCLM,"D",20,$O(^TMP("IBMSG",$J,"CLAIM",IBCLM,"D",20,""),-1)+1)="##RAW DATA: "_IBD
     196 . S IBD("LINE")=$G(IBD("LINE"))+CT
     197 Q
     198 ;
     19921(IBD) ; Process service line ID data
     200 ; Moved for size too big
     201 D 21^IBCE277A(IBD)
     202 Q
    209203 ;
    210204DATE(DT) ; Convert YYMMDD Date into MM/DD/YY or YYYYMMDD into MM/DD/YYYY
     
    216210GETCLM(X) ; Extract the claim # without site id from the data in X
    217211 N IBCLM
    218  S IBCLM=$P(X,"-",2) I IBCLM="",X'="" S IBCLM=$E(X,$S($L(X)>7:4,1:1),$L(X))
     212 S IBCLM=$P(X,"-",2)
     213 I IBCLM="",X'="" S IBCLM=$E(X,$S($L(X)>7:4,1:1),$L(X))
     214 ;S IBCLM=$E(X,$L(IBCLM)-6,$L(IBCLM)) ; Only take last 7 char
    219215 Q IBCLM
    220216 ;
Note: See TracChangeset for help on using the changeset viewer.