1 | DVB458P1 ;ALB/RBS - POST-INSTALL FOR PATCH DVB*4*58 (CONT.) ; 4/24/07 3:53pm
|
---|
2 | ;;4.0;HINQ;**58**;03/25/92;Build 29
|
---|
3 | ;
|
---|
4 | ;This routine is the main post-install driver that will update the
|
---|
5 | ;DISABILITY CONDITION (#31) file with the new mapping of Rated
|
---|
6 | ;Disabilities (VA) VBA DX CODES to specific ICD DIAGNOSIS codes.
|
---|
7 | ;
|
---|
8 | Q ;no direct entry
|
---|
9 | ;
|
---|
10 | POST(DVBTMP,DVBTOT) ;post-install driver for updating the (#31) file
|
---|
11 | ;This procedure will call a series of routines that contain the data
|
---|
12 | ;element values that will be used to create the new VBA-ICD9 mapping.
|
---|
13 | ;
|
---|
14 | ; Input:
|
---|
15 | ; DVBTMP - Closed Root global reference for error reporting
|
---|
16 | ; DVBTOT - Total number of ICD9 codes filed
|
---|
17 | ;
|
---|
18 | ; Output:
|
---|
19 | ; DVBTMP - Temp file of error messages (if any)
|
---|
20 | ; DVBTOT - Total number of ICD9 codes filed
|
---|
21 | ;
|
---|
22 | N DVBRTN,DVBCNT
|
---|
23 | S DVBTMP=$G(DVBTMP)
|
---|
24 | S DVBTOT=$G(DVBTOT) I DVBTOT']"" S DVBTOT=0
|
---|
25 | I DVBTMP']"" S DVBTMP=$NA(^TMP("DVB458P",$J)) K @DVBTMP
|
---|
26 | ;
|
---|
27 | ;loop each routine
|
---|
28 | F DVBCNT=1:1:6 S DVBRTN="^DVB458P"_DVBCNT D
|
---|
29 | . Q:($T(@DVBRTN)="")
|
---|
30 | . D BLDXRF(DVBRTN,DVBTMP,.DVBTOT)
|
---|
31 | Q
|
---|
32 | ;
|
---|
33 | ;
|
---|
34 | BLDXRF(DVBRTN,DVBTMP,DVBTOT) ;call each routine to file VBA/ICD9 codes
|
---|
35 | ;
|
---|
36 | ; Input:
|
---|
37 | ; DVBRTN - Post Install routine to process VBA/ICD9 codes
|
---|
38 | ; DVBTMP - Closed Root global reference for error reporting
|
---|
39 | ; DVBTOT - Total number of ICD9 codes filed
|
---|
40 | ;
|
---|
41 | ; Output:
|
---|
42 | ; DVBTOT - Total number of ICD9 codes filed
|
---|
43 | ;
|
---|
44 | N DVBLINE ;$TEXT code line
|
---|
45 | N DVBLN ;line counter incrimenter
|
---|
46 | N DVBTAG ;line tag of routine to process
|
---|
47 | N DVBVBA ;VBA DX code (external value)
|
---|
48 | ;
|
---|
49 | S (DVBLN,DVBVBA)=0
|
---|
50 | ;
|
---|
51 | F S DVBTAG="TEXT+"_DVBLN_DVBRTN,DVBLINE=$T(@DVBTAG) Q:DVBLINE["$EXIT" D
|
---|
52 | . ;get VBA DX CODE var setup
|
---|
53 | . I DVBLINE'["~" D Q
|
---|
54 | . . S DVBVBA=$P(DVBLINE,";",3),DVBLN=DVBLN+1
|
---|
55 | . . ; - if code not found setup ^TMP() file error record
|
---|
56 | . . I '$O(^DIC(31,"C",DVBVBA,"")) D
|
---|
57 | . . . S @DVBTMP@("ERROR",DVBVBA)="DX CODE not found in (#31) file"
|
---|
58 | . . . S DVBVBA=0
|
---|
59 | . ;
|
---|
60 | . ;quit back to loop if no VBA code ien found (just in case)
|
---|
61 | . I 'DVBVBA S DVBLN=DVBLN+1 Q
|
---|
62 | . ;
|
---|
63 | . D BLDVBA(DVBVBA,DVBLINE,.DVBTOT)
|
---|
64 | . S DVBLN=DVBLN+1
|
---|
65 | Q
|
---|
66 | ;
|
---|
67 | ;
|
---|
68 | BLDVBA(DVBVBA,DVBLINE,DVBTOT) ;extract ICD9 codes from text line
|
---|
69 | ;
|
---|
70 | ; Input:
|
---|
71 | ; DVBVBA - VBA DX code (external value)
|
---|
72 | ; DVBLINE - $TEXT code line of ICD9's
|
---|
73 | ; DVBTOT - Total number of ICD9 codes filed
|
---|
74 | ;
|
---|
75 | ; Output:
|
---|
76 | ; DVBTOT - Total number of ICD9 codes filed
|
---|
77 | ;
|
---|
78 | Q:'$G(DVBVBA)
|
---|
79 | Q:$G(DVBLINE)']""
|
---|
80 | ;
|
---|
81 | N DVBDATA,DVBI,DVBICD,DVBICDEN,DVBIEN,DVBMATCH,DVBX
|
---|
82 | ;
|
---|
83 | ;loop in case there might be multiple VBA ien's setup
|
---|
84 | S DVBIEN=0
|
---|
85 | F S DVBIEN=$O(^DIC(31,"C",DVBVBA,DVBIEN)) Q:DVBIEN="" D
|
---|
86 | . S DVBX=$P(DVBLINE,";",3,999)
|
---|
87 | . S (DVBI,DVBICD)=0
|
---|
88 | . F DVBI=1:1 S DVBDATA=$P(DVBX,"^",DVBI) Q:DVBDATA="" D
|
---|
89 | . . Q:DVBDATA[";"
|
---|
90 | . . S DVBICD=$P(DVBDATA,"~"),DVBMATCH=+$P(DVBDATA,"~",2)
|
---|
91 | . . ; - get ICD9 pointer from ICD DIAGNOSIS (#80) file
|
---|
92 | . . S DVBICDEN=+$$ICDDX^ICDCODE(DVBICD)
|
---|
93 | . . I ('DVBICDEN)!(DVBICDEN<0) D Q
|
---|
94 | . . . S @DVBTMP@("ERROR",DVBVBA,DVBIEN,DVBICD)="not found in ICD DIAGNOSIS (#80) file"
|
---|
95 | . . ;
|
---|
96 | . . Q:$D(^DIC(31,DVBIEN,"ICD","B",DVBICDEN)) ;ICD9 already setup
|
---|
97 | . . ;
|
---|
98 | . . ;call to create new multiple field (#20) RELATED ICD9 CODES
|
---|
99 | . . I '$$FILEICD(DVBIEN,DVBICDEN,DVBMATCH) D Q
|
---|
100 | . . . S @DVBTMP@("ERROR",DVBVBA,DVBIEN,DVBICD)="error filing to (#31) file"
|
---|
101 | . . S DVBTOT=DVBTOT+1
|
---|
102 | Q
|
---|
103 | ;
|
---|
104 | ;
|
---|
105 | FILEICD(DVBIEN,DVBICDEN,DVBMATCH) ;file code mapping to (#31) file
|
---|
106 | ;
|
---|
107 | ; Input:
|
---|
108 | ; DVBIEN - ien of VBA DX CODE in file (#31)
|
---|
109 | ; DVBICDEN - ien of ICD9 code in file (#80)
|
---|
110 | ; DVBMATCH - match code (1 or 0)
|
---|
111 | ;
|
---|
112 | ; Output:
|
---|
113 | ; Function result - 1 on success, 0 on failure
|
---|
114 | ;
|
---|
115 | ; New Fields created:
|
---|
116 | ; (#20) RELATED ICD9 CODES - ICD;0 POINTER Multiple (#31.01)
|
---|
117 | ; (#31.01) -- RELATED ICD9 CODES SUB-FILE
|
---|
118 | ; Field(s):
|
---|
119 | ; .01 RELATED ICD9 CODES - 0;1 POINTER TO ICD DIAGNOSIS FILE (#80)
|
---|
120 | ; .02 ICD9 MATCH - 0;2 SET ('0' FOR PARTIAL MATCH; '1' FOR MATCH;)
|
---|
121 | ;
|
---|
122 | N DVBERR,DVBFDA,DVBRSLT
|
---|
123 | S DVBRSLT=0
|
---|
124 | ;
|
---|
125 | I $G(DVBIEN),$G(DVBICDEN),$G(DVBMATCH)]"" D
|
---|
126 | . K DVBFDA,DVBERR
|
---|
127 | . S DVBFDA(31,"?+1,",.01)=DVBIEN
|
---|
128 | . S DVBFDA(31.01,"+2,?+1,",.01)=DVBICDEN
|
---|
129 | . S DVBFDA(31.01,"+2,?+1,",.02)=DVBMATCH
|
---|
130 | . D UPDATE^DIE("","DVBFDA","","DVBERR")
|
---|
131 | . S:'$D(DVBERR) DVBRSLT=1
|
---|
132 | Q DVBRSLT
|
---|
133 | ;
|
---|
134 | ;
|
---|
135 | ;FOR TESTING ONLY
|
---|
136 | DELETE ;delete (#20) field sub-file (#31.01) ICD9 entries
|
---|
137 | ;
|
---|
138 | N DVBIEN,CNT
|
---|
139 | N DA,DIC,DIK,X,Y
|
---|
140 | ;
|
---|
141 | ;delete all ICD9 entries first
|
---|
142 | S (CNT,DVBIEN)=0
|
---|
143 | F S DVBIEN=$O(^DIC(31,DVBIEN)) Q:DVBIEN="" D
|
---|
144 | . I $O(^DIC(31,DVBIEN,"ICD",0)) D
|
---|
145 | . . S DA(1)=DVBIEN,DIK="^DIC(31,"_DA(1)_",""ICD"",",DA=0,CNT=CNT+1
|
---|
146 | . . I CNT=1 D BMES^XPDUTL(" >>> *** Removing data from field #20 in the DISABILITY CONDITION (#31) file... "),MES^XPDUTL(" ")
|
---|
147 | . . F S DA=$O(^DIC(31,DA(1),"ICD",DA)) Q:'DA D ^DIK
|
---|
148 | . . ;
|
---|
149 | . . ;now kill the (#20) RELATED ICD9 CODES field node
|
---|
150 | . . I '$O(^DIC(31,DA(1),"ICD",0)) K ^DIC(31,DA(1),"ICD",0)
|
---|
151 | Q
|
---|
152 | ;
|
---|
153 | ;
|
---|
154 | ;NOTE:
|
---|
155 | ;The DISABILITY CONDITION FILE (#31) will have a new multiple field
|
---|
156 | ;added that will contain the Rated Disabilities (VA) field DX CODE
|
---|
157 | ;mapping of a specific ICD9 diagnosis code and a Match code value.
|
---|
158 | ;
|
---|
159 | ; New Fields created:
|
---|
160 | ; (#20) RELATED ICD9 CODES - ICD;0 POINTER Multiple (#31.01)
|
---|
161 | ; (#31.01) -- RELATED ICD9 CODES SUB-FILE
|
---|
162 | ; Field(s):
|
---|
163 | ; .01 RELATED ICD9 CODES - 0;1 POINTER TO ICD DIAGNOSIS FILE (#80)
|
---|
164 | ; .02 ICD9 MATCH - 0;2 SET ('0' FOR PARTIAL MATCH; '1' FOR MATCH;)
|
---|
165 | ;
|
---|
166 | ;The following TEXT lines are a combination of a single 4 digit VBA
|
---|
167 | ;rated disabilities code (DX CODE) on one line followed by on the
|
---|
168 | ;next sequential line(s), all of the related ICD9 DIAGNOSIS codes
|
---|
169 | ;that are to be mapped together. Each IDC9 code also has a (1/0)
|
---|
170 | ;match value that will be filed with it.
|
---|
171 | ;
|
---|
172 | ;Example:
|
---|
173 | ; ;;5000 = a single (VBA) Rated Disabilities (VA) DX CODE
|
---|
174 | ; ;;003.24~1^376.03~1^730.00~1^... = string of ICD9 DIAGNOSIS CODES
|
---|
175 | ; (delimited by (^) up-arrow)
|
---|
176 | ; Each (^) piece contains 2 pieces of data delimited by (~):
|
---|
177 | ; $P(1) = a single ICD9 diagnosis code
|
---|
178 | ; $P(2) = (1/0) match code value
|
---|
179 | ;
|
---|
180 | ; Note: If the TEXT line ends with a (;) semi-colon, this means the
|
---|
181 | ; next sequential line is associated with the same DX CODE.
|
---|
182 | ; (No sequential line(s) are carried over to the next
|
---|
183 | ; post-install Routine.)
|
---|
184 | ;
|
---|
185 | TEXT ;;5000
|
---|
186 | ;;003.24~0^376.03~0^730.00~0^730.01~0^730.02~0^730.03~0^730.04~0^730.05~0^730.06~0^730.07~0^730.08~0^730.09~1^730.10~0^730.11~0^730.12~0^730.13~0^730.14~0^730.15~0^730.16~0^730.17~0^730.18~0^730.19~1^;
|
---|
187 | ;;730.20~0^730.21~0^730.22~0^730.23~0^730.24~0^730.25~0^730.26~0^730.27~0^730.28~0^730.29~1
|
---|
188 | ;;5001
|
---|
189 | ;;015.00~0^015.01~0^015.02~0^015.03~0^015.04~0^015.05~0^015.06~0^015.10~0^015.11~0^015.12~0^015.13~0^015.14~0^015.15~0^015.16~0^015.20~0^015.21~0^015.22~0^015.23~0^015.24~0^015.25~0^015.26~0^015.50~0^;
|
---|
190 | ;;015.51~0^015.52~0^015.53~0^015.54~0^015.55~0^015.56~0^015.60~0^015.61~0^015.62~0^015.63~0^015.64~0^015.65~0^015.66~0^015.70~0^015.71~0^015.72~0^015.73~0^015.74~0^015.75~0^015.76~0^015.80~0^015.81~0^;
|
---|
191 | ;;015.82~0^015.83~0^015.84~0^015.85~0^015.86~0^015.90~0^015.91~0^015.92~0^015.93~0^015.94~0^015.95~0^015.96~0
|
---|
192 | ;;5002
|
---|
193 | ;;714.0~0^714.1~0^714.2~0^714.30~0^714.31~0^714.32~0^714.33~0^714.4~0
|
---|
194 | ;;5003
|
---|
195 | ;;715.00~0^715.04~0^715.09~0^715.10~0^715.11~0^715.12~0^715.13~0^715.14~0^715.15~0^715.16~0^715.17~0^715.18~0^715.20~0^715.21~0^715.22~0^715.23~0^715.24~0^715.25~0^715.26~0^715.27~0^715.28~0^715.30~0^;
|
---|
196 | ;;715.31~0^715.32~0^715.33~0^715.34~0^715.35~0^715.36~0^715.37~0^715.38~0^715.80~0^715.89~0^715.90~0^715.91~0^715.92~0^715.93~0^715.94~0^715.95~0^715.96~0^715.97~0^715.98~0
|
---|
197 | ;;5004
|
---|
198 | ;;098.50~0
|
---|
199 | ;;$EXIT
|
---|