- SROAPM ;BIR/ADM - PATIENT DEMOGRAPHIC INFO ;05/28/10
- ;;3.0;Surgery;**47,81,111,107,100,125,142,160,166,174,175,182,184**;24 Jun 93;Build 35
- I '$D(SRTN) W !!,"A Surgery Risk Assessment must be selected prior to using this option.",!!,"Press <RET> to continue " R X:DTIME G END
- S SRSOUT=0,SRSUPCPT=1 D ^SROAUTL
- START G:SRSOUT END D HDR^SROAUTL
- S DIR("A",1)="Enter/Edit Patient Demographic Information",DIR("A",2)=" ",DIR("A",3)="1. Capture Information from PIMS Records",DIR("A",4)="2. Enter, Edit, or Review Information",DIR("A",5)=" "
- S DIR("?",1)="Enter '1' if you want to capture patient movement information from PIMS",DIR("?",2)="records. Enter '2' if you want to enter, edit, or review patient",DIR("?")="movement and other information on this screen."
- S DIR("A")="Select Number",DIR(0)="NO^1:2" D ^DIR K DIR I $D(DTOUT)!$D(DUOUT)!'Y S SRSOUT=1 G END
- I Y=1 D PIMS G START
- EDIT S SRR=0 D HDR^SROAUTL K DR S SRQ=0,(DR,SRDR)="413;452;453;454;418;419;420;421;685;247;.011"
- K DA,DIC,DIQ,SRY S DIC="^SRF(",DA=SRTN,DIQ="SRY",DIQ(0)="E",DR=SRDR D EN^DIQ1 K DA,DIC,DIQ,DR
- K SRZ S SRZ=0 F M=1:1 S I=$P(SRDR,";",M) Q:'I D
- .D TR,GET
- .S SRZ=SRZ+1,Y=$P(X,";;",2),SRFLD=$P(Y,"^"),(Z,SRZ(SRZ))=$P(Y,"^",2)_"^"_SRFLD,SREXT=SRY(130,SRTN,SRFLD,"E")
- .W !,$S($L(SRZ)<2:" "_SRZ,1:SRZ)_". "_$P(Z,"^")_":" D EXT
- ;
- D DEM^VADPT
- ;Find patient's ethnicity and list it on the display
- W !,"12. *Patient's Ethnicity:" S SRZ(12)="" D
- .I $G(VADM(11)) W ?40,$P(VADM(11,1),U,2)
- .I '$G(VADM(11)) W ?40,"UNANSWERED"
- ;
- ;Find all race entries and place into a string with commas inbetween
- S SRORC=0,C=1,SRORACE="",SROLINE="",N=1,SROL=""
- F S SRORC=$O(VADM(12,SRORC)) Q:SRORC="" Q:C=11 D
- .I $G(VADM(12,SRORC)) S SRORACE(C)=$P(VADM(12,SRORC),U,2)
- .I SROLINE'="" S SROLINE=SROLINE_", "_SRORACE(C)
- .I SROLINE="" S SROLINE=SRORACE(C)
- .S C=C+1
- ;
- ;Find total length of 'race' string and wrap the text if necessary
- I $L(SROLINE)=40!$L(SROLINE)<40 S SROL(N)=SROLINE,SRNUM1=2
- I $L(SROLINE)>40 D WRAP
- ;
- W !,"13. *Patient's Race:" S SRZ(13)=""
- I $G(VADM(12)) F D=1:1:SRNUM1-1 D
- .W:D=1 ?40,SROL(D)
- .W:D'=1 !,?40,SROL(D)
- ;
- I '$G(VADM(12)) W ?40,"UNANSWERED"
- ;
- K DA,DIC,DIQ,DR,SRY S (DR,SRDR)="342;342.1",DIC="^SRF(",DA=SRTN,DIQ="SRY",DIQ(0)="E",DR=SRDR D EN^DIQ1 K DA,DIC,DIQ,DR
- S SRZ=13 F M=1:1 S I=$P(SRDR,";",M) Q:'I D
- .D TR,GET
- .S SRZ=SRZ+1,Y=$P(X,";;",2),SRFLD=$P(Y,"^"),(Z,SRZ(SRZ))=$P(Y,"^",2)_"^"_SRFLD,SREXT=SRY(130,SRTN,SRFLD,"E")
- .W !,$S($L(SRZ)<2:" "_SRZ,1:SRZ)_". "_$P(Z,"^")_":" D EXT
- K SROL,SROLINE,SRORC,SRORACE,SROLN,SROLN1,SROWRAP,SRNUM1
- ;
- W !! F K=1:1:80 W "-"
- D SEL G:SRR=1 EDIT
- S SROERR=SRTN D ^SROERR0
- G START
- Q
- ;
- WRAP ;Wrap multiple race entries so that wrapped line
- ;does not break in the middle of a word
- ;
- N SROLNGTH S SROLNGTH=$L(SROLINE),E=40,SROWRAP="",SROLN="",SROLN1="",SROL=""
- F I=1:40:SROLNGTH S SROLN(I)=SROWRAP_$E(SROLINE,I,E) D
- .F K=40:-1:1 I $E(SROLN(I),K)[" " D Q ;Break lines at space
- ..S SROLN1(I)=$E(SROLN(I),1,K-1)
- ..S SROWRAP=$E(SROLN(I),K+1,E)
- .S E=E+40
- ;
- S:'$D(SROLN1(I)) SROLN1(I)=SROLN(I),SROWRAP=""
- I $L(SROLN1(I))+$L(SROWRAP)>39 S SROLN1(I+1)=SROWRAP ;Last line
- I $L(SROLN1(I))+$L(SROWRAP)'>39 S SROLN1(I)=SROLN1(I)_" "_SROWRAP
- ;
- ;Renumber the SROLN1 array to be in numeric order
- S SRNUM=0,SRNUM1=1
- F S SRNUM=$O(SROLN1(SRNUM)) Q:SRNUM="" D
- .S SROL(SRNUM1)=SROLN1(SRNUM)
- .S SRNUM1=SRNUM1+1
- Q
- ;
- EXT I $L(SREXT)<40 W ?40,SREXT W:SRFLD=247 $S(SREXT="":"",SREXT=1:" Day",SREXT=0:" Days",SREXT>1:" Days",1:"") Q
- N I,J,X,Y S X=SREXT F D W:$L(X) ! I $L(X)<40!(X'[" ") W ?40,X Q
- .F I=0:1:38 S J=39-I,Y=$E(X,J) I Y=" " W ?40,$E(X,1,J-1) S X=$E(X,J+1,$L(X)) Q
- Q
- SEL W !,"Select Patient Demographics Information to Edit: " R X:DTIME I '$T!(X["^") S SRSOUT=1 Q
- I (X=12)!(X=13) S SRR=1 W !!,"The Patient's Race and Ethnicity information cannot be updated through the" D Q
- .W !,"Surgery package options."
- .W !!,"Press RETURN to continue " R X:DTIME
- Q:X="" S:X="a" X="A" I '$D(SRFLG),'$D(SRZ(X)),(X'?1.2N1":"1.2N),X'="A" D HELP S SRR=1 Q
- I X?1.2N1":"1.2N S Y=$P(X,":"),Z=$P(X,":",2) I Y<1!(Z>SRZ)!(Y>Z) D HELP S SRR=1 Q
- I X="A" S X="1:"_SRZ
- I X?1.2N1":"1.2N D RANGE S SRR=1 Q
- I $D(SRZ(X)),+X=X S EMILY=X D S SRR=1
- .I $$LOCK^SROUTL(SRTN) D ONE,UNLOCK^SROUTL(SRTN)
- Q
- PIMS ; get update from PIMS records
- W ! K DIR S DIR("A")="Are you sure you want to retrieve information from PIMS records ? ",DIR("B")="YES",DIR(0)="YOA" D ^DIR K DIR I $D(DTOUT)!$D(DUOUT)!'Y Q
- I $$LOCK^SROUTL(SRTN) D D UNLOCK^SROUTL(SRTN)
- .W ! D WAIT^DICD D ^SROAPIMS
- Q
- HELP W @IOF,!!!!,"Enter the number or range of numbers you want to edit. Examples of proper",!,"responses are listed below.",!!,"NOTE: Items 12 and 13 cannot be updated through the surgery package options."
- W !!,"1. Enter 'A' to update items 1 through 11 and item 14.",!!,"2. Enter a number (1-"_SRZ_") to update an individual item. (For example,",!," enter '1' to update "_$P(SRZ(1),"^")_")"
- W !!,"3. Enter a range of numbers (1-"_SRZ_") separated by a ':' to enter a range",!," of items. (For example, enter '1:4' to update items 1, 2, 3 and 4.)",!
- I $D(SRFLG) W !,"4. Enter 'N' or 'NO' to enter negative response for all items.",!!,"5. Enter '@' to delete information from all items.",!
- PRESS W ! K DIR S DIR("A")="Press the return key to continue or '^' to exit: ",DIR(0)="FOA" D ^DIR K DIR I $D(DTOUT)!$D(DUOUT) S SRSOUT=1
- Q
- RANGE ; range of numbers
- I $$LOCK^SROUTL(SRTN) D D UNLOCK^SROUTL(SRTN)
- .S SHEMP=$P(X,":"),CURLEY=$P(X,":",2) D
- ..F EMILY=SHEMP:1:CURLEY Q:SRSOUT D ONE
- Q
- ONE ; edit one item
- Q:(EMILY=12!(EMILY=13))
- K DR,DA,DIE S DR=$P(SRZ(EMILY),"^",2)_"T",DA=SRTN,DIE=130,SRDT=$P(SRZ(EMILY),"^",3) S:SRDT DR=DR_";"_SRDT_"T" D ^DIE K DR,DA I $D(Y) S SRSOUT=1
- Q
- TR S J=I,J=$TR(J,"1234567890.","ABCDEFGHIJP")
- Q
- GET S X=$T(@J)
- Q
- END W @IOF D ^SRSKILL
- Q
- PJAA ;;.011^Hospital Admission Status
- BDG ;;247^Length of Postop Hospital Stay
- DAC ;;413^Transfer Status
- DAG ;;417^Patient's Race
- DAH ;;418^Hospital Admission Date/Time
- DAI ;;419^Hospital Discharge Date/Time
- DBJ ;;420^Admit/Transfer to Surgical Svc.
- DBA ;;421^Discharge/Transfer to Chronic Care
- FHE ;;685^DC/REL Destination
- DEB ;;452^Observation Admission Date/Time
- DEC ;;453^Observation Discharge Date/Time
- DED ;;454^Observation Treating Specialty
- CDB ;;342^Date of Death
- CDBPA ;;342.1^30-Day Death
- --- Routine Detail --- with STRUCTURED ROUTINE LISTING ---[H[J[2J[HSROAPM 6447 printed Jan 18, 2025@03:42:45 Page 2
- SROAPM ;BIR/ADM - PATIENT DEMOGRAPHIC INFO ;05/28/10
- +1 ;;3.0;Surgery;**47,81,111,107,100,125,142,160,166,174,175,182,184**;24 Jun 93;Build 35
- +2 IF '$DATA(SRTN)
- WRITE !!,"A Surgery Risk Assessment must be selected prior to using this option.",!!,"Press <RET> to continue "
- READ X:DTIME
- GOTO END
- +3 SET SRSOUT=0
- SET SRSUPCPT=1
- DO ^SROAUTL
- START if SRSOUT
- GOTO END
- DO HDR^SROAUTL
- +1 SET DIR("A",1)="Enter/Edit Patient Demographic Information"
- SET DIR("A",2)=" "
- SET DIR("A",3)="1. Capture Information from PIMS Records"
- SET DIR("A",4)="2. Enter, Edit, or Review Information"
- SET DIR("A",5)=" "
- +2 SET DIR("?",1)="Enter '1' if you want to capture patient movement information from PIMS"
- SET DIR("?",2)="records. Enter '2' if you want to enter, edit, or review patient"
- SET DIR("?")="movement and other information on this screen."
- +3 SET DIR("A")="Select Number"
- SET DIR(0)="NO^1:2"
- DO ^DIR
- KILL DIR
- IF $DATA(DTOUT)!$DATA(DUOUT)!'Y
- SET SRSOUT=1
- GOTO END
- +4 IF Y=1
- DO PIMS
- GOTO START
- EDIT SET SRR=0
- DO HDR^SROAUTL
- KILL DR
- SET SRQ=0
- SET (DR,SRDR)="413;452;453;454;418;419;420;421;685;247;.011"
- +1 KILL DA,DIC,DIQ,SRY
- SET DIC="^SRF("
- SET DA=SRTN
- SET DIQ="SRY"
- SET DIQ(0)="E"
- SET DR=SRDR
- DO EN^DIQ1
- KILL DA,DIC,DIQ,DR
- +2 KILL SRZ
- SET SRZ=0
- FOR M=1:1
- SET I=$PIECE(SRDR,";",M)
- if 'I
- QUIT
- Begin DoDot:1
- +3 DO TR
- DO GET
- +4 SET SRZ=SRZ+1
- SET Y=$PIECE(X,";;",2)
- SET SRFLD=$PIECE(Y,"^")
- SET (Z,SRZ(SRZ))=$PIECE(Y,"^",2)_"^"_SRFLD
- SET SREXT=SRY(130,SRTN,SRFLD,"E")
- +5 WRITE !,$SELECT($LENGTH(SRZ)<2:" "_SRZ,1:SRZ)_". "_$PIECE(Z,"^")_":"
- DO EXT
- End DoDot:1
- +6 ;
- +7 DO DEM^VADPT
- +8 ;Find patient's ethnicity and list it on the display
- +9 WRITE !,"12. *Patient's Ethnicity:"
- SET SRZ(12)=""
- Begin DoDot:1
- +10 IF $GET(VADM(11))
- WRITE ?40,$PIECE(VADM(11,1),U,2)
- +11 IF '$GET(VADM(11))
- WRITE ?40,"UNANSWERED"
- End DoDot:1
- +12 ;
- +13 ;Find all race entries and place into a string with commas inbetween
- +14 SET SRORC=0
- SET C=1
- SET SRORACE=""
- SET SROLINE=""
- SET N=1
- SET SROL=""
- +15 FOR
- SET SRORC=$ORDER(VADM(12,SRORC))
- if SRORC=""
- QUIT
- if C=11
- QUIT
- Begin DoDot:1
- +16 IF $GET(VADM(12,SRORC))
- SET SRORACE(C)=$PIECE(VADM(12,SRORC),U,2)
- +17 IF SROLINE'=""
- SET SROLINE=SROLINE_", "_SRORACE(C)
- +18 IF SROLINE=""
- SET SROLINE=SRORACE(C)
- +19 SET C=C+1
- End DoDot:1
- +20 ;
- +21 ;Find total length of 'race' string and wrap the text if necessary
- +22 IF $LENGTH(SROLINE)=40!$LENGTH(SROLINE)<40
- SET SROL(N)=SROLINE
- SET SRNUM1=2
- +23 IF $LENGTH(SROLINE)>40
- DO WRAP
- +24 ;
- +25 WRITE !,"13. *Patient's Race:"
- SET SRZ(13)=""
- +26 IF $GET(VADM(12))
- FOR D=1:1:SRNUM1-1
- Begin DoDot:1
- +27 if D=1
- WRITE ?40,SROL(D)
- +28 if D'=1
- WRITE !,?40,SROL(D)
- End DoDot:1
- +29 ;
- +30 IF '$GET(VADM(12))
- WRITE ?40,"UNANSWERED"
- +31 ;
- +32 KILL DA,DIC,DIQ,DR,SRY
- SET (DR,SRDR)="342;342.1"
- SET DIC="^SRF("
- SET DA=SRTN
- SET DIQ="SRY"
- SET DIQ(0)="E"
- SET DR=SRDR
- DO EN^DIQ1
- KILL DA,DIC,DIQ,DR
- +33 SET SRZ=13
- FOR M=1:1
- SET I=$PIECE(SRDR,";",M)
- if 'I
- QUIT
- Begin DoDot:1
- +34 DO TR
- DO GET
- +35 SET SRZ=SRZ+1
- SET Y=$PIECE(X,";;",2)
- SET SRFLD=$PIECE(Y,"^")
- SET (Z,SRZ(SRZ))=$PIECE(Y,"^",2)_"^"_SRFLD
- SET SREXT=SRY(130,SRTN,SRFLD,"E")
- +36 WRITE !,$SELECT($LENGTH(SRZ)<2:" "_SRZ,1:SRZ)_". "_$PIECE(Z,"^")_":"
- DO EXT
- End DoDot:1
- +37 KILL SROL,SROLINE,SRORC,SRORACE,SROLN,SROLN1,SROWRAP,SRNUM1
- +38 ;
- +39 WRITE !!
- FOR K=1:1:80
- WRITE "-"
- +40 DO SEL
- if SRR=1
- GOTO EDIT
- +41 SET SROERR=SRTN
- DO ^SROERR0
- +42 GOTO START
- +43 QUIT
- +44 ;
- WRAP ;Wrap multiple race entries so that wrapped line
- +1 ;does not break in the middle of a word
- +2 ;
- +3 NEW SROLNGTH
- SET SROLNGTH=$LENGTH(SROLINE)
- SET E=40
- SET SROWRAP=""
- SET SROLN=""
- SET SROLN1=""
- SET SROL=""
- +4 FOR I=1:40:SROLNGTH
- SET SROLN(I)=SROWRAP_$EXTRACT(SROLINE,I,E)
- Begin DoDot:1
- +5 ;Break lines at space
- FOR K=40:-1:1
- IF $EXTRACT(SROLN(I),K)[" "
- Begin DoDot:2
- +6 SET SROLN1(I)=$EXTRACT(SROLN(I),1,K-1)
- +7 SET SROWRAP=$EXTRACT(SROLN(I),K+1,E)
- End DoDot:2
- QUIT
- +8 SET E=E+40
- End DoDot:1
- +9 ;
- +10 if '$DATA(SROLN1(I))
- SET SROLN1(I)=SROLN(I)
- SET SROWRAP=""
- +11 ;Last line
- IF $LENGTH(SROLN1(I))+$LENGTH(SROWRAP)>39
- SET SROLN1(I+1)=SROWRAP
- +12 IF $LENGTH(SROLN1(I))+$LENGTH(SROWRAP)'>39
- SET SROLN1(I)=SROLN1(I)_" "_SROWRAP
- +13 ;
- +14 ;Renumber the SROLN1 array to be in numeric order
- +15 SET SRNUM=0
- SET SRNUM1=1
- +16 FOR
- SET SRNUM=$ORDER(SROLN1(SRNUM))
- if SRNUM=""
- QUIT
- Begin DoDot:1
- +17 SET SROL(SRNUM1)=SROLN1(SRNUM)
- +18 SET SRNUM1=SRNUM1+1
- End DoDot:1
- +19 QUIT
- +20 ;
- EXT IF $LENGTH(SREXT)<40
- WRITE ?40,SREXT
- if SRFLD=247
- WRITE $SELECT(SREXT="":"",SREXT=1:" Day",SREXT=0:" Days",SREXT>1:" Days",1:"")
- QUIT
- +1 NEW I,J,X,Y
- SET X=SREXT
- FOR
- Begin DoDot:1
- +2 FOR I=0:1:38
- SET J=39-I
- SET Y=$EXTRACT(X,J)
- IF Y=" "
- WRITE ?40,$EXTRACT(X,1,J-1)
- SET X=$EXTRACT(X,J+1,$LENGTH(X))
- QUIT
- End DoDot:1
- if $LENGTH(X)
- WRITE !
- IF $LENGTH(X)<40!(X'[" ")
- WRITE ?40,X
- QUIT
- +3 QUIT
- SEL WRITE !,"Select Patient Demographics Information to Edit: "
- READ X:DTIME
- IF '$TEST!(X["^")
- SET SRSOUT=1
- QUIT
- +1 IF (X=12)!(X=13)
- SET SRR=1
- WRITE !!,"The Patient's Race and Ethnicity information cannot be updated through the"
- Begin DoDot:1
- +2 WRITE !,"Surgery package options."
- +3 WRITE !!,"Press RETURN to continue "
- READ X:DTIME
- End DoDot:1
- QUIT
- +4 if X=""
- QUIT
- if X="a"
- SET X="A"
- IF '$DATA(SRFLG)
- IF '$DATA(SRZ(X))
- IF (X'?1.2N1":"1.2N)
- IF X'="A"
- DO HELP
- SET SRR=1
- QUIT
- +5 IF X?1.2N1":"1.2N
- SET Y=$PIECE(X,":")
- SET Z=$PIECE(X,":",2)
- IF Y<1!(Z>SRZ)!(Y>Z)
- DO HELP
- SET SRR=1
- QUIT
- +6 IF X="A"
- SET X="1:"_SRZ
- +7 IF X?1.2N1":"1.2N
- DO RANGE
- SET SRR=1
- QUIT
- +8 IF $DATA(SRZ(X))
- IF +X=X
- SET EMILY=X
- Begin DoDot:1
- +9 IF $$LOCK^SROUTL(SRTN)
- DO ONE
- DO UNLOCK^SROUTL(SRTN)
- End DoDot:1
- SET SRR=1
- +10 QUIT
- PIMS ; get update from PIMS records
- +1 WRITE !
- KILL DIR
- SET DIR("A")="Are you sure you want to retrieve information from PIMS records ? "
- SET DIR("B")="YES"
- SET DIR(0)="YOA"
- DO ^DIR
- KILL DIR
- IF $DATA(DTOUT)!$DATA(DUOUT)!'Y
- QUIT
- +2 IF $$LOCK^SROUTL(SRTN)
- Begin DoDot:1
- +3 WRITE !
- DO WAIT^DICD
- DO ^SROAPIMS
- End DoDot:1
- DO UNLOCK^SROUTL(SRTN)
- +4 QUIT
- HELP WRITE @IOF,!!!!,"Enter the number or range of numbers you want to edit. Examples of proper",!,"responses are listed below.",!!,"NOTE: Items 12 and 13 cannot be updated through the surgery package options."
- +1 WRITE !!,"1. Enter 'A' to update items 1 through 11 and item 14.",!!,"2. Enter a number (1-"_SRZ_") to update an individual item. (For example,",!," enter '1' to update "_$PIECE(SRZ(1),"^")_")"
- +2 WRITE !!,"3. Enter a range of numbers (1-"_SRZ_") separated by a ':' to enter a range",!," of items. (For example, enter '1:4' to update items 1, 2, 3 and 4.)",!
- +3 IF $DATA(SRFLG)
- WRITE !,"4. Enter 'N' or 'NO' to enter negative response for all items.",!!,"5. Enter '@' to delete information from all items.",!
- PRESS WRITE !
- KILL DIR
- SET DIR("A")="Press the return key to continue or '^' to exit: "
- SET DIR(0)="FOA"
- DO ^DIR
- KILL DIR
- IF $DATA(DTOUT)!$DATA(DUOUT)
- SET SRSOUT=1
- +1 QUIT
- RANGE ; range of numbers
- +1 IF $$LOCK^SROUTL(SRTN)
- Begin DoDot:1
- +2 SET SHEMP=$PIECE(X,":")
- SET CURLEY=$PIECE(X,":",2)
- Begin DoDot:2
- +3 FOR EMILY=SHEMP:1:CURLEY
- if SRSOUT
- QUIT
- DO ONE
- End DoDot:2
- End DoDot:1
- DO UNLOCK^SROUTL(SRTN)
- +4 QUIT
- ONE ; edit one item
- +1 if (EMILY=12!(EMILY=13))
- QUIT
- +2 KILL DR,DA,DIE
- SET DR=$PIECE(SRZ(EMILY),"^",2)_"T"
- SET DA=SRTN
- SET DIE=130
- SET SRDT=$PIECE(SRZ(EMILY),"^",3)
- if SRDT
- SET DR=DR_";"_SRDT_"T"
- DO ^DIE
- KILL DR,DA
- IF $DATA(Y)
- SET SRSOUT=1
- +3 QUIT
- TR SET J=I
- SET J=$TRANSLATE(J,"1234567890.","ABCDEFGHIJP")
- +1 QUIT
- GET SET X=$TEXT(@J)
- +1 QUIT
- END WRITE @IOF
- DO ^SRSKILL
- +1 QUIT
- PJAA ;;.011^Hospital Admission Status
- BDG ;;247^Length of Postop Hospital Stay
- DAC ;;413^Transfer Status
- DAG ;;417^Patient's Race
- DAH ;;418^Hospital Admission Date/Time
- DAI ;;419^Hospital Discharge Date/Time
- DBJ ;;420^Admit/Transfer to Surgical Svc.
- DBA ;;421^Discharge/Transfer to Chronic Care
- FHE ;;685^DC/REL Destination
- DEB ;;452^Observation Admission Date/Time
- DEC ;;453^Observation Discharge Date/Time
- DED ;;454^Observation Treating Specialty
- CDB ;;342^Date of Death
- CDBPA ;;342.1^30-Day Death