| 1 | DVBAPOST ;ALBANY-ISC/GTS-AMIE 2.6 POST-INIT RTN ;1/15/93
 | 
|---|
| 2 |  ;;2.7;AMIE;;Apr 10, 1995
 | 
|---|
| 3 |  ;
 | 
|---|
| 4 | EN D SET1^DVBAUTL1
 | 
|---|
| 5 |  K ^TMP("DVBA",$J)
 | 
|---|
| 6 |  W !,"Setting up List Manager Templates",!
 | 
|---|
| 7 |  D ^DVBAL ;set up templates used by List Manager screens
 | 
|---|
| 8 |  D ^DVBAONIT ;calls the onits to set up the List Manager screens/actions
 | 
|---|
| 9 |  D REINDAC^DVBAPST1
 | 
|---|
| 10 |  D REINDAF^DVBAPST1
 | 
|---|
| 11 |  D REINDAE^DVBAPST1
 | 
|---|
| 12 | EN12 D ^DVBAPOPU ;populates various global information
 | 
|---|
| 13 | EN14 D ^DVBAPOP2 ;populates the pointer field of 396.6
 | 
|---|
| 14 | EN11 D EN^DVBAPADD ;adds new disability conditions
 | 
|---|
| 15 | EN10 D ^DVBAORPH ;adds orphan exams.
 | 
|---|
| 16 | EN1 K STOP
 | 
|---|
| 17 |  D CHECK ; checks if pre init ran ok.
 | 
|---|
| 18 |  I $D(STOP) D SE G MAIL ;stops if pre init did not run ok.
 | 
|---|
| 19 | EN2 D EN^DVBAPLNG ;updates the long description of file 31.
 | 
|---|
| 20 | EN3 K STOP
 | 
|---|
| 21 |  D EN^DVBAPLL ;updates the local lookup file with file 31.
 | 
|---|
| 22 |  I $D(STOP) D SE1 G MAIL ;stops if problems adding to Local Lookup file.
 | 
|---|
| 23 |  D ORPHAN^DVBAPCXR
 | 
|---|
| 24 | EN4 ;;;D EN^DVBAPSHT ;enters the short cuts into the MTLU files. (DVBAPH1-99)
 | 
|---|
| 25 | EN5 D EN^DVBAPKY ;enters the keywords into the MTLU files. (DVBAPK1-99)
 | 
|---|
| 26 | EN13 D EN^DVBAPOKY ;enters the orphan keywords into the MTLU files. (DVBAPOK1)
 | 
|---|
| 27 | EN6 D EN^DVBAPSYN ;enters the synonyms into the MTLU files. (DVBAPS1-99)
 | 
|---|
| 28 | EN7 D EN^DVBAPBDY ;enters the disability codes into the body system file. (DVBAPB1-99)
 | 
|---|
| 29 | EN8 D EN^DVBAPWKS ;enters the disability codes into the AMIE worksheets. (DVBAPW1-99)
 | 
|---|
| 30 |  D FINISHED ;prints out a completed message
 | 
|---|
| 31 | MAIL S V3=$$MAL($J) ;builds and sends the mail message from the post init running
 | 
|---|
| 32 |  D EXIT^DVBAUTL1
 | 
|---|
| 33 |  Q
 | 
|---|
| 34 |  ;
 | 
|---|
| 35 | FINISHED ;
 | 
|---|
| 36 |  N VAR
 | 
|---|
| 37 |  S VAR="The Post-Init has completed."
 | 
|---|
| 38 |  W *7,!!!,VAR
 | 
|---|
| 39 |  D BUMP(VAR)
 | 
|---|
| 40 |  Q
 | 
|---|
| 41 |  ;
 | 
|---|
| 42 | CHECK ;checks for the 'post' node to see if the pre init ran ok.
 | 
|---|
| 43 |  I '$D(^DVB(396.1,1,"POST")) S STOP=1 Q
 | 
