subroutine speech(string) ! SPEECH SUBROUTINE SPEECH CESR.SPEECH SBP 98.02.19 !tpl call speech(string) ! subroutine to make speech synthesizer talk ! string=up to 120 characters implicit none ! ! character(*) string #if defined (CESR_VMS) include '($foriosdef)' character strh*120,stripstr*120,ts*23,lineout*73 ! integer year, day_of_year, slen, lencc,ls character(8) yyyy_ddd character(40) file_name character(10) topiclabel(1) integer ialr !alarm number in sentry character(4) chrstr*4,pname*3,logout*1 integer(4) ios,lun,lunget,lunsave,lun_common,nchar,line integer highsave,widesave,junk data line /0/ common /l/logout,pname common /luncom/ lun_common,chrstr common /file_log_n/ ialr common /file_log_c/ topiclabel ! nchar=lencc(string) !passed length call str$upcase(strh,string) ! buffer character input lun=lunget() !Get first free disk unit number at or above 30 open(unit=lun,name='SAY1:',status='unknown',iostat=ios,err=222) write(lun,2,iostat=ios,err=111) strh(1:nchar),char(10) 2 format(1x,a,a) 111 close(unit=lun) if(ios /= 0) then !INTERPRET ERROR call lib$signal(%val(ios)) ios=0 endif ! if(logout == 'Y') then !remove cpumatch requirement call csr_tstamp(ts) call stripbells(strh, stripstr) ! Log it in a file slen = lenCC(stripstr) call julian(year, day_of_year) write(yyyy_ddd, 400) year, day_of_year 400 format(i4.4,'_',i3.3) file_name = '[cesr.sentry.logfiles]senlog.'//yyyy_ddd lun = lunget() !get unit number for file output open(lun,file=file_name,status='unknown',access='append',err=200) if((pname(1:3) == 'SEN') .and. (ialr > 0)) then write(lun, '(x,a,x,a3,x,i4,x,a10,x,a)') & ts(13:20), pname(1:3),ialr,topiclabel(ialr),stripstr(1:slen) else write(lun, '(x,a,x,a3,x,a)') & ts(13:20),pname(1:3),stripstr(1:slen) endif close(lun) 200 continue !in case of open error ls=min(nchar,54) if(line < 1) line=1 lineout=' ' write(lineout,500) pname,ts(1:7)//ts(10:17),stripstr(1:ls) 500 format('x',a3,a,a) line=mod(line,28)+1 endif return 222 print *,' SPEECH COULDNT OPEN UNIT FOR OUTPUT ' #else call system('$CESR_ONLINE/acc_control/bin/speech_connect.pl "' //string//'"') #endif return end