1 | DVBHUTIL ;ALB/JLU -This is a general utility program ;3/19/90
|
---|
2 | ;;4.0;HINQ;**3,12,17,32**;03/25/92
|
---|
3 | ;entry point for DVBHQUP to set up intensity for screens.
|
---|
4 | A S DVBOUT="",IOP="HOME",(DVBBLO,DVBBLF,DVBON,DVBOFF,DVBLIT1,DVBLIT2)="" D ^%ZIS K IOP
|
---|
5 | I $S('$D(^DVB(395,1,0)):1,'$P(^(0),U,3):1,1:0) Q
|
---|
6 | S X="IOINHI;IOINLOW;IOBON;IOBOFF" D ENDR^%ZISS S DVBON=IOINHI,DVBOFF=IOINLOW,DVBBLO=IOBON,DVBBLF=IOBOFF
|
---|
7 | ;;;I ^%ZOSF("OS")["VAX" S DVBLIT="" E ;
|
---|
8 | W !,DVBON,"",DVBOFF S O=$X
|
---|
9 | S DVBLIT1="S DX=$X-"_O_",DY=$S($Y>IOSL:IOSL,1:$Y) "_^%ZOSF("XY")_" K DX,DY"
|
---|
10 | W !,DVBBLO,"",DVBBLF S O=$X
|
---|
11 | S DVBLIT2="S DX=$X-"_O_",DY=$S($Y>IOSL:IOSL,1:$Y) "_^%ZOSF("XY")_" K DX,DY"
|
---|
12 | ;
|
---|
13 | ;
|
---|
14 | K IOINHI,IOINLOW,IOBOFF,IOBON
|
---|
15 | Q
|
---|
16 | ;Entry point from update template for three part question
|
---|
17 | Q W !!,"Is this the patient to update (YES, NO, IGNORE, DISPLAY, ALERT)? YES//" R DVBUQ:DTIME S DVBOUT=DVBUQ
|
---|
18 | I DVBUQ["^" S Y="@10" Q
|
---|
19 | I "Yy"[DVBUQ!(""[DVBUQ) S $P(^DVB(395.5,DFN,0),U,5)="I" W " YES" DO Q
|
---|
20 | .I '$D(DVBDATA) Q
|
---|
21 | .I 'DVBDATA Q
|
---|
22 | .S DIE("NO^")=""
|
---|
23 | .S Y=+DVBDATA
|
---|
24 | .S Y=$S("1234"[Y:"@"_(Y-1),Y=5:"@104",Y=6:"@1006",1:"@10")
|
---|
25 | .Q:Y="@10"
|
---|
26 | .S DVBDATA=$P(DVBDATA,"^",2,10)_"^"_$P(DVBDATA,"^",10,99)
|
---|
27 | .I Y="@" S Y="@8"
|
---|
28 | I "Nn"[DVBUQ S Y="@10" W " NO" Q
|
---|
29 | I "Ii"[DVBUQ S Y="@10" S $P(^DVB(395.5,DFN,0),U,5)="I" W " IGNORE" Q
|
---|
30 | ;
|
---|
31 | I "Dd"[DVBUQ W " DISPLAY" S DVBMM=1,DVBJIO=IO(0) D EN^DVBHIQM,WRT1^DVBHQD1,TEM^DVBHIQR K ^TMP($J),DVBMM,DVBJIO S Y="@101" Q
|
---|
32 | I "Aa"[DVBUQ,$D(DVBDATA),1 W " ALERT" DO Q
|
---|
33 | .D ACHK^DVBHT1
|
---|
34 | .D DISPLAY^DVBHT I $D(DVBNOALR) S Y="@10" Q
|
---|
35 | .I $D(DVBJ2),DVBJ2 D ACKNOW^DVBHT S Y="@101" Q
|
---|
36 | .D PAGE^DVBHT S Y="@101" Q
|
---|
37 | E I "Aa"[DVBUQ DO G Q
|
---|
38 | .W !!,"You are not processing an Alert, 'A'lert update and display not available."
|
---|
39 | ;
|
---|
40 | W *7,!," 'Y'es, Will continue with this patient",!," 'N'o, Go next patient",!," 'I'gnore, Patient will NOT appear in ALL option until reHINQ",!," 'D'isplay will show you the HINQ mail message."
|
---|
41 | W !," 'A'lert, will update and display the Alert if processing alerts",!," '^' to quit"
|
---|
42 | G Q
|
---|
43 | ;header for ^DVBHQZ6
|
---|
44 | 2 W !,?9,"**************************************************************"
|
---|
45 | W !,?9,"* This option will print out a report, identical to the mail *"
|
---|
46 | W !,?9,"* messages, of the patients in the suspense file with a *"
|
---|
47 | W !,?9,"* successful HINQ request. *"
|
---|
48 | W !,?9,"**************************************************************"
|
---|
49 | Q
|
---|
50 | ;
|
---|
51 | SIGN ;General sign converter var to be worked on/defined DVBV1,DVBV2
|
---|
52 | ;DVBV1 contains the string of characters
|
---|
53 | ;DVBV2 contains the character at which the sign resides.
|
---|
54 | ;Must be sure there is a sign there before sending to this routine
|
---|
55 | N CT,A1,V
|
---|
56 | I '$D(DVBS) S CT=1,DVBS("{")=0 F A1=65:1:73 S DVBS($C(A1))=CT S CT=CT+1
|
---|
57 | I '$D(DVBS($E(DVBV1,DVBV2))) D W2 Q
|
---|
58 | S V=DVBS($E(DVBV1,DVBV2)),DVBV2=$S(DVBV2=1:1,1:DVBV2-1),DVBV1=$S(DVBV2=1:"",1:$E(DVBV1,1,DVBV2))_V
|
---|
59 | Q
|
---|
60 | ;
|
---|
61 | SCRHD W @$S('$D(IOF):"#",IOF="":"#",1:IOF)
|
---|
62 | W ?1,$E(DVBDIQ(2,DFN,.01,"E"),1,30)
|
---|
63 | W ?22,"Patient File"
|
---|
64 | W ?35,DVBON,"((",DVBSCRN,"))",DVBOFF X DVBLIT1
|
---|
65 | W ?49,"HINQ Response"
|
---|
66 | W ?68,"SSN: ",DVBON,$E(DVBDIQ(2,DFN,.09,"E"),6,9),DVBOFF
|
---|
67 | W !,"-------------------------------------------------------------------------------"
|
---|
68 | Q
|
---|
69 | ;
|
---|
70 | CHK ;This entry point will print an error message for the edit template
|
---|
71 | ;if the diag. were BIRLS only and the DIAG. Verif. ind. was not 'Y'
|
---|
72 | ;
|
---|
73 | W !!,*7,?7,"BIRLS only response and the 'Diagnostic Verified Indicator' is NO.",!,?16,"Verify SC at folder location: ",DVBFL,!,?28,DVBON,"No updating allowed.",DVBOFF
|
---|
74 | X DVBLIT1 S DVB=D0,DVBLP=2,DVBMM=1 D QB^DVBHQZ6 S Y="@50"
|
---|
75 | Q
|
---|
76 | ;
|
---|
77 | POW ;This entry point is to determine the variable for the input to the
|
---|
78 | ;patient file. Whether POW or not.
|
---|
79 | ;
|
---|
80 | I $D(DVBPOW) S DVBPOW1=$S(DVBPOW=1!(DVBPOW=2):"Y",1:"N")
|
---|
81 | I $D(DVBPOWD) S DVBPOW1=$S(+DVBPOWD:"Y",1:"N")
|
---|
82 | Q
|
---|
83 | ;
|
---|
84 | VERR ;This entry point prints an error message if mas not >5.1 cause .305 unemployable field is not there.
|
---|
85 | W !!,*7,?2,"Your version of MAS is NOT greater than 5.1, thus the Unemployable field"
|
---|
86 | W !,?2,"is not in your patient file. No uploading of this field allowed."
|
---|
87 | R !,?25,"<RET to continue>",DVBQ:DTIME K DVBQ
|
---|
88 | Q
|
---|
89 | ;
|
---|
90 | SCRQ ;The screens will call this entry point to read the answer from the user.
|
---|
91 | W !!,DVBON,"<RET> ",DVBOFF X DVBLIT1
|
---|
92 | W "to CONTINUE, "
|
---|
93 | W DVBON,"'^' ",DVBOFF X DVBLIT1
|
---|
94 | W "to QUIT, "
|
---|
95 | W DVBON,"N N-N N,N,N,N or (A)-ALL",DVBOFF X DVBLIT1
|
---|
96 | W " to update: "
|
---|
97 | R ANS:DTIME S Y=$S(ANS="^"!($T=0):"@10",ANS=""&$T=1:"@4",ANS["?":"@6",1:"@8")
|
---|
98 | I Y="@4",$D(DVBDATA),DVBDATA DO
|
---|
99 | .S Y=+DVBDATA
|
---|
100 | .S DVBDATA=$P(DVBDATA,"^",2,10)_"^"_$P(DVBDATA,"^",10,99)
|
---|
101 | .S Y=$S("1234"[Y:"@"_(Y-1),Y=5:"@104",Y=6:"@1006",1:"@10")
|
---|
102 | I Y="@8" ;;;,$D(DVBDATA),DVBDATA S $P(DVBDATA,"^")=""
|
---|
103 | Q
|
---|
104 | S Y=$S(DVBJS=11:"@1",DVBJS=28:"@2",DVBJS=35:"@3",DVBJS=44:"@104",DVBJS=53:"@1006",1:"@10")
|
---|
105 | Q
|
---|
106 | ;
|
---|
107 | W2 ;error message for missing data found in sign subroutine
|
---|
108 | S DVBERCS=1 I '$G(DVBTSK) D
|
---|
109 | .W !!!!,?15,"HINQ data does NOT seem right."
|
---|
110 | .I +DFN>0 D
|
---|
111 | ..W !,?15,"Data appears to be missing for ",$S($D(^DPT(DFN,0)):$P(^(0),U),1:DFN)
|
---|
112 | ..W !,?15,"Please re-HINQ for this patient.",! H 3
|
---|
113 | Q
|
---|