|---|
| 44 |  I ^DVB(396.1,1,"POST")']"" S STOP=1 Q
 | 
|---|
| 45 |  Q
 | 
|---|
| 46 | MAL(V2) ;builds a mail message and sends to the DUZ defined.  v2 must be the
 | 
|---|
| 47 |  ;$J from the job of the post init.
 | 
|---|
| 48 |  ;
 | 
|---|
| 49 |  N LNE,LNCNT
 | 
|---|
| 50 |  S XMDUZ="AMIE POST INIT"
 | 
|---|
| 51 |  S XMSUB="AMIE v2.7 install results"
 | 
|---|
| 52 |  D XMZ^XMA2 ;** Get message number
 | 
|---|
| 53 |  I XMZ'>0 DO
 | 
|---|
| 54 |  .W !!,"Mail Message containing Error Log has failed!",!
 | 
|---|
| 55 |  .W "Errors contained in ^TMP(""DVBA"","_V2_") global.",!
 | 
|---|
| 56 |  .W "Investigate this global to determine any existing problems."
 | 
|---|
| 57 |  .W !!
 | 
|---|
| 58 |  I XMZ>0 DO
 | 
|---|
| 59 |  .F LNE=0:0 S LNE=$O(^TMP("DVBA",V2,LNE)) Q:'LNE  DO
 | 
|---|
| 60 |  ..S ^XMB(3.9,XMZ,2,LNE,0)=(^TMP("DVBA",V2,LNE)),LNCNT=LNE
 | 
|---|
| 61 |  .S ^XMB(3.9,XMZ,2,0)="^3.92A^"_LNCNT_"^"_LNCNT_"^"_DT
 | 
|---|
| 62 |  .K XMDUN
 | 
|---|
| 63 |  .S (XMY(DUZ),XMY(.5))=""
 | 
|---|
| 64 |  .D ENT1^XMD
 | 
|---|
| 65 |  .W !!,"Mail message containing Error Log has been sent.",!
 | 
|---|
| 66 |  .W "Check your mail to see this log.",!!
 | 
|---|
| 67 |  .K ^TMP("DVBA",V2)
 | 
|---|
| 68 |  Q 1
 | 
|---|
| 69 |  ;
 | 
|---|
| 70 | SET ;set necessary local variables
 | 
|---|
| 71 |  S CNT=1
 | 
|---|
| 72 |  Q
 | 
|---|
| 73 |  ;
 | 
|---|
| 74 | SE S VAR="The pre-init found a problem in the version of MTLU and KERNEL."
 | 
|---|
| 75 |  W !!,VAR D BUMPBLK,BUMP(VAR)
 | 
|---|
| 76 |  S VAR="Please review and correct.  See install guide for further details."
 | 
|---|
| 77 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 78 |  S VAR="No updates have occurred to the following files:"
 | 
|---|
| 79 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 80 |  S VAR="      Local Lookup"
 | 
|---|
| 81 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 82 |  S VAR="      Local keyword"
 | 
|---|
| 83 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 84 |  S VAR="      Local Synonym"
 | 
|---|
| 85 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 86 |  ;;;S VAR="      Local Shortcut"
 | 
|---|
| 87 |  ;;;W !,VAR D BUMP(VAR)
 | 
|---|
| 88 |  S VAR="      2507 Body System"
 | 
|---|
| 89 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 90 |  S VAR="      AMIE Exam file."
 | 
|---|
| 91 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 92 |  S VAR="      Long Descriptions of the Disability Condition file."
 | 
|---|
| 93 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 94 |  Q
 | 
|---|
| 95 |  ;
 | 
|---|
| 96 | SE1 ;
 | 
|---|
| 97 |  S VAR="The post init could not add to the Local Lookup file."
 | 
|---|
| 98 |  W !!,VAR D BUMPBLK,BUMP(VAR)
 | 
|---|
| 99 |  S VAR="No updates have occurred to the following files:"
 | 
|---|
| 100 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 101 |  S VAR="      Local keyword"
 | 
|---|
| 102 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 103 |  S VAR="      Local Synonym"
 | 
|---|
| 104 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 105 |  S VAR="      Local Shortcut"
 | 
|---|
| 106 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 107 |  S VAR="      2507 Body System"
 | 
|---|
| 108 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 109 |  S VAR="      AMIE Exam file."
 | 
|---|
| 110 |  W !,VAR D BUMP(VAR)
 | 
|---|
| 111 |  Q
 | 
|---|
| 112 |  ;
 | 
|---|
| 113 | BUMP(V1) ;adds the entry and bumps the general counter.
 | 
|---|
| 114 |  S ^TMP("DVBA",$J,CNT)=V1
 | 
|---|
| 115 |  S CNT=CNT+1
 | 
|---|
| 116 |  Q
 | 
|---|
| 117 |  ;
 | 
|---|
| 118 | BUMPBLK ;adds a blank line to the array
 | 
|---|
| 119 |  S ^TMP("DVBA",$J,CNT)=""
 | 
|---|
| 120 |  S CNT=CNT+1
 | 
|---|
| 121 |  Q
 | 
|---|
| 122 |  ;
 | 
|---|
| 123 | OPEN F LP3=1:1 S LP4=$T(OPT+LP3) Q:LP4'[";;"  S LP4=$P(LP4,";;",2) DO
 | 
|---|
| 124 |  .S DIC="^DIC(19,",DIC(0)="MZ",X=LP4
 | 
|---|
| 125 |  .D ^DIC
 | 
|---|
| 126 |  .K DIC
 | 
|---|
| 127 |  .I Y<0 D ERR Q
 | 
|---|
| 128 |  .I Y>0 DO
 | 
|---|
| 129 |  ..S DIE="^DIC(19,",DIC(0)="MZ",DA=+Y,DR="2///@"
 | 
|---|
| 130 |  ..D ^DIE
 | 
|---|
| 131 |  ..W !,LP4," Now in order!"
 | 
|---|
| 132 |  ..K DIE,DIC,VAR,DR
 | 
|---|
| 133 |  ..Q
 | 
|---|
| 134 |  .K Y
 | 
|---|
| 135 |  .Q
 | 
|---|
| 136 |  K DIC,DIE,X,Y,DA,DR
 | 
|---|
| 137 |  S DIC="^ORD(101,",DIC(0)="MZ",X="DVBA C&P SCHD EVENT"
 | 
|---|
| 138 |  D ^DIC
 | 
|---|
| 139 |  K DIC
 | 
|---|
| 140 |  I Y<0 D ERR
 | 
|---|
| 141 |  I Y>0 DO
 | 
|---|
| 142 |  .S DIE="^ORD(101,",DIC(0)="MZ",DA=+Y,DR="2///@"
 | 
|---|
| 143 |  .D ^DIE
 | 
|---|
| 144 |  .W !,"DVBA C&P SCHD EVENT Now in order!"
 | 
|---|
| 145 |  K DIC,DIE,X,Y,LP3,LP4,DA,DR
 | 
|---|
| 146 |  Q
 | 
|---|
| 147 |  ;
 | 
|---|
| 148 | ERR ;
 | 
|---|
| 149 |  W "Could not find menu option ",X," NOT opened!"
 | 
|---|
| 150 |  Q
 | 
|---|
| 151 |  ;
 | 
|---|
| 152 | OPT ;
 | 
|---|
| 153 |  ;;DVBA MEDICAL ADM 7131 MENU
 | 
|---|
| 154 |  ;;DVBA REGIONAL OFFICE MENU
 | 
|---|
| 155 |  ;;DVBA C PROCESS MAIL MESSAGE
 | 
|---|
| 156 |  ;;DVBA C PHYSICIANS GUIDE
 | 
|---|
| 157 |  ;
 | 
|---|