diff --git a/tecs/coc_server.c b/tecs/coc_server.c index f744028..505049f 100644 --- a/tecs/coc_server.c +++ b/tecs/coc_server.c @@ -243,9 +243,14 @@ int CocPutThisVar(CocVar *var, void *base, StrBuf *buf, int separator) { int CocGetVar(const char *name, StrBuf *buf, int separator) { CocVar *var; void *base; - + static char msg[128]; + var=CocFindVar(name, &base); - if (var==NULL) ERR_MSG("undefined variable"); + if (var==NULL) { + str_copy(msg, "undefined variable ; "); + str_append(msg, name); + ERR_MSG(msg); + } ERR_I(CocGetThisVar(var, base, buf, separator)); return(0); OnError: str_copy(err_name, name); ErrTxt(err_name,0); return(-1); @@ -277,11 +282,11 @@ void CocFreeVarList(void) { char *CocReadVars(char *str, char stop){ int i, l; - char *eql, *cr, buf[80]; + char *eql, *cr, buf[256]; StrBuf sbuf; /* interprete variables until stop character appeares */ - i=sscanf(str, "%79s%n", buf, &l); + i=sscanf(str, "%255s%n", buf, &l); while (i>0 && buf[0]!=stop) { if (buf[0]=='!') { cr=strchr(str, '\n'); @@ -293,7 +298,7 @@ char *CocReadVars(char *str, char stop){ *eql='\0'; if (eql[1] == '\'' || eql[1]== '"') { eql=strchr(str, '='); - StrNLink(&sbuf, eql+1, 80); + StrNLink(&sbuf, eql+1, 256); ERR_I(CocGetVar(buf, &sbuf, StrNONE)); str = sbuf.buf + sbuf.rdpos; } else { @@ -302,7 +307,7 @@ char *CocReadVars(char *str, char stop){ ERR_I(CocGetVar(buf, &sbuf, ' ')); } } - i=sscanf(str, "%79s%n", buf, &l); + i=sscanf(str, "%255s%n", buf, &l); } return str; OnError: return NULL; diff --git a/tecs/conv.f b/tecs/conv.f new file mode 100644 index 0000000..40d17f1 --- /dev/null +++ b/tecs/conv.f @@ -0,0 +1,735 @@ + program conv + + include 'conv.inc' + + logical init + integer i,j,l,lin,iostat + character*128 line + character*2048 input + + data lun/0/,pos/0/,nlist/0/ + + path=' ' + lp=0 + verbose=.false. + call sys_get_cmdpar(input, l) + if (input .eq. ' ') then + verbose=.true. + print '(a,$)', + 1' File(s) (separated with space): ' + read(*,'(a)',end=99) input + if (input .eq. ' ') goto 99 + endif + i=index(input, '-p') + if (i .ne. 0) then ! first path option valid from start + j=index(input(i+1:), ' ') + call str_trim(path, input(i+2:i+j), lp) + endif + i=0 + do while (input(i+1:) .ne. ' ') + j=index(input(i+1:), ' ') + if (j .le. 1) then + i=i+1 + else if (input(i+1:i+2) .eq. '-p') then + call str_trim(path, input(i+3:i+j), lp) + i=i+j + else if (input(i+1:i+1) .eq. '-') then + print *,'unknown option: ',input(i+1:i+j) + i=i+j + else + call str_trim(file, input(i+1:i+j), lf) + i=i+j + if (verbose) print * + open(1,name=file(1:lf),status='old',iostat=iostat) + if (iostat .ne. 0) then + if (verbose) then + print *,'can not open ',file(1:lf) + print "(x,60('-'))" + endif + nlist=nlist+1 + list(nlist)='can not open '//file(1:lf) + else + lin=0 + do + call lsc_errinit(1) ! 1=lun + call lsc_convert_table(lin) + if (lin .lt. 0) goto 19 + if (verbose) print "(x,60('-'))" + enddo +19 continue + close(1) + endif + endif + enddo + + do i=1,nlist + call str_trim(list(i), list(i), l) + print *,list(i)(1:l) + enddo + +99 continue + end + + + subroutine pack(line, l, x, y, offset, m) + character line*(*) + integer l, offset, m + real x(m), y(m) + + integer j,p + + p=0 + do j=1,m + call str_append(line, p, '#0,') + call cvt_real_str(line(p+1:), l, 1.0*(offset+j), 1, 0, 6, 3) + p=p+l + call str_append(line, p, ':') + call cvt_real_str(line(p+1:), l, x(j), 1, 0, 6, 3) + p=p+l + call str_append(line, p, ',') + call cvt_real_str(line(p+1:), l, y(j), 1, 0, 6, 3) + p=p+l + call str_append(line, p, ';') + enddo + line(p:p)=' ' + l=p-1 + end + + + subroutine lsc_convert_table(lin) + + implicit none + include 'conv.inc' + + integer lin + + integer ntypes,nvolts, namps + parameter (ntypes=12, nvolts=12, namps=12) + integer np + + real x(200), y(200), ex, ey + integer i,j,l,p,li,crc,form,iostat + + character name*15, sensor*10, header*64, line*128, old*128, intype*16 + character crcmp*3, filnam*128, cfgdir*128 + character c40*40/'0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ$+-&'/ + integer unit, stype, excit, irange, coef, iunit, stdcurv + ! codes + character types(0:ntypes)*12/'Special','Si Diode','GaAlAs Diode' + 1 ,'Pt250 Ohm','Pt500 Ohm','Pt2500 Ohm','RhFe','C-Glass' + 1 ,'Cernox','RuOx','Ge','Cap','Tc'/ + integer nunits + parameter (nunits=3) + character units(nunits)*5/'mV','V','Ohm'/ + integer nexcits + parameter (nexcits=12) + character excits(0:nexcits)*8/'Off','30nA','100nA','300nA','1uA','3uA' + 1 ,'10uA','30uA','100uA','300uA','1mA','10mV','1mV'/ + integer nforms + parameter (nforms=5) + character forms(nforms)*6/'ill','ill','lin','log','loglog'/ + + ! default values + integer defu(ntypes)/ 1, 1, 2, 2,2, 2, 2, 2, 2, 2, 3, 1/ ! unit + integer defe(ntypes)/ 6, 6,10,10,8,10,11,11,11,12, 0, 0/ ! excit + integer defr(ntypes)/11,12, 8, 9,8, 8, 4, 4, 4, 1, 1, 6/ ! range + integer defc(ntypes)/ 1, 1, 2, 2,2, 2, 1, 1, 1, 1, 2, 2/ ! coef + real volts(nvolts)/1E-3,2.5E-3,5E-3,1E-2,2.5E-2,5E-2 + 1 ,1E-1,2.5E-1,5E-1,1E-0,2.5E-0,5E-0/ + real amps(namps)/3E-8,1E-7,3E-7,1E-6,3E-6,1E-5,3E-5,1E-4,3E-4,1E-3 + 1 ,3E-8,3E-8/ ! minimal values are for voltage excitation + integer stdmax + parameter (stdmax=10) + character*40 stdhdr(stdmax)/ + 1 'DT-470 ,Standard ,2,+475.000E+0,1', + 1 'DT-500-D ,Standard ,2,+365.000E+0,1', + 1 'DT-500-E1 ,Standard ,2,+330.000E+0,1', + 1 'PT-100 ,Standard ,3,+800.000E+0,2', + 1 'PT-1000 ,Standard ,3,+800.000E+0,2', + 1 'TYPE K ,Standard ,1,+1645.00E+0,2', + 1 'TYPE E ,Standard ,1,+1188.50E+0,2', + 1 'TYPE T ,Standard ,1,+673.000E+0,2', + 1 'CrAuFe.03%,Standard ,1,+500.000E+0,2', + 1 'CrAuFe.07%,Standard ,1,+610.000E+0,2'/ + integer stdtype(stdmax)/1,1,1,4,5,12,12,12,12,12/ + + real tlim, range, xmax, ymax, curr, rl + + real x1,x2,xi,y1,y2,yi,sum,sum1,sum2,mum,mum1,mum2,d,at,at1,at2 + logical eof, first, inverted + + ! functions + integer lsc_getno + external lsc_getno, pack + + first=.true. + eof=.false. + np=0 + name=' ' + sensor=' ' + unit=0 + tlim=0 + stype=0 + excit=0 + form=0 + range=-1.0 + stdcurv=0 +1 read(1,'(a)',err=97,end=97) line + call str_trim(line, line, l) + lin=lin+1 + call str_first_nonblank(line, i) + if (i .eq. 0) goto 1 + if (line(i:i) .eq. '!') goto 1 + first=.false. + call str_upcase(line(1:l),line(i:l)) + i=index(line(1:l),'!') + if (i .ne. 0) line=line(1:i-1) + call str_trim(line(1:l),line(1:l),l) + if (line(1:4) .ne. 'CURV') then + i=index(line,'=') + if (i .eq. 0) then + call lsc_error(lin, 'missing "="') + goto 1 + endif + if (i .eq. l) then + call lsc_error(lin, 'missing value') + goto 1 + endif + call str_first_nonblank(line(i+1:l), j) + i=i+j + if (line(1:4) .eq. 'SENS') then + sensor=line(i:l) + name=sensor + elseif (line(1:4) .eq. 'UNIT') then + unit=lsc_getno(units, nunits, line(i:l)) + if (unit .le. 0) call lsc_error(lin, 'illegal unit') + elseif (line(1:4) .eq. 'TLIM') then + read(line(i:l),*,err=92,end=92) tlim + elseif (line(1:4) .eq. 'TYPE') then + stype=lsc_getno(types, ntypes+1, line(i:l))-1 + if (stype .lt. 0) call lsc_error(lin, 'illegal type') + elseif (line(1:4) .eq. 'EXCI') then + call str_substitute(line(1:8),line(i:l),' ',char(0)) + excit=lsc_getno(excits, nexcits, line(1:8))-1 + if (excit .lt. 0) call lsc_error(lin, 'illegal excitation') + elseif (line(1:4) .eq. 'RANG') then + read(line(i:l),*,err=93,end=93) range + if (range .lt. 0) goto 93 + elseif (line(1:4) .eq. 'FORM') then + form=lsc_getno(forms, nforms, line(i:l)) + if (form .lt. 3) call lsc_error(lin, 'illegal format') + else + call lsc_error(lin, 'unknown parameter name') + endif + goto 1 + endif + if (sensor .eq. ' ') call lsc_error(lin, 'missing sensor name') + i=index(line,'=') + if (i .ne. 0) then + read(line(i+1:l), *, err=2,end=2) stdcurv +2 continue + if (stdcurv .lt. 0 .or. stdcurv .gt. stdmax) then + call lsc_error(lin, 'illegal standard curve no.') + goto 101 + endif + if (unit .ne. 0 .or. stype .ne. 0 .or. + 1 excit .ne. 0 .or. tlim .ne. 0) then + if (verbose) then + print *,'Warning: all parameters except "sens"' + 1 ,', "range" and "curv" are ignored',char(7) + endif + errstat=max(errstat,1) + endif + line=stdhdr(stdcurv) + i=index(line, ',') + if (i .eq. 0) goto 96 ! illegal stdhdr + j=index(line(i+1:), ',') + if (j .eq. 0) goto 96 ! illegal stdhdr + + read(line(i+j+1:), *, err=96, end=96) unit, ymax, coef + stype=stdtype(stdcurv) +! if (range .lt. 0) then +! range=stdrange(stdcurv) +! end if + xmax=0 + excit=0 + tlim=0 + goto 100 + endif + if (line(5:) .ne. ' ') then + call lsc_error(lin, 'missing "="') + goto 101 + end if + ! user curve + if (unit .eq. 0) call lsc_error(lin, 'missing unit') + if (stype .eq. 0) then + if (excit .le. 0) call lsc_error(lin, 'missing excitation') + if (range .lt. 0) call lsc_error(lin, 'missing range') + else + if (excit .eq. 0) excit=defe(stype) + endif +3 np=np+1 + read(1,'(a)',err=98,end=98) line + lin=lin+1 + if (line .eq. ' ') goto 9 + read(line, *, err=94, end=94) x(np), y(np) + goto 3 + + +92 call lsc_error(lin,'illegal tlim') + goto 1 +93 call lsc_error(lin,'illegal range') + goto 1 +94 call lsc_error(lin,'illegal datapoint') + goto 101 +95 call lsc_error(lin,'illegal table no') + goto 1 +96 stop 'internal error: illegal stdhdr' +97 if (.not. first) then + call lsc_error(lin,'unexpected end of file') + endif + lin=-1 + RETURN +98 eof=.true. + +9 np=np-1 ! point (np) is not valid + + if (np .lt. 2) call lsc_error(lin+np, 'not enough data points') + if (x(np) .lt. x(1)) then ! inverse order + j=np + do i=1,np/2 + ex=x(i) + ey=y(i) + x(i)=x(j) + y(i)=y(j) + x(j)=ex + y(j)=ey + j=j-1 + enddo + inverted=.true. + else + inverted=.false. + endif + do i=2,np + if (x(i) .le. x(i-1)) then + j=i + if (inverted) j=np-i+1 + call lsc_error(lin+j, 'table not ordered') + goto 101 + endif + enddo + xmax=x(np) + if (y(np) .lt. y(1)) then + coef=1 + do i=2,np + if (y(i) .ge. y(i-1)) then + j=i + if (inverted) j=np-i+1 + call lsc_error(lin+j, 'table not ordered') + goto 101 + endif + enddo + ymax=y(1) + else + coef=2 + do i=2,np + if (y(i) .le. y(i-1)) then + j=i + if (inverted) j=np-i+1 + call lsc_error(lin+j, 'table not ordered') + goto 101 + endif + enddo + ymax=y(np) + endif +101 continue + do i=1,np + if (x(i) .eq. 0.0) then + j=i + if (inverted) j=np-i+1 + call lsc_error(lin+j, 'illegal sensor value') + endif + if (y(i) .le. 0.0) then + j=i + if (inverted) j=np-i+1 + call lsc_error(lin+j, 'illegal temperature') + endif + enddo + if (errstat .gt. 1) goto 999 + + sum=0 + sum1=0 + sum2=0 + mum=0 + mum1=0 + mum2=0 + do i=2,np-1 + xi=x(i) + x1=x(i-1) + x2=x(i+1) + yi=log(y(i)) + y1=y(i-1) + y2=y(i+1) + d=abs(yi-log(y1+(xi-x1)/(x2-x1)*(y2-y1))) + sum=sum+d*d + if (d .gt. mum) then + mum=d + at=y(i) + endif + xi=log(abs(xi)) + x1=log(abs(x1)) + x2=log(abs(x2)) + d=abs(yi-log(y1+(xi-x1)/(x2-x1)*(y2-y1))) + sum1=sum1+d*d + if (d .gt. mum1) then + mum1=d + at1=y(i) + endif + y1=log(y1) + y2=log(y2) + d=abs(yi-(y1+(xi-x1)/(x2-x1)*(y2-y1))) + sum2=sum2+d*d + if (d .gt. mum2) then + mum2=d + at2=y(i) + endif + enddo + if (np .gt. 2) then + sum=sqrt(sum/(np-1))*25 + sum1=sqrt(sum1/(np-1))*25 + sum2=sqrt(sum2/(np-1))*25 + + if (verbose) then + print '(x,a)','Interpolation accuracy mean worst at' + print '(13x,a,3(f8.2,a))','linear ',sum, '%',mum *25,'%',at,' K' + print '(13x,a,3(f8.2,a))','log/lin ',sum1,'%',mum1*25,'%',at1,' K' + print '(13x,a,3(f8.2,a))','log/log ',sum2,'%',mum2*25,'%',at2,' K' + endif + + if (unit .eq. 3) then + sum1=(sum1/sum)**2+(mum1/mum)**2 + sum2=(sum2/sum)**2+(mum2/mum)**2 + if (form .eq. 0 .and. (sum1 .lt. 1.0 .or. sum2 .lt. 1.0) + 1 .or. form .gt. 3) then + if (form .eq. 0 .and. sum2 .lt. sum1 .or. form .eq. 5) then + unit=5 + do i=1,np + y(i)=log10(y(i)) + enddo + else + unit=4 + endif + do i=1,np + x(i)=log10(x(i)) + enddo + endif + else + if (form .gt. 3 .and. verbose) + 1 print *,'FORM ignored (not unit Ohm)' + endif + endif + +100 continue + + if (unit .eq. 1) then ! check for mV / V consistency + if (xmax .gt. 990) then + unit=2 + do i=1,np + x(i)=x(i)/1000.0 + enddo + endif + xmax=xmax/1000.0 + range=range/1000.0 + elseif (unit .eq. 2) then + if (xmax .lt. 0.5) then + unit=1 + do i=1,np + x(i)=x(i)*1000.0 + enddo + endif + endif + if (range .eq. 0) range=xmax + if (tlim .eq. 0 .or. tlim .gt. ymax) tlim=ymax + irange=0 + if (range .gt. 0) then + if (unit .ge. 3) then ! Ohm + curr=amps(excit) + rl=range*curr ! convert Ohm to V + if (rl .gt. 5.0) then +! print *,'Warning: maximum range exceeded: ' +! 1 , range,'>',5/curr,' Ohm',char(7) +! errstat=max(errstat,1) + irange=12 + endif + else + rl=range ! V + endif + if (irange .eq. 0) then + if (stype.eq.12) then + j=6 + else + j=nvolts + end if + do i=1,j + if (rl .le. volts(i)) then + irange=i + goto 150 + endif + enddo +! print *,'Warning: maximum range exceeded: ', range,' > ',volts(j),' V',char(7) +! errstat=max(errstat,1) + irange=j +150 continue + if (excit .eq. 11) then ! 10 mV excit -> min. 10 mV range + if (irange .lt. 4) irange=4 + endif + endif + else + irange=defr(stype) + range=xmax + endif + if (stdcurv.eq.0) then + if (unit .ge. 3) then + if (range*amps(excit) .gt. volts(irange)) then + print *,'Warning: max. range exceeded: ' + 1 ,range,' > ',volts(irange)/amps(excit),' Ohm',char(7) + errstat=max(errstat,1) + endif + else if (range .gt. volts(irange)) then + print *,'Warning: max. range exceeded: ' + 1 ,range,' > ',volts(irange), ' V',char(7) + errstat=max(errstat,1) + endif + endif + + if (stype .gt. 0) then + if (excit .le. 0) excit=defe(stype) + if (irange .eq. 0) irange=defr(stype) + endif + if (verbose) then + print *,'Sensor type: ',types(stype) + print *,'Excitation: ',excits(excit) + if (unit .eq. 1) then + print *,'Sensor Range: ',volts(irange)*1000,' mV' + elseif (unit .eq. 2) then + print *,'Sensor Range: ',volts(irange),' V' + else + print *,'Sensor Range: ',volts(irange)/amps(excit),' Ohm' + if (unit .eq. 5) then + print *,'table double logarithmic' + elseif (unit .eq. 4) then + print *,'table logarithmic' + else + print *,'table linear' + endif + endif + if (coef .eq. 1) then + print *,'negative characteristic' + else + print *,'positive characteristic' + endif + print * + endif + + if (stype .eq. 0) then + if (unit .ge. 3) then + iunit=2 + else + iunit=1 + endif + else + if (unit .le. 2) then ! mV / V + iunit=1 + else ! Ohm + iunit=2 + endif + if (iunit .ne. defu(stype) .or. + 1 coef .ne. defc(stype) .or. + 1 excit .ne. defe(stype) .or. + 1 irange.ne. defr(stype)) then + if (stype .ne. 12) stype=0 + endif + endif + + + if (stype .eq. 12) then + l=5 + write (line(1:l), '(a,i1)') ',,,,',max(0,irange-5) + elseif (stype .eq. 0) then + l=14 + write (line(1:l), '(i2,4(a,i2.0))') + 1 stype,',',iunit,',',coef,',',excit,',',irange + else + l=2 + write(line(1:l), '(i2)') stype + endif + + call str_substitute(intype, line(1:l), ' ', char(0)) + call str_trim(intype, intype, li) + + if (tlim .gt. 1500) tlim=1500 + if (tlim .lt. 0) tlim=0 + + if (stdcurv.eq.0) then +! calculate crc of table + crc=0 + do i=1,np + call pack(line, l, x(i), y(i), i-1, 1) + call str_crc(crc, line(1:l)) + enddo + call str_crc_comp(crc, crcmp) + write (header, "(a,x,a,',',a,',',i1,',',f8.3,',',i1)") + 1 name(1:11), crcmp,sensor,unit,tlim,coef + else + crc=0 + header=stdhdr(stdcurv) + endif + + ! compare with old file + call str_trim(filnam, sensor, l) + call str_lowcase(filnam, filnam) + filnam(l+1:)='.crv' + if (path(1:lp) .ne. ' ') then + filnam=path(1:lp)//filnam + endif + open(unit=2, file=filnam, status='old', iostat=iostat) + if (iostat .ne. 0) goto 198 + read(2, '(a)',end=199) old + if (old .ne. header) goto 199 + read(2, '(a)', end=199) old + if (old .ne. intype) goto 199 + if (stdcurv .ne. 0) then + write(line, '(a, i2)') '$',stdcurv + read(2, '(a)', end=199) old + if (line .ne. old) goto 199 + read(2, '(a)', end=197) old ! goto end (o.k.) if no more line + goto 199 + endif + do i=1,np,ncolumn + read(2, '(a)', end=199) old + call pack(line, l, x(i), y(i), i-1, min(ncolumn,np-i+1)) + if (line .ne. old) goto 199 + enddo + read(2, '(a)', end=199) old + call pack(line, l, 0.0, 0.0, np, 1) + if (line .ne. old) goto 199 + read(2, '(a)', end=197) old ! goto end (o.k.) if no more line + goto 199 +197 close(2) + if (verbose) print *,'curve file has not changed: ',filnam + goto 200 +! goto 999 + +198 if (verbose) print *,'create new curve file: ',filnam + nlist=nlist+1 + list(nlist)='created '//filnam + goto 200 + +199 close(2) + if (verbose) print *,'modify curve file: ',filnam + nlist=nlist+1 + list(nlist)='modified '//filnam +200 continue + open(unit=2, file=filnam, status='unknown', iostat=iostat) + if (iostat .ne. 0) then + call str_trim(filnam, filnam, l) + print *,'can not open ',filnam(1:l) + nlist=nlist-1 + lin=-1 + return + endif + call str_trim(header, header, l) + write(2, '(a)') header(1:l) + write(2, '(a)') intype(1:li) + if (stdcurv .ne. 0) then + write(2, '(a,i2)') '$',stdcurv + else + do i=1,np,ncolumn + call pack(line, l, x(i), y(i), i-1, min(ncolumn,np-i+1)) + write(2,'(a)') line(1:l) + enddo + call pack(line, l, 0.0, 0.0, np, 1) + write(2,'(a)') line(1:l) + endif + close(2) +999 continue + if (errstat .gt. 0) then + if (name.eq.' ') name='' + nlist=nlist+1 + if (errstat .gt. 1) then + list(nlist)='error in '//file(1:lf)//', curve '//name + if (verbose) print *,'no curve file written' + lin=-1 + else + list(nlist)='warning in '//file(1:lf)//', curve '//name + endif + endif + if (eof) lin=-1 + return + end + + + integer function lsc_getno(list, n, name) + + integer n + character list(n)*(*), name*(*) + character str*32 + + integer i,l + + call str_trim(name, name, l) + l=min(l,len(str)) + do i=1,n + call str_upcase(str(1:l), list(i)) + if (name(1:l) .eq. str(1:l)) then + lsc_getno=i + RETURN + endif + enddo + lsc_getno=0 + end + + + subroutine lsc_errinit(lunit) + + include 'conv.inc' + + integer lunit + + lun=lunit + pos=0 + errstat=0 + end + + + subroutine lsc_error(lin, text) + + include 'conv.inc' + + integer lin + character text*(*) + + integer i,l + character line*132 + + if (pos .eq. 0) then + print * + endif + if (lin .gt. pos) then + rewind lun + do i=1,lin-1 + read(lun, '(a)', end=8) line + call str_trim(line, line, l) + if (i .gt. max(pos,lin-3)) then + print '(5x,a)',line(1:l) + endif + enddo + read(lun, '(a)', end=8) line + call str_trim(line, line, l) + print '(x,2a)','>>> ',line(1:l) +8 pos=lin + errstat=2 + endif + +9 print '(x,a)', text + end diff --git a/tecs/didi b/tecs/didi index 4dc4e53..30b7052 100755 --- a/tecs/didi +++ b/tecs/didi @@ -4,24 +4,34 @@ set what="$1" set where="$2" set destlist=( type@osf1 \ -AMOR@lnsa14:bin/ DMC@lnsa05:bin/ FOCUS@lnsa16:bin/ \ -HRPT@lnsa11:bin/ TRICS@lnsa18:bin/ \ -lnslib@lnsa15:bin/ \ +AMOR@lnsa14:tecs/ FOCUS@lnsa16:tecs/ TRICS@lnsa18:tecs/ \ +lnsg@lnsa15:tecs/ \ +alpha=/afs/psi.ch/project/sinq/tru64/stow/tecs/bin/ \ type@linux \ -zolliker@llc3:/afs/psi.ch/project/sinq/linux/bin/ \ -TASP@pc4478:tasp_sics/ \ -TOPSI@pc4120:topsi_sics/ SANS@pc3965:sans_sics/ SANS2@sans2:sans2_sics/ \ +linux=/afs/psi.ch/project/sinq/linux/stow/tecs/bin/ \ +TASP@pc4478:tecs/ DMC@pc4629:tecs/ HRPT@hrpt:tecs/ \ +MORPHEUS@pc4120:tecs/ SANS@pc3965:tecs/ SANS2@sans2:tecs/ \ +type@darwin \ +macosx=/afs/psi.ch/project/sinq/mac_os/stow/tecs/bin/ \ ) set dests="" set destl="" foreach dest ($destlist) + set ext="${dest:s/=/ /}" + set ext=($ext) + if ("$ext" != "$dest") then + set dest="$ext[2]" + set d="$ext[1]" + else + set d="" + endif set ext=${dest:s/@/ /} set ext=($ext) if ("$ext[1]" == type) then set type=$ext[2] else - set d=$ext[1] + if ("$d" == "") set d=$ext[1] if ($?type) then set t_$d=$type else @@ -29,7 +39,7 @@ foreach dest ($destlist) exit endif set d_$d=$dest - set dests=($dests $ext[1]) + set dests=($dests $d) endif end @@ -67,15 +77,16 @@ foreach dest ($where) alias get 'set d=$'"d_$dest;"'set t=$'"t_$dest" get foreach item ($what) + echo $item D $d T $t if ($item == cfg) then if ($makeit) then make config set makeit=0 endif echo tecs $d - rsync -e ssh -rCtv --delete-excluded $obj/tecs $d + rsync -e ssh -rCtv --delete-excluded $obj/cfg $d else if ("$t" == "$OSTYPE") then - echo $item $d + echo $item to $d rsync -e ssh -vt $obj/$item $d endif end diff --git a/tecs/inp/apd.cfg b/tecs/inp/apd.cfg new file mode 100644 index 0000000..d1849e7 --- /dev/null +++ b/tecs/inp/apd.cfg @@ -0,0 +1,5 @@ + sensA.type=m sensA.curve=mz020124 + sensB.type=s sensB.curve=r10409 + dev="APD closed cycle refrigerator (TriCS)" + tlimit=310 resist=40 maxPower=16 + prop=15 int=10 deriv=0 diff --git a/tecs/inp/apdl.cfg b/tecs/inp/apdl.cfg new file mode 100644 index 0000000..36b9255 --- /dev/null +++ b/tecs/inp/apdl.cfg @@ -0,0 +1,2 @@ + sensC.type=x + dev="APD auxilliary sensor" diff --git a/tecs/inp/c020415.inp b/tecs/inp/c020415.inp new file mode 100644 index 0000000..444dc4c --- /dev/null +++ b/tecs/inp/c020415.inp @@ -0,0 +1,109 @@ +sens=c020415 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=C ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +form=loglog +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +87 278.58 +87.7 273.38 +88.4 267.75 +89.1 261.75 +89.9 254.55 +90.7 247.11 +91.6 238.55 +92.6 228.96 +93.7 218.46 +95 206.33 +96.6 192.03 +98.9 173.02 +104 138.05 +106.2 125.83 +108.4 115.1 +110.6 105.67 +112.8 97.379 +115 90.068 +117.2 83.601 +119.4 77.863 +121.7 72.535 +124.1 67.603 +126.6 63.049 +129.1 59.004 +131.7 55.261 +134.4 51.8 +137.3 48.498 +140.3 45.466 +143.4 42.683 +147 39.828 +150 37.712 +154 35.206 +158 33.003 +162 31.056 +166 29.324 +170 27.775 +175 26.057 +180 24.543 +185 23.201 +191 21.781 +197 20.532 +203 19.429 +210 18.293 +217 17.293 +225 16.29 +233 15.409 +242 14.539 +251 13.775 +261 13.028 +272 12.31 +284 11.628 +297 10.985 +311 10.384 +326 9.8244 +342 9.3062 +360 8.8014 +379 8.3407 +400 7.9007 +423 7.4854 +448 7.0969 +475 6.736 +505 6.3915 +540 6.0487 +580 5.7176 +620 5.4367 +670 5.1397 +720 4.8893 +780 4.6356 +840 4.4212 +910 4.2092 +990 4.0054 +1080 3.8132 +1180 3.6344 +1300 3.456 +1440 3.2845 +1600 3.1239 +1780 2.9757 +1990 2.8344 +2240 2.6977 +2530 2.5697 +2900 2.4393 +3300 2.3271 +3800 2.2154 +4400 2.1099 +5100 2.0131 +6000 1.916 +7100 1.8247 +8400 1.7416 +10000 1.663 +12000 1.5879 +14600 1.5142 +18000 1.4427 +22000 1.3801 +27000 1.3216 +34000 1.2614 +43000 1.2054 +55000 1.1518 +71000 1.1009 +93000 1.0519 +124000 1.0041 +300000 0.75 + + diff --git a/tecs/inp/c030307.inp b/tecs/inp/c030307.inp new file mode 100644 index 0000000..7e7681f --- /dev/null +++ b/tecs/inp/c030307.inp @@ -0,0 +1,34 @@ +sens=c030307 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=C ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +100000 0.42 +15000 1.05 +8000 1.42 +4000 1.99 +2000 2.77 +1600 3.1 +1400 3.32 +1200 3.61 +1000 4.01 +900 4.28 +800 4.61 +700 5.05 +600 5.64 +500 6.5 +400 7.96 +300 10.81 +265 12.68 +228 15.77 +206 18.96 +191 21.67 +180 24.48 +171 27.3 +154 35.2 +142 45 +134 60 +130 70 +90 310 + + diff --git a/tecs/inp/c030311.inp b/tecs/inp/c030311.inp new file mode 100644 index 0000000..3ee2056 --- /dev/null +++ b/tecs/inp/c030311.inp @@ -0,0 +1,107 @@ +sens=c030311 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=C ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +94 331.07 +95.6 301.46 +98.2 258.68 +100.3 229.17 +102.1 207.24 +103.8 189.07 +105.4 173.97 +107 160.58 +108.6 148.68 +110.2 138.09 +111.9 128.07 +113.6 119.17 +115.3 111.22 +117.1 103.71 +118.9 97.013 +120.8 90.694 +122.8 84.763 +124.8 79.468 +126.9 74.498 +129.1 69.849 +131.4 65.511 +133.8 61.473 +136.3 57.722 +138.9 54.241 +141.7 50.902 +144.6 47.825 +147.6 44.991 +151 42.141 +154 39.899 +158 37.247 +162 34.917 +166 32.859 +170 31.029 +174 29.394 +179 27.58 +184 25.982 +189 24.565 +195 23.065 +201 21.747 +207 20.581 +214 19.38 +221 18.324 +229 17.263 +237 16.331 +246 15.411 +255 14.602 +265 13.812 +276 13.051 +288 12.328 +301 11.646 +315 11.009 +330 10.416 +346 9.8657 +363 9.3576 +382 8.8648 +403 8.3941 +426 7.9501 +451 7.5349 +478 7.1492 +508 6.7812 +540 6.4443 +580 6.0862 +620 5.7828 +660 5.5221 +710 5.2433 +770 4.9621 +830 4.7255 +900 4.4923 +980 4.2688 +1070 4.0588 +1170 3.8641 +1280 3.685 +1410 3.5088 +1560 3.3408 +1730 3.184 +1930 3.0326 +2160 2.8904 +2430 2.7546 +2700 2.6432 +3100 2.5095 +3500 2.4024 +4000 2.2943 +4600 2.1908 +5300 2.0948 +6200 1.9976 +7300 1.9054 +8600 1.8209 +10300 1.736 +12400 1.6564 +15000 1.582 +18000 1.5166 +22000 1.4505 +27000 1.3888 +34000 1.3252 +43000 1.2661 +55000 1.2096 +71000 1.156 +93000 1.1043 +123000 1.0554 +170000 1.0039 + + diff --git a/tecs/inp/c1.inp b/tecs/inp/c1.inp new file mode 100644 index 0000000..ec5dc2b --- /dev/null +++ b/tecs/inp/c1.inp @@ -0,0 +1,74 @@ +sens=c1 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=C ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=100uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +range=333333 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +999999 1.00 +272100 1.03 +172977 1.12 +112093 1.21 +74662 1.31 +50854.6 1.42 +35305.6 1.53 +25003.3 1.66 +18090 1.80 +13356.3 1.94 +10053.4 2.10 +7697.32 2.28 +5986.53 2.47 +4724.73 2.67 +3784.47 2.89 +3069.36 3.13 +2518.99 3.39 +2091.39 3.67 +1755.38 3.97 +1487.08 4.30 +1273.44 4.66 +1101.81 5.04 +960.139 5.46 +844.434 5.91 +747.186 6.40 +665.698 6.93 +596.693 7.50 +539.771 8.12 +490.76 8.79 +448.006 9.52 +412.762 10.30 +380.541 11.15 +352.62 12.08 +328.321 13.07 +306.25 14.16 +288.286 15.32 +271.424 16.59 +256.195 17.96 +242.787 19.45 +230.54 21.05 +219.532 22.79 +209.575 24.68 +200.383 26.72 +192.065 28.93 +184.48 31.32 +177.432 33.91 +171.256 36.71 +165.012 39.74 +159.59 43.03 +154.324 46.58 +149.365 50.43 +144.78 54.60 +139.937 60.00 +133.722 68.50 +128.791 77.30 +123.897 88.60 +119.039 103.50 +114.217 124.20 +109.43 154.70 +107.05 176.00 +104.678 203.80 +102.316 240.90 +100.237 287.70 +99.6953 300.00 +90 310 + + diff --git a/tecs/inp/c12900.inp b/tecs/inp/c12900.inp new file mode 100644 index 0000000..4136dde --- /dev/null +++ b/tecs/inp/c12900.inp @@ -0,0 +1,87 @@ +sens=c12900 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +type=C ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +range=800000 +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +1012550 1.20497 +546701 1.30399 +312268 1.40162 +114040 1.60623 +51444 1.80617 +26719.2 2.00576 +15435.5 2.20444 +9602.53 2.40494 +6397.94 2.60259 +4489.76 2.79906 +3219.32 3.00654 +2461.2 3.19842 +1897.64 3.40336 +1502.24 3.6079 +1230.54 3.80022 +1012.12 4.00621 +841.192 4.22067 +637.469 4.58241 +489.918 4.97865 +367.931 5.4844 +264.075 6.1965 +195.15 7.00194 +144.285 8.00824 +113.298 9.01723 +92.4347 10.0564 +78.2614 11.0715 +67.9423 12.0828 +60.1888 13.0842 +54.1233 14.0857 +49.3103 15.0747 +45.3379 16.0757 +42.0996 17.0531 +39.3391 18.0384 +36.9796 19.0217 +34.9151 20.0177 +32.9926 21.0862 +30.5452 22.6981 +28.6209 24.2233 +26.9266 25.8078 +25.4992 27.3598 +24.2509 28.9385 +23.0398 30.7055 +21.8009 32.8076 +20.3302 35.8012 +19.1087 38.8327 +18.0816 41.8826 +17.2216 44.8952 +16.4751 47.9305 +16.0348 49.938 +15.0984 54.8967 +14.3247 59.8577 +13.6715 64.8573 +13.1178 69.8244 +12.636 74.8078 +12.2143 79.7839 +11.8399 84.8244 +11.5105 89.8012 +11.2102 94.8438 +10.942 99.8132 +10.4716 109.826 +10.0743 119.846 +9.73462 129.833 +9.43818 139.857 +9.17665 149.828 +8.94393 159.859 +8.73457 169.862 +8.54545 179.864 +8.37336 189.826 +8.21397 199.879 +8.06779 209.858 +7.93285 219.86 +7.80698 229.843 +7.68873 239.855 +7.57774 249.851 +7.47313 259.852 +7.37448 269.854 +7.28072 279.868 +7.19198 289.881 +7.10731 299.874 +7.02683 309.874 + + diff --git a/tecs/inp/c17844.inp b/tecs/inp/c17844.inp new file mode 100644 index 0000000..bd1ab0a --- /dev/null +++ b/tecs/inp/c17844.inp @@ -0,0 +1,93 @@ +sens=c17844 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=C ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +range=1500000 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +1600000.000 1.1 +970035.6003 1.20121 +505060.7083 1.30296 +338710.9339 1.3989 +120001.056 1.60059 +51903.02439 1.80271 +14804.70375 2.20221 +9145.783794 2.39764 +5892.856091 2.60368 +4098.343859 2.798 +2949.617582 2.99639 +2170.79842 3.20492 +1650.889664 3.41307 +1316.149683 3.60371 +1062.659731 3.80091 +877.1929825 3.99488 +724.6376812 4.20335 +465.1162791 4.77734 +358.4229391 5.17319 +274.7252747 5.65299 +201.2072435 6.31596 +150.6024096 7.06791 +111.1111111 8.04676 +85.17887564 9.11986 +70.92198582 10.0142 +59.9880024 10.982 +51.25576627 12.0445 +45.74565416 12.9337 +41.05090312 13.8897 +37.09198813 14.9045 +33.99048266 15.8801 +31.56565657 16.7995 +29.43773918 17.7499 +27.5862069 18.7256 +25.96728123 19.7153 +24.27184466 20.9274 +22.37637055 22.5615 +20.90301003 24.0999 +19.5427008 25.7898 +18.43657817 27.4256 +17.49475157 29.0442 +16.50709805 31.0254 +15.64945227 33.0448 +14.53911021 36.2007 +13.70801919 39.0782 +12.97690112 42.0868 +12.39157373 44.9234 +11.84553423 47.9836 +11.52339249 50.031 +10.84245907 55.0141 +10.28806584 59.9738 +9.811616954 65.062 +9.409993413 70.0969 +9.071117562 75.0211 +8.765778401 80.058 +8.494733265 85.1505 +8.25968448 90.1304 +8.048289738 95.0917 +7.840677435 100.499 +7.505817008 110.505 +7.22230247 120.57 +6.97934115 130.684 +6.770022341 140.651 +6.582411796 150.794 +6.416014372 160.824 +6.26605677 170.879 +6.130456106 181.012 +6.007810153 191.033 +5.895183635 201.141 +5.788376939 211.227 +5.691519636 221.232 +5.602554765 231.279 +5.518154729 241.451 +5.437442227 251.53 +5.361642807 261.574 +5.291285253 272.626 +5.2227503 281.619 +5.158095631 291.746 +5.096060745 301.885 +5.03626108 311.966 +5.007260528 317.011 +4.979831682 322.01 +4.947555907 328.015 +4.927322 331.981 + + diff --git a/tecs/inp/c2.inp b/tecs/inp/c2.inp new file mode 100644 index 0000000..a83e1bb --- /dev/null +++ b/tecs/inp/c2.inp @@ -0,0 +1,83 @@ +sens=c2 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=C ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=100uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +179323 0.607 +112538 0.749 +75275 0.891 +52838 1.033 +38592 1.176 +29156 1.318 +22674 1.460 +18077 1.593 +14725 1.709 +10302 1.930 +8000 2.112 +7000 2.211 +6500 2.272 +6000 2.332 +5500 2.404 +5000 2.500 +4500 2.595 +4000 2.713 +3500 2.865 +3000 3.050 +2800 3.142 +2600 3.234 +2400 3.349 +2200 3.485 +2000 3.644 +1800 3.825 +1600 4.051 +1500 4.186 +1400 4.342 +1300 4.510 +1200 4.711 +1100 4.945 +1000 5.233 +900 5.577 +800 6.008 +750 6.273 +700 6.582 +650 6.934 +600 7.363 +550 7.879 +500 8.516 +450 9.327 +400 10.412 +380 10.949 +360 11.541 +340 12.309 +320 13.188 +300 14.177 +280 15.498 +260 17.041 +240 19.140 +210 23.577 +200 25.693 +190 28.258 +180 31.496 +170 35.618 +165 38.056 +160 40.920 +155 44.302 +150 48.177 +145 52.835 +140 58.344 +135 65.188 +130 73.754 +126 82.556 +122 93.825 +118 108.675 +114 129.321 +110 159.772 +108 181.052 +106 208.836 +104 245.923 +102 299.013 +101.8 300.013 +100 330.010 + diff --git a/tecs/inp/c_1.inp b/tecs/inp/c_1.inp new file mode 100644 index 0000000..ccd717b --- /dev/null +++ b/tecs/inp/c_1.inp @@ -0,0 +1,24 @@ +sens=c_1 +unit=Ohm +type=C +form=loglog +curv +50049 1 +6549 2 +2249 3 +1149 4.2 +674 6 +399 10 +299 15 +259 20 +229 27 +209 35 +189 50 +173 77 +165 100 +156 150 +152 200 +147 300 +139 500 + + diff --git a/tecs/inp/c_2.inp b/tecs/inp/c_2.inp new file mode 100644 index 0000000..f623b60 --- /dev/null +++ b/tecs/inp/c_2.inp @@ -0,0 +1,24 @@ +sens=c_2 +unit=Ohm +type=C +form=loglog +curv +50053 1 +6553 2 +2253 3 +1153 4.2 +678 6 +403 10 +303 15 +263 20 +233 27 +213 35 +193 50 +177 77 +169 100 +160 150 +156 200 +151 300 +143 500 + + diff --git a/tecs/inp/c_3.inp b/tecs/inp/c_3.inp new file mode 100644 index 0000000..8086b2c --- /dev/null +++ b/tecs/inp/c_3.inp @@ -0,0 +1,24 @@ +sens=c_3 +unit=Ohm +type=C +form=loglog +curv +50076 1 +6576 2 +2276 3 +1176 4.2 +701 6 +426 10 +326 15 +286 20 +256 27 +236 35 +216 50 +200 77 +192 100 +183 150 +179 200 +174 300 +166 500 + + diff --git a/tecs/inp/c_4.inp b/tecs/inp/c_4.inp new file mode 100644 index 0000000..aecc9ad --- /dev/null +++ b/tecs/inp/c_4.inp @@ -0,0 +1,23 @@ +sens=c_4 +unit=Ohm +type=C +form=loglog +curv +50077 1 +6577 2 +2277 3 +1177 4.2 +702 6 +427 10 +327 15 +287 20 +257 27 +237 35 +217 50 +201 77 +193 100 +184 150 +180 200 +175 300 +167 500 + diff --git a/tecs/inp/ccr2.cfg b/tecs/inp/ccr2.cfg new file mode 100644 index 0000000..4c7001c --- /dev/null +++ b/tecs/inp/ccr2.cfg @@ -0,0 +1,7 @@ + sensA.type=m sensA.curve=x31318 + sensC.type=k sensC.curve=x31320 + sensD.type=s sensD.curve=x31319 + dev="4 K closed cycle refrigerator (FOCUS)" + tlimit=700 resist=25 maxPower=100 + sensA.alarm=310 + prop=50 int=20 deriv=0 diff --git a/tecs/inp/ccr2ht.cfg b/tecs/inp/ccr2ht.cfg new file mode 100644 index 0000000..3d002b3 --- /dev/null +++ b/tecs/inp/ccr2ht.cfg @@ -0,0 +1,8 @@ + sensA.type=t sensA.curve=x14231 sensA.alarm=310 + sensB.type=m sensB.curve=pt + sensC.type=k sensC.curve=x10409 + sensD.type=s sensD.curve=x24506 + + dev="4 K closed cycle refrigerator (FOCUS) with hi-T stage" + tlimit=700 resist=25 maxPower=100 + prop=50 int=20 deriv=0 diff --git a/tecs/inp/ccr4k.cfg b/tecs/inp/ccr4k.cfg new file mode 100644 index 0000000..b974ab0 --- /dev/null +++ b/tecs/inp/ccr4k.cfg @@ -0,0 +1,4 @@ + sensA.type=m sensA.curve=x22644 + dev="4 K closed cycle refrigerator" + tlimit=310 resist=25 maxPower=100 + prop=50 int=20 deriv=0 diff --git a/tecs/inp/cma11.inp b/tecs/inp/cma11.inp new file mode 100644 index 0000000..a86d33c --- /dev/null +++ b/tecs/inp/cma11.inp @@ -0,0 +1,23 @@ +sens=cma11 +unit=Ohm +type=C +form=loglog +curv +50007 1 +6507 2 +2207 3 +1107 4.2 +632 6 +357 10 +257 15 +217 20 +187 27 +167 35 +147 50 +131 77 +122 100 +114 150 +110 200 +105 300 + 97 500 + diff --git a/tecs/inp/cplus45.inp b/tecs/inp/cplus45.inp new file mode 100644 index 0000000..073af53 --- /dev/null +++ b/tecs/inp/cplus45.inp @@ -0,0 +1,23 @@ +sens=cplus45 +unit=Ohm +type=C +form=loglog +curv +50045 1 +6545 2 +2245 3 +1145 4.2 +670 6 +395 10 +295 15 +255 20 +225 27 +205 35 +185 50 +169 77 +161 100 +152 150 +148 200 +143 300 +135 500 + diff --git a/tecs/inp/cplus70.inp b/tecs/inp/cplus70.inp new file mode 100644 index 0000000..f04330d --- /dev/null +++ b/tecs/inp/cplus70.inp @@ -0,0 +1,23 @@ +sens=cplus70 +unit=Ohm +type=C +form=loglog +curv +50070 1 +6570 2 +2270 3 +1170 4.2 +695 6 +420 10 +320 15 +280 20 +250 27 +230 35 +210 50 +194 77 +186 100 +177 150 +173 200 +168 300 +135 500 + diff --git a/tecs/inp/cti1.cfg b/tecs/inp/cti1.cfg new file mode 100644 index 0000000..22a3872 --- /dev/null +++ b/tecs/inp/cti1.cfg @@ -0,0 +1,4 @@ + sensA.type=m sensA.curve=r10401 + dev="CTI closed cycle refrigerator" + tlimit=310 resist=25 maxPower=25 + prop=15 int=10 deriv=0 diff --git a/tecs/inp/cti2.cfg b/tecs/inp/cti2.cfg new file mode 100644 index 0000000..141bef1 --- /dev/null +++ b/tecs/inp/cti2.cfg @@ -0,0 +1,4 @@ + sensA.type=m sensA.curve=r10402 + dev="CTI closed cycle refrigerator" + tlimit=310 resist=25 maxPower=25 + prop=15 int=10 deriv=0 diff --git a/tecs/inp/cti3.cfg b/tecs/inp/cti3.cfg new file mode 100644 index 0000000..db49323 --- /dev/null +++ b/tecs/inp/cti3.cfg @@ -0,0 +1,4 @@ + sensA.type=m sensA.curve=r10403 + dev="CTI closed cycle refrigerator" + tlimit=310 resist=25 maxPower=25 + prop=15 int=10 deriv=0 diff --git a/tecs/inp/cti4.cfg b/tecs/inp/cti4.cfg new file mode 100644 index 0000000..6f535a4 --- /dev/null +++ b/tecs/inp/cti4.cfg @@ -0,0 +1,5 @@ + sensA.type=t sensA.curve=r10411 sensA.alarm=300 + sensB.type=m sensB.curve=rhfe4140 + dev="CTI closed cycle refrigerator (30...475 K)" + tlimit=600 resist=25 maxPower=25 + prop=15 int=10 deriv=0 diff --git a/tecs/inp/cti5.cfg b/tecs/inp/cti5.cfg new file mode 100644 index 0000000..752d299 --- /dev/null +++ b/tecs/inp/cti5.cfg @@ -0,0 +1,4 @@ + sensA.type=m sensA.curve=r10410 + dev="CTI closed cycle refrigerator (high power)" + tlimit=310 resist=25 maxPower=25 + prop=15 int=10 deriv=0 diff --git a/tecs/inp/cti6.cfg b/tecs/inp/cti6.cfg new file mode 100644 index 0000000..e7d7fa7 --- /dev/null +++ b/tecs/inp/cti6.cfg @@ -0,0 +1,5 @@ + sensA.type=m sensA.curve=std1 + sensB.type=t sensB.curve=r10413 + dev="CTI closed cycle refrigerator (FOCUS, 475 K)" + tlimit=474 resist=50 maxPower=25 + prop=15 int=10 deriv=0 diff --git a/tecs/inp/dil.cfg b/tecs/inp/dil.cfg new file mode 100644 index 0000000..9195ff7 --- /dev/null +++ b/tecs/inp/dil.cfg @@ -0,0 +1,6 @@ + sensC.type=s sensC.curve=rxdil + dev="dilution (Risoe)" + tlimit=375 resist=25 maxpower=25 + prop=20 int=10 deriv=0 + loop=2 + diff --git a/tecs/inp/disc.cfg b/tecs/inp/disc.cfg new file mode 100644 index 0000000..0c6b649 --- /dev/null +++ b/tecs/inp/disc.cfg @@ -0,0 +1,6 @@ + sensA.type=m sensA.curve=psam + sensB.type=n sensB.curve=g24741 + dev="Displex closed cycle refrigerator C" + tlimit=310 resist=50 maxpower=50 + sensA.lim=30 sensB.lim=60 + prop=15 int=10 deriv=0 diff --git a/tecs/inp/dise.cfg b/tecs/inp/dise.cfg new file mode 100644 index 0000000..27a337b --- /dev/null +++ b/tecs/inp/dise.cfg @@ -0,0 +1,6 @@ + sensA.type=m sensA.curve=psam + sensB.type=n sensB.curve=g26552 + dev="Displex closed cycle refrigerator E" + tlimit=310 resist=50 maxpower=50 + sensA.lim=30 sensB.lim=60 + prop=15 int=10 deriv=0 diff --git a/tecs/inp/ds3b.inp b/tecs/inp/ds3b.inp new file mode 100644 index 0000000..f8fbfb7 --- /dev/null +++ b/tecs/inp/ds3b.inp @@ -0,0 +1,76 @@ +sens=ds3b +unit=V ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=Si ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=100uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +2.0 1.0 +1.701 1.023 +1.696 1.339 +1.691 1.634 +1.681 2.096 +1.671 2.507 +1.659 2.969 +1.644 3.482 +1.627 4.035 +1.602 4.782 +1.564 5.825 +1.527 6.836 +1.489 7.865 +1.455 8.890 +1.42273 9.93526 +1.39637 10.8854 +1.3709 11.8914 +1.34717 12.9115 +1.3257 13.9068 +1.30501 14.9288 +1.2869 15.871 +1.26837 16.872 +1.24986 17.9012 +1.23182 18.9267 +1.21451 19.9173 +1.19683 20.9082 +1.18224 21.6778 +1.1643 22.5364 +1.1509 23.1421 +1.13892 23.7461 +1.1304 24.3304 +1.12457 24.9558 +1.12113 25.5134 +1.11756 26.3163 +1.11473 27.1373 +1.11227 27.9723 +1.10969 28.963 +1.10731 29.9676 +1.10303 31.9567 +1.09724 34.9549 +1.09182 37.9771 +1.08496 41.9734 +1.06774 51.9579 +1.05704 57.9796 +1.04616 63.991 +1.03518 69.9483 +1.02386 75.9817 +1.01241 81.9671 +1.00074 87.9604 +0.98883 93.9712 +0.97685 99.929 +0.95628 109.968 +0.92481 124.962 +0.89261 139.951 +0.85971 154.977 +0.82636 169.973 +0.79251 184.99 +0.75829 200.005 +0.72381 214.98 +0.68899 229.971 +0.65383 244.991 +0.61847 259.998 +0.58301 274.976 +0.54722 290.026 +0.5113 305.074 +0.47525 320.108 +0.45111 330.134 + + diff --git a/tecs/inp/dt-470.inp b/tecs/inp/dt-470.inp new file mode 100644 index 0000000..3375d10 --- /dev/null +++ b/tecs/inp/dt-470.inp @@ -0,0 +1,94 @@ +sens=dt-470 +unit=V ! sensor format (mV,V,Ohm), log formats are choosen automatically +type=Si ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +2.5 0.1 +1.7027 1.1 +1.69818 1.4 +1.69367 1.7 +1.68585 2.1 +1.67398 2.6 +1.65156 3.4 +1.62622 4.2 +1.59075 5.2 +1.50258 7.5 +1.46684 8.5 +1.43474 9.5 +1.40605 10.5 +1.38012 11.5 +1.35642 12.5 +1.33438 13.5 +1.30404 15 +1.26685 17 +1.22321 19.5 +1.19645 21 +1.17705 22 +1.15558 23 +1.13598 24 +1.12463 25 +1.11896 26 +1.11517 27 +1.11212 28 +1.10945 29 +1.10702 30 +1.10476 31 +1.10263 32 +1.1006 33 +1.09864 34 +1.09489 36 +1.08953 39 +1.08781 40 +1.0775 46 +1.06702 52 +1.0563 58 +1.04353 65 +1.03425 70 +1.02482 75 +1.01525 80 +1.00552 85 +0.99565 90 +0.98564 95 +0.9755 100 +0.96524 105 +0.95487 110 +0.9444 115 +0.93383 120 +0.92317 125 +0.91243 130 +0.90161 135 +0.89072 140 +0.87976 145 +0.86874 150 +0.84651 160 +0.82405 170 +0.80139 180 +0.77857 190 +0.744 205 +0.70909 220 +0.67389 235 +0.63842 250 +0.60275 265 +0.55494 285 +0.51892 300 +0.50691 305 +0.4586 325 +0.44647 330 +0.41005 345 +0.36111 365 +0.32417 380 +0.28701 395 +0.27456 400 +0.24964 410 +0.22463 420 +0.19961 430 +0.1871 435 +0.17464 440 +0.16221 445 +0.14985 450 +0.13759 455 +0.12547 460 +0.11356 465 +0.10191 470 +0.09062 475 + + diff --git a/tecs/inp/fi.cfg b/tecs/inp/fi.cfg new file mode 100644 index 0000000..eb02c06 --- /dev/null +++ b/tecs/inp/fi.cfg @@ -0,0 +1,10 @@ + sensA.type=f + sensB.type=t sensB.curve=rhfe4140 sensB.alarm=323 + sensC.type=s sensC.curve=std6 + sensD.type=m sensD.curve=std6 + dev="ILL Furnace (1500 K, typ K)" + tlimit=1500 resist=1000 maxPower=2000 powfact=2000 + controlmode=1 + prop=3 int=0.3 deriv=0 + lscfg="LINEAR A,2,1.6,3,1,-1.4;INTYPE A,0,1,2,10,12;DISPFLD 4,A,4;DISPLAY:4" + diff --git a/tecs/inp/fs.cfg b/tecs/inp/fs.cfg new file mode 100644 index 0000000..17d9035 --- /dev/null +++ b/tecs/inp/fs.cfg @@ -0,0 +1,5 @@ + sensC.type=m sensC.curve=std6 + sensD.type=s sensD.curve=std6 + dev="small furnace" + tlimit=800 resist=25 maxPower=100 + prop=10 int=5 deriv=0 diff --git a/tecs/inp/ft.cfg b/tecs/inp/ft.cfg new file mode 100644 index 0000000..412a88b --- /dev/null +++ b/tecs/inp/ft.cfg @@ -0,0 +1,9 @@ + sensA.type=f + sensB.type=t sensB.curve=rhfe4140 sensB.alarm=373 + sensC.type=s sensC.curve=std6 + sensD.type=m sensD.curve=std6 + dev="tantalum furnace (1400 K)" + tlimit=1405 resist=1000 maxPower=50 powfact=2000 + controlmode=1 + prop=10 int=5 deriv=0 + lscfg="LINEAR A,2,1.6,3,1,-1.4;INTYPE A,0,1,2,10,12;DISPFLD 4,A,4;DISPLAY:4" diff --git a/tecs/inp/fw.cfg b/tecs/inp/fw.cfg new file mode 100644 index 0000000..e270efe --- /dev/null +++ b/tecs/inp/fw.cfg @@ -0,0 +1,10 @@ + sensA.type=f + sensB.type=t sensB.curve=rhfe4140 sensB.alarm=323 + sensC.type=s sensC.curve=type_c sensC.scale=2.0 sensC.kink=333.15 + sensD.type=m sensD.curve=type_c sensD.scale=2.0 sensD.kink=333.15 + dev="ILL Furnace (2000 K, typ C / W5)" + tlimit=1850 resist=1000 maxPower=2000 powfact=2000 + controlmode=1 + prop=3 int=0.3 deriv=0 + lscfg="LINEAR A,2,1.6,3,1,-1.4;INTYPE A,0,1,2,10,12;DISPFLD 4,A,4;DISPLAY:4" + diff --git a/tecs/inp/g24741.inp b/tecs/inp/g24741.inp new file mode 100644 index 0000000..d5ac5da --- /dev/null +++ b/tecs/inp/g24741.inp @@ -0,0 +1,57 @@ +sens=g24741 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=Ge ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +range=33333 +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +3716.48 3.614 +3303.08 3.805 +2939.81 4.007 +2634.1 4.211 +2207.84 4.568 +1850.95 4.962 +1510.33 5.464 +1168.62 6.17 +898.255 6.969 +664.661 7.969 +503.54 8.966 +385.764 9.997 +302.717 11.005 +241.569 12.011 +196.091 13.009 +161.375 14.009 +134.756 15.002 +113.613 16.009 +97.1542 16.995 +83.7844 17.987 +72.9223 18.98 +63.8891 19.986 +55.898 21.062 +46.4039 22.685 +39.5526 24.203 +33.94 25.781 +29.5042 27.352 +25.8808 28.938 +22.6148 30.71 +19.5475 32.811 +16.2503 35.791 +13.7919 38.802 +11.9208 41.828 +10.4837 44.827 +9.33607 47.855 +8.70341 49.86 +7.45938 54.825 +6.54015 59.805 +5.84053 64.822 +5.30420 69.803 +4.87975 74.794 +4.54002 79.775 +4.26248 84.818 +4.03819 89.795 +3.85122 94.839 +3.69833 99.809 +3.46425 109.82 +3.30216 119.843 +1 350 + + diff --git a/tecs/inp/g25328.inp b/tecs/inp/g25328.inp new file mode 100644 index 0000000..a4d5014 --- /dev/null +++ b/tecs/inp/g25328.inp @@ -0,0 +1,69 @@ +sens=g25328 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=Ge ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +range=33333 +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +51742 1.20397 +38374.4 1.30097 +29285.9 1.39987 +18336.7 1.59973 +12322.8 1.80467 +8953.12 2.00029 +6797.69 2.19633 +5283.47 2.40223 +4277.88 2.59821 +3518.79 2.80215 +2970 2.99976 +2553.86 3.19379 +2199.04 3.40534 +1942.6 3.59649 +1720.04 3.79904 +1539.73 3.99753 +1386.08 4.19945 +1141.13 4.6087 +960.495 5.01198 +788.722 5.52181 +617.915 6.22374 +481.462 7.01657 +359.562 8.04131 +276.645 9.05249 +216.121 10.0975 +173.58 11.1109 +142.19 12.115 +118.256 13.1243 +100.185 14.1049 +85.7627 15.0937 +74.0598 16.0946 +64.7476 17.0714 +57.0177 18.0515 +50.5646 19.0281 +45.0554 20.0179 +40.0589 21.0809 +33.8704 22.6975 +29.2326 24.2277 +25.307 25.8307 +22.174 27.4033 +19.5516 29.0097 +17.2057 30.757 +14.9274 32.8585 +12.4205 35.8717 +10.5431 38.8891 +9.09534 41.9407 +7.99882 44.9009 +7.09635 47.9674 +6.6064 49.9668 +5.633 54.9499 +4.92135 59.8927 +4.38084 64.8514 +3.96147 69.8101 +3.62938 74.7892 +3.36171 79.8027 +3.14631 84.787 +2.96943 89.7821 +2.82263 94.8151 +2.70184 99.7862 +2.51544 109.819 +2.38525 119.826 +1 350 + diff --git a/tecs/inp/g25550.inp b/tecs/inp/g25550.inp new file mode 100644 index 0000000..2ee7860 --- /dev/null +++ b/tecs/inp/g25550.inp @@ -0,0 +1,69 @@ +sens=g25550 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=Ge ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +range=33333 +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +62321.3 1.2009 +46207 1.30013 +35094.4 1.40258 +22373.5 1.59752 +15326 1.79521 +11200.4 1.9899 +8362.98 2.20207 +6513.28 2.41223 +5356.83 2.5985 +4433.07 2.80016 +3742.13 3.00175 +3222.56 3.19821 +2805.65 3.39878 +2470.82 3.59887 +2194.89 3.8009 +1969.57 4.00008 +1775.99 4.20356 +1422.69 4.68654 +1220.45 5.05936 +1018.33 5.54189 +811.357 6.21394 +641.701 6.97679 +487.564 7.97051 +381.494 8.95538 +303.493 9.9658 +247.623 10.9549 +205.794 11.9455 +173.45 12.9489 +148.82 13.9294 +128.951 14.9234 +112.674 15.9345 +99.5655 16.9246 +88.6102 17.9191 +79.3856 18.913 +71.4038 19.9217 +64.0717 21.0093 +54.8993 22.659 +48.003 24.1928 +42.1299 25.7827 +37.3274 27.3466 +33.2266 28.9435 +29.4847 30.6837 +25.777 32.7852 +21.6144 35.807 +18.4462 38.8362 +15.9599 41.9041 +14.0667 44.8711 +12.4931 47.9476 +11.6357 49.9458 +9.86331 55.1436 +8.64011 59.988 +7.69916 64.8521 +6.95065 69.8121 +6.35553 74.7943 +5.87526 79.8043 +5.48659 84.7949 +5.16668 89.7832 +4.89963 94.8091 +4.67607 99.917 +4.33433 109.992 +4.09814 119.813 + + diff --git a/tecs/inp/g26552.inp b/tecs/inp/g26552.inp new file mode 100644 index 0000000..9c2ba9e --- /dev/null +++ b/tecs/inp/g26552.inp @@ -0,0 +1,69 @@ +sens=g26552 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=Ge ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +range=33333 +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +44339.7 1.26752 +30479.5 1.40131 +19063.5 1.60058 +12816.1 1.80449 +9363.14 1.99492 +6947.58 2.20682 +5431.88 2.40878 +4384.64 2.60805 +3637.07 2.80314 +3058.28 3.00423 +2614.88 3.20522 +2273.22 3.40257 +1991.83 3.60531 +1765.38 3.80634 +1582.8 4.00195 +1380.44 4.26656 +1159.05 4.63876 +975.898 5.04379 +798.593 5.56593 +623.062 6.28577 +483.097 7.10211 +361.38 8.13119 +277.733 9.16019 +215.352 10.2524 +173.155 11.2782 +142.178 12.2899 +118.874 13.2861 +100.926 14.2709 +86.8487 15.2417 +75.4522 16.2141 +66.3158 17.1623 +58.6667 18.1158 +52.189 19.0755 +46.619 20.0485 +41.5819 21.0898 +35.1838 22.7081 +30.4344 24.2187 +26.3232 25.8396 +23.0313 27.4345 +20.2266 29.0991 +17.7346 30.9099 +15.3757 33.0415 +12.7993 36.0755 +10.893 39.0826 +9.4386 42.0696 +8.29125 45.0773 +7.3856 48.0592 +6.87377 50.0678 +5.85986 55.0763 +5.11841 60.0483 +4.55332 65.0504 +4.11832 70.0235 +3.78204 74.8823 +3.50414 79.8877 +3.27933 84.8633 +3.09329 89.9091 +2.94139 94.8836 +2.81229 100.02 +2.61888 109.99 +2.48327 119.985 +1 350 + + diff --git a/tecs/inp/gemark.inp b/tecs/inp/gemark.inp new file mode 100644 index 0000000..4b79c18 --- /dev/null +++ b/tecs/inp/gemark.inp @@ -0,0 +1,105 @@ +sens=gemark +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=Ge ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=100uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +992.7556998 1 +792.1858987 1.1 +653.3182511 1.2 +552.6026325 1.3 +476.8394272 1.4 +418.1430416 1.5 +371.2262706 1.6 +332.9399159 1.7 +301.2666387 1.8 +274.7819189 1.9 +252.4107683 2 +233.326363 2.1 +216.8968945 2.2 +202.6260845 2.3 +190.1282584 2.4 +179.0951525 2.5 +169.2860274 2.6 +160.5048437 2.7 +152.5965004 2.8 +145.4329823 2.9 +138.9113482 3 +132.9452312 3.1 +127.4641573 3.2 +122.4082475 3.3 +117.7278231 3.4 +113.3802387 3.5 +109.329501 3.6 +105.5444561 3.7 +101.9985953 3.8 +98.66854327 3.9 +95.53422694 4 +89.78411574 4.2 +84.63036666 4.4 +79.9817946 4.6 +75.76394149 4.8 +71.91810156 5 +68.39563463 5.2 +65.15718079 5.4 +62.16911131 5.6 +59.40347818 5.8 +56.83732393 6 +51.16738451 6.5 +46.37614641 7 +42.28750151 7.5 +38.77347458 8 +35.73473767 8.5 +33.09366895 9 +30.7880927 9.5 +28.76957297 10 +26.99811498 10.5 +25.43582083 11 +24.04933649 11.5 +22.81264984 12 +21.70478628 12.5 +20.7087146 13 +19.81020181 13.5 +18.99659056 14 +18.25670823 14.5 +17.58098117 15 +16.96112438 15.5 +16.39008975 16 +15.86178642 16.5 +15.3710694 17 +14.91350279 17.5 +14.48533597 18 +14.08331295 18.5 +13.70467074 19 +13.3469953 19.5 +13.00822897 20 +12.38041392 21 +11.80935842 22 +11.28600739 23 +10.8031861 24 +10.35529442 25 +9.937879436 26 +9.547310328 27 +9.180686215 28 +8.835616101 29 +8.510135723 30 +8.202631541 31 +7.911729004 32 +7.636291925 33 +7.375312858 34 +7.127928135 35 +6.893358558 36 +6.670875366 37 +6.459793187 38 +6.259469861 39 +6.069291409 40 +5.6863 42.177 +5.226 45.156 +3 70 +1.85 100 +1.15 140 +0.69 200 +0.37 310 + + diff --git a/tecs/inp/hef4c.cfg b/tecs/inp/hef4c.cfg new file mode 100644 index 0000000..aa2df79 --- /dev/null +++ b/tecs/inp/hef4c.cfg @@ -0,0 +1,6 @@ + sensA.type=m sensA.curve=r3510 + sensB.type=t sensB.curve=r3509 + sensC.type=s sensC.curve=x14126 + dev="He-flow 4 circle cryostat" + tlimit=310 resist=50 maxPower=25 + prop=50 int=20 deriv=0 diff --git a/tecs/inp/ill1.cfg b/tecs/inp/ill1.cfg new file mode 100644 index 0000000..b17b7aa --- /dev/null +++ b/tecs/inp/ill1.cfg @@ -0,0 +1,7 @@ + sensB.type=m sensB.curve=x15601 + sensC.type=s sensC.curve=x12532 + sensD.type=h + dev="orange cryostat 50 mm" + tLimit=310 resist=50 maxpower=25 controlMode=0 + prop=25 int=10 deriv=0 + full=4.64 diff --git a/tecs/inp/ill2.cfg b/tecs/inp/ill2.cfg new file mode 100644 index 0000000..ef366e3 --- /dev/null +++ b/tecs/inp/ill2.cfg @@ -0,0 +1,6 @@ + sensA.type=m sensA.curve=ds3b + sensC.type=s sensC.curve=x14130 + sensD.type=h + dev="orange cryostat 70 mm" + tLimit=310 resist=50 maxpower=25 controlMode=0 full=4.64 + prop=25 int=10 deriv=0 diff --git a/tecs/inp/ill2p.cfg b/tecs/inp/ill2p.cfg new file mode 100644 index 0000000..b007ec8 --- /dev/null +++ b/tecs/inp/ill2p.cfg @@ -0,0 +1,2 @@ + sensC.type=s sensC.curve=x22637 + dev="uniaxial pressure insert for ILL2" diff --git a/tecs/inp/ill3.cfg b/tecs/inp/ill3.cfg new file mode 100644 index 0000000..4284ad1 --- /dev/null +++ b/tecs/inp/ill3.cfg @@ -0,0 +1,6 @@ + sensA.type=m sensA.curve=rhfe8119 + sensB.type=h + sensC.type=s sensC.curve=rhfe8244 + dev="cryofurnace without power supply" + tLimit=450 resist=10 maxpower=40 controlMode=0 full=4.64 + prop=25 int=10 deriv=0 diff --git a/tecs/inp/ill3f.cfg b/tecs/inp/ill3f.cfg new file mode 100644 index 0000000..a2a38dd --- /dev/null +++ b/tecs/inp/ill3f.cfg @@ -0,0 +1,7 @@ + sensA.type=m sensA.curve=rhfe8119 + sensB.type=h + sensC.type=s sensC.curve=rhfe8244 + dev="cryofurnace with power supply" + tLimit=600 resist=1000 maxpower=180 powFact=45 + prop=25 int=10 deriv=0 + controlMode=0 full=4.64 diff --git a/tecs/inp/ill4.cfg b/tecs/inp/ill4.cfg new file mode 100644 index 0000000..cfe1bbd --- /dev/null +++ b/tecs/inp/ill4.cfg @@ -0,0 +1,6 @@ + sensA.type=m sensA.curve=dt-470 + sensB.type=h + sensC.type=s sensC.curve=x13089 + dev="FOCUS orange cryostat 70 mm" + tLimit=310 resist=50 maxpower=25 controlMode=0 full=4.64 + prop=25 int=10 deriv=0 diff --git a/tecs/inp/ill5.cfg b/tecs/inp/ill5.cfg new file mode 100644 index 0000000..1e8a35d --- /dev/null +++ b/tecs/inp/ill5.cfg @@ -0,0 +1,7 @@ + sensB.type=m sensB.curve=x10045 + sensC.type=s sensC.curve=x09882 + sensD.type=h + dev="maxi orange crostat 100 mm" + tLimit=310 resist=50 maxpower=25 controlMode=0 full=4.64 + prop=25 int=10 deriv=0 + sensA.alarm=0 diff --git a/tecs/inp/ill5n.cfg b/tecs/inp/ill5n.cfg new file mode 100644 index 0000000..9a23823 --- /dev/null +++ b/tecs/inp/ill5n.cfg @@ -0,0 +1,3 @@ + sensC.type=s sensC.curve=x09883 + sensD.type=h + dev="precoolable sample stick for maxi orange cryostat" diff --git a/tecs/inp/lsc.codes b/tecs/inp/lsc.codes new file mode 100644 index 0000000..eab7341 --- /dev/null +++ b/tecs/inp/lsc.codes @@ -0,0 +1,27 @@ +# Code list for SE devices connected via LSC340 +# +ill1 1 -1 +ill2 2 -2 +ill2p -3 +ill3 3 -5 +ill4 4 -6 +ill5 5 -4 +ill5n -7 +cti1 6 +cti2 7 +cti3 8 +cti4 9 +cti6 11 +apd 12 +apdl -9 +ccr4k 13 +ccr2 28 -28 +hef4c 14 -11 +sup4t 15 60 +ma09 19 -19 +dise 26 -26 +ori1 29 -29 +ori2 25 -25 +ori3 22 -22 +ma11 27 +ma02 23 -23 diff --git a/tecs/inp/ma02.cfg b/tecs/inp/ma02.cfg new file mode 100644 index 0000000..7ca80c3 --- /dev/null +++ b/tecs/inp/ma02.cfg @@ -0,0 +1,5 @@ + sensA.type=m sensA.curve=x29746 + sensC.type=s sensC.curve=x29630 + dev="1.8 T horizontal cryomagnet (Risoe)" + tlimit=310 resist=50 maxpower=50 + prop=15 int=10 deriv=0 diff --git a/tecs/inp/ma09.cfg b/tecs/inp/ma09.cfg new file mode 100644 index 0000000..8b7f31e --- /dev/null +++ b/tecs/inp/ma09.cfg @@ -0,0 +1,8 @@ + sensA.type=m sensA.curve=c17844 + sensB.type=t sensB.curve=cplus70 + sensC.type=s sensC.curve=x22642 + dev="9 T vertical cryomagnet (Risoe)" + tlimit=310 resist=50 maxpower=50 + swRangeOn=1 + prop=20 int=10 deriv=0 + lscfg="dispfld 4,B,3;display 4" diff --git a/tecs/inp/ma11.cfg b/tecs/inp/ma11.cfg new file mode 100644 index 0000000..60100b6 --- /dev/null +++ b/tecs/inp/ma11.cfg @@ -0,0 +1,3 @@ + sensA.type=t sensA.curve=cplus45 + dev="SANS test carbon resistors" + lscfg="dispfld 2,A,3;display 2" diff --git a/tecs/inp/mz020124.inp b/tecs/inp/mz020124.inp new file mode 100644 index 0000000..891eb9d --- /dev/null +++ b/tecs/inp/mz020124.inp @@ -0,0 +1,110 @@ +sens=mz020124 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +form=loglog +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +1.954519465 3.1206 +1.985957728 3.391099984 +2.017855208 3.674243588 +2.050312219 3.970801721 +2.083291299 4.281292125 +2.116752103 4.606384478 +2.150799862 4.946893604 +2.185344956 5.303354639 +2.220496025 5.676624202 +2.256160544 6.067557577 +2.292450675 6.476886834 +2.329270895 6.905479786 +2.366736998 7.354276657 +2.404750369 7.824233572 +2.443430553 8.316344412 +2.482675737 8.831617418 +2.522609344 9.371236431 +2.563126259 9.936251595 +2.604353905 10.52785303 +2.646183761 11.14740374 +2.688747379 11.79612797 +2.731932722 12.47543812 +2.775875604 13.18668703 +2.820460358 13.93153058 +2.865827198 14.71147282 +2.911856711 15.52816789 +2.957399533 16.38012579 +3.001096774 17.2515529 +3.043336677 18.12271256 +3.084537113 18.99996906 +3.125143759 19.89802618 +3.165555994 20.82438653 +3.206343152 21.78831425 +3.248029761 22.80187398 +3.291091827 23.88041394 +3.336184037 25.02255504 +3.383062335 26.2130948 +3.431310348 27.45487455 +3.481528863 28.75178258 +3.534516391 30.107979 +3.590789942 31.52786691 +3.651236801 33.01467207 +3.716464596 34.5715482 +3.787476963 36.20179764 +3.864826479 37.90887837 +3.947389668 39.69641134 +4.03663982 41.56818814 +4.135042713 43.52817906 +4.245120281 45.58054151 +4.369884919 47.72962882 +4.512425035 49.9799995 +4.672292251 52.33642688 +4.846743092 54.80390926 +5.036861394 57.3876805 +5.244329856 60.09322113 +5.470789441 62.92626996 +5.717945347 65.89283627 +5.98783742 68.99921254 +6.280872826 72.25198782 +6.597812965 75.65806167 +6.93920951 79.22465883 +7.306173816 82.95934454 +7.698923424 86.87004057 +8.118017814 90.96504202 +8.56406589 95.25303495 +9.036702813 99.74311475 +9.535643365 104.4448055 +10.06027842 109.3680801 +10.61133438 114.5233815 +11.18948246 119.9216448 +11.7953274 125.5743203 +12.42910909 131.4933983 +13.09181923 137.6914338 +13.78319816 144.1815737 +14.50373981 150.9775845 +15.25351734 158.0938814 +16.03356143 165.5455591 +16.84612427 173.3484235 +17.69253242 181.5190256 +18.57462266 190.0746963 +19.49395683 199.0335833 +20.45266947 208.4146897 +21.45210925 218.2379139 +22.49468935 228.5240925 +23.58305153 239.2950438 +24.71894892 250.5736143 +25.90955775 262.3837275 +27.15813858 274.7504342 +28.46033449 287.6999658 +29.81192363 301.25979 +31.2169163 315.4586691 +32.68812424 330.3267207 +34.22866808 345.895482 +35.84181551 362.1979764 +37.53098823 379.2687837 +39.29976921 397.1441134 +41.15191027 415.8618814 +43.09134006 435.4617906 +45.12217235 455.9854151 +47.24871481 477.4762882 + + diff --git a/tecs/inp/mz030500.inp b/tecs/inp/mz030500.inp new file mode 100644 index 0000000..3a7024d --- /dev/null +++ b/tecs/inp/mz030500.inp @@ -0,0 +1,126 @@ +sens=mz030500 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +2.498 4.472532903 +3 9.773124819 +3.06 10.55303764 +3.12 11.46731087 +3.18 12.38397382 +3.24 13.37176795 +3.3 14.42540969 +3.37 15.73076805 +3.44 17.12343827 +3.51 18.64642133 +3.58 20.24301705 +3.65 21.9221971 +3.72 23.69988759 +3.79 25.51904558 +3.87 27.62746099 +3.95 29.74116813 +4.03 31.80878152 +4.11 33.81739732 +4.19 35.75357133 +4.27 37.5847035 +4.36 39.53810683 +4.45 41.40171428 +4.54 43.17988888 +4.63 44.87496076 +4.72 46.49129524 +4.81 48.04370952 +4.91 49.6720703 +5.01 51.27267707 +5.11 52.82258535 +5.21 54.30211212 +5.31 55.74326127 +5.42 57.25945659 +5.53 58.73605895 +5.64 60.19158187 +5.75 61.60151532 +5.87 63.10400027 +5.99 64.58000866 +6.11 66.03690471 +6.23 67.45325536 +6.35 68.84502457 +6.48 70.32891791 +6.61 71.79267469 +6.74 73.23720062 +6.87 74.66546356 +7.01 76.18382684 +7.15 77.67731168 +7.29 79.15321097 +7.44 80.71669982 +7.59 82.26065751 +7.74 83.77920365 +7.89 85.2977498 +8.05 86.91753235 +8.21 88.50330232 +8.37 90.08781524 +8.54 91.77136022 +8.71 93.42984611 +8.88 95.08617427 +9.06 96.8399335 +9.24 98.57303396 +9.42 100.3060185 +9.61 102.1321031 +9.8 103.9440315 +10 105.8513246 +10.2 107.752616 +10.4 109.6486395 +10.61 111.6394642 +10.82 113.6247095 +11.04 115.7043276 +11.26 117.7833593 +11.49 119.9563834 +11.72 122.130388 +11.95 124.3074784 +12.19 126.5792385 +12.43 128.853444 +12.68 131.2224081 +12.93 133.5961045 +13.19 136.0654791 +13.45 138.5436461 +13.72 141.119047 +13.99 143.7001032 +14.27 146.3776573 +14.56 149.1617938 +14.85 151.9478907 +15.15 154.8374244 +15.45 157.7280848 +15.76 160.7164093 +16.08 163.8065005 +16.4 166.8996993 +16.73 170.0966977 +17.06 173.302643 +17.4 176.6125596 +17.75 180.0321832 +18.11 183.5578675 +18.47 187.0893314 +18.84 190.7241807 +19.22 194.4710294 +19.6 198.2263364 +19.99 202.0878068 +20.39 206.0543442 +20.8 210.127842 +21.22 214.3079218 +21.64 218.4924193 +22.07 222.7820044 +22.51 227.1788701 +22.96 231.6827282 +23.42 236.2894724 +23.89 241.001239 +24.37 245.8178023 +24.86 250.7437405 +25.36 255.7715377 +25.87 260.8990519 +26.39 266.1324909 +26.92 271.458145 +27.46 276.8800659 +28.01 282.4402052 +28.57 288.1037036 +29.14 293.8716111 +37.2 375.1552482 + diff --git a/tecs/inp/ori1.cfg b/tecs/inp/ori1.cfg new file mode 100644 index 0000000..b0ecd55 --- /dev/null +++ b/tecs/inp/ori1.cfg @@ -0,0 +1,7 @@ + sensA.type=m sensA.curve=pcry sensA.lim=50 + sensB.type=n sensB.curve=c030311 sensB.lim=60 + sensC.type=s sensC.curve=psam sensC.lim=50 + sensD.type=l sensD.curve=g25328 sensD.lim=60 + dev="orange cryostat 50 mm (Risoe)" + tlimit=310 resist=50 maxpower=50 controlmode=0 + prop=25 int=10 deriv=0 diff --git a/tecs/inp/ori2.cfg b/tecs/inp/ori2.cfg new file mode 100644 index 0000000..7bee7c7 --- /dev/null +++ b/tecs/inp/ori2.cfg @@ -0,0 +1,7 @@ + sensA.type=m sensA.curve=pcry sensA.lim=30 + sensB.type=n sensB.curve=c030307 sensB.lim=40 + sensC.type=t sensC.curve=psam + sensD.type=s sensD.curve=x2060 + dev="orange cryostat 50 mm (Risoe)" + tlimit=310 resist=50 maxpower=50 controlmode=0 + prop=25 int=10 deriv=0 diff --git a/tecs/inp/ori3.cfg b/tecs/inp/ori3.cfg new file mode 100644 index 0000000..069a927 --- /dev/null +++ b/tecs/inp/ori3.cfg @@ -0,0 +1,6 @@ + sensA.type=m sensA.curve=pcry sensA.lim=50 + sensB.type=n sensB.curve=c020415 sensB.lim=60 + sensC.type=s sensC.curve=x22643 + dev="maxi orange cryostat 100 mm (Risoe)" + tlimit=310 resist=50 maxpower=50 controlmode=0 + prop=25 int=10 deriv=0 diff --git a/tecs/inp/pcry.inp b/tecs/inp/pcry.inp new file mode 100644 index 0000000..861b44e --- /dev/null +++ b/tecs/inp/pcry.inp @@ -0,0 +1,84 @@ +sens=pcry +unit=Ohm +type=Pt250 +curv +0.001 10 +0.141 13 +0.164 14 +0.193 15 +0.228 16 +0.271 17 +0.321 18 +0.379 19 +0.525 21 +0.713 23 +0.823 24 +0.946 25 +1.555 29 +2.139 32 +2.587 34 +3.082 36 +3.619 38 +4.195 40 +4.807 42 +5.126 43 +5.788 45 +6.833 48 +7.56 50 +8.31 52 +8.692 53 +9.469 55 +10.261 57 +11.474 60 +11.884 61 +12.713 63 +13.971 66 +15.243 69 +16.953 73 +18.244 76 +19.107 78 +20.407 81 +21.71 84 +22.58 86 +23.886 89 +24.755 91 +26.057 94 +26.924 96 +27.789 98 +28.652 100 +29.515 102 +30.376 104 +31.236 106 +32.095 108 +32.952 110 +33.809 112 +34.664 114 +35.518 116 +36.371 118 +37.222 120 +38.073 122 +38.498 123 +39.347 125 +40.195 127 +41.041 129 +42.31 132 +43.154 134 +47.36 144 +50.708 153 +55.703 164 +59.842 174 +63.962 184 +67.654 193 +72.149 204 +75.811 213 +79.865 223 +88.335 244 +91.948 253 +95.949 263 +99.939 273 +104.315 284 +107.884 293 +112.234 304 +115.782 313 + + diff --git a/tecs/inp/psam.inp b/tecs/inp/psam.inp new file mode 100644 index 0000000..9644925 --- /dev/null +++ b/tecs/inp/psam.inp @@ -0,0 +1,90 @@ +sens=psam +unit=Ohm +type=Pt250 +curv +0.001 1 +1.806 11.014 +1.855 13.02 +1.909 14.627 +1.924 15 +2.019 16.858 +2.087 17.962 +2.122 18.462 +2.165 19.053 +2.391 21.605 +2.561 23.17 +2.68 24.154 +2.848 25.4 +3.551 29.725 +4.154 32.689 +4.656 34.85 +5.112 36.661 +5.534 38.241 +6.279 40.827 +6.933 42.954 +7.241 43.924 +7.833 45.742 +8.64 48.081 +9.402 50.233 +10.11 52.159 +10.768 53.915 +11.415 55.611 +12.021 57.17 +13.16 60.054 +13.709 61.422 +14.73 63.939 +15.735 66.413 +17.176 69.883 +18.516 73.074 +19.803 76.131 +21.014 78.997 +22.173 81.727 +23.3 84.385 +24.368 86.89 +25.426 89.382 +26.427 91.735 +27.424 94.083 +28.371 96.319 +29.323 98.565 +30.224 100.689 +31.133 102.843 +32 104.889 +32.865 106.94 +33.708 108.941 +34.537 110.912 +35.359 112.864 +36.15 114.752 +36.954 116.669 +37.73 118.519 +38.501 120.368 +39.266 122.204 +40.007 123.973 +40.756 125.779 +41.485 127.528 +42.201 129.251 +43.622 132.682 +44.32 134.373 +48.378 144.217 +52.255 153.673 +56.564 164.241 +60.698 174.433 +64.687 184.307 +68.544 193.884 +72.767 204.422 +76.379 213.474 +80.392 223.56 +84.256 233.308 +88.516 244.079 +92.107 253.192 +96.145 263.468 +99.966 273.226 +104.27 284.239 +107.917 293.61 +112.073 304.315 +115.569 313.341 +119.4 323.15 +123.24 333.15 +127.07 343.15 +130.89 353.15 +134.7 363.15 + diff --git a/tecs/inp/r10401.inp b/tecs/inp/r10401.inp new file mode 100644 index 0000000..7664a4d --- /dev/null +++ b/tecs/inp/r10401.inp @@ -0,0 +1,79 @@ +sens=r10401 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +10.96200458 3.603395939 +11.04714997 3.808389425 +11.13021051 4.011863947 +11.2073775 4.204595804 +11.36363222 4.605828285 +11.50949981 4.993322611 +11.69383035 5.504942894 +11.93243104 6.212180376 +12.18509969 7.012435913 +12.47627119 8.014698029 +12.74734121 9.034718037 +13.00782548 10.10107994 +13.23587728 11.11396694 +13.44662561 12.12006378 +13.64412098 13.1283412 +13.82350155 14.10537004 +13.99576341 15.10103607 +14.15889543 16.09725189 +14.31057818 17.07322216 +14.45655057 18.06075191 +14.5951817 19.0368576 +14.73183773 20.03655338 +14.87087365 21.09358788 +15.07781173 22.72771549 +15.26460339 24.24478149 +15.4628644 25.89118862 +15.65567767 27.49553299 +15.85444989 29.14401627 +16.08139617 30.97371197 +16.35794886 33.11646652 +16.77443694 36.13684464 +17.22711357 39.14133644 +17.71083059 42.07385445 +18.25288311 45.08248711 +18.84057851 48.0809536 +19.26707994 50.11228752 +20.3967488 55.07016945 +21.65691551 60.06259346 +23.03485099 65.08966827 +24.49958857 70.08788681 +26.03263916 75.05260086 +27.61641081 79.97705841 +29.31389895 85.09089661 +30.93957939 89.87670898 +32.71619025 95.01864243 +34.48065399 100.0529747 +38.00798124 110.0273895 +41.56033691 120.0323105 +45.104542 130.033226 +48.63416685 140.0548325 +52.12144721 150.0316315 +55.58240817 160.0153122 +59.02106315 170.0214767 +62.41786749 179.9794617 +65.80196734 189.977066 +69.16736962 199.9859848 +72.50752808 209.9737015 +75.83749417 219.9729462 +79.16022406 229.9922028 +82.45405462 239.9561462 +85.75238933 249.9529495 +89.04424414 259.9512482 +92.33610995 269.953186 +95.62668504 279.9625397 +98.90977798 289.950943 +102.1982893 299.9454956 +105.4870335 309.9390564 +107.1249122 314.9157104 +108.7501604 319.8446808 +110.735724 325.8632507 +112.0061582 329.714859 + diff --git a/tecs/inp/r10402.inp b/tecs/inp/r10402.inp new file mode 100644 index 0000000..fd1587c --- /dev/null +++ b/tecs/inp/r10402.inp @@ -0,0 +1,80 @@ +sens=r10402 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +10.8760399 3.60362947 +10.96156416 3.808573246 +11.04405501 4.011402369 +11.12172118 4.20448184 +11.27828274 4.605803728 +11.42410062 4.99340415 +11.60857321 5.504968882 +11.84771555 6.212155819 +12.10084347 7.012536526 +12.39236716 8.014623165 +12.6648384 9.034653187 +12.92509584 10.1014185 +13.15382122 11.11374331 +13.36476997 12.1199131 +13.56275485 13.12841368 +13.74237726 14.1056633 +13.91456868 15.10070419 +14.07806907 16.09651661 +14.22988723 17.07314491 +14.37653962 18.06040382 +14.51557176 19.03698158 +14.65198532 20.0368824 +14.79137027 21.09377289 +14.99888246 22.72714233 +15.18589533 24.24513531 +15.38513597 25.89107323 +15.57862236 27.49502659 +15.7781861 29.14448071 +16.01069201 31.00509262 +16.28352089 33.10315704 +16.70616645 36.14212799 +17.16219556 39.13899994 +17.65208858 42.07397842 +18.20100239 45.08285522 +18.7978474 48.08141899 +19.22993208 50.1128273 +20.37744592 55.07047462 +21.65843739 60.06211853 +23.06152406 65.08961487 +24.55309641 70.08821106 +26.11557305 75.0525322 +27.73038954 79.97639084 +29.46248067 85.09117508 +31.12198308 89.87803268 +32.9346229 95.01881409 +34.7358574 100.0531731 +38.33871566 110.0273514 +41.96687299 120.0326347 +45.5878966 130.0335617 +49.19480258 140.0551605 +52.75888613 150.0321045 +56.29611486 160.0150681 +59.8107402 170.0214767 +63.28329598 179.9793091 +66.74330971 189.9777985 +70.18486106 199.9863586 +73.60028459 209.9743118 +77.00348012 219.9716187 +80.40250057 229.9917068 +83.77295968 239.956543 +87.14592329 249.9542999 +90.51287247 259.951004 +93.87840797 269.9521942 +97.24650837 279.9622955 +100.6056404 289.9507294 +103.9689725 299.9463196 +107.3335317 309.9401703 +109.0114567 314.9165039 +110.6735137 319.8454895 +112.7047006 325.8605194 +114.0035247 329.7149658 + + diff --git a/tecs/inp/r10403.inp b/tecs/inp/r10403.inp new file mode 100644 index 0000000..a77f891 --- /dev/null +++ b/tecs/inp/r10403.inp @@ -0,0 +1,79 @@ +sens=r10403 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +10.6589403 3.603681803 +10.74693977 3.808842421 +10.83184562 4.011125088 +10.91174656 4.204480171 +11.07008341 4.605695724 +11.22122242 4.993436098 +11.41199261 5.50510931 +11.65901085 6.211949348 +11.91981091 7.012576103 +12.2204079 8.014651299 +12.50069799 9.034644127 +12.77010674 10.10183287 +13.00552529 11.11413336 +13.22311022 12.11994553 +13.42717567 13.12845087 +13.61233701 14.10592365 +13.79031137 15.10077524 +13.95889108 16.09677029 +14.11560108 17.07359982 +14.26661806 18.05983448 +14.40984191 19.03727055 +14.5506561 20.03670979 +14.69458498 21.09279442 +14.90837715 22.72693634 +15.10083847 24.24472809 +15.30573011 25.89060211 +15.50466727 27.49477291 +15.70943846 29.14482689 +15.94295831 30.97421741 +16.22611694 33.10346222 +16.65634655 36.1368618 +17.12132175 39.14064407 +17.61812467 42.07350922 +18.17453481 45.08229637 +18.77835056 48.08135033 +19.21609154 50.11287498 +20.37406579 55.07047844 +21.66598185 60.0625267 +23.07960366 65.09007263 +24.58132513 70.08819199 +26.15302615 75.05251312 +27.77673525 79.97599792 +29.46796366 84.94778442 +31.18561739 89.8794136 +33.0060656 95.01772308 +34.81426904 100.0529938 +38.43009061 110.0272751 +42.07047262 120.0328369 +45.70143982 130.033226 +49.31827048 140.0540085 +52.89095876 150.0311432 +56.43606152 160.0155334 +59.95774205 170.0206146 +63.43579175 179.9800644 +66.90180014 189.9785233 +70.34817459 199.9858704 +73.7683642 209.9743729 +77.17653595 219.9694138 +80.57844445 229.9915466 +83.95262042 239.9578171 +87.32915214 249.9561996 +90.69928285 259.9510498 +94.06762515 269.9521942 +97.43635403 279.9628296 +100.7974683 289.9478302 +104.1636115 299.9465179 +107.5305484 309.9395905 +109.2074342 314.913208 +110.8721465 319.8458862 +112.9024567 325.8596039 +114.2030693 329.7140808 + diff --git a/tecs/inp/r10409.inp b/tecs/inp/r10409.inp new file mode 100644 index 0000000..18db70c --- /dev/null +++ b/tecs/inp/r10409.inp @@ -0,0 +1,79 @@ +sens=r10409 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +9.729170415 3.599108246 +9.807471838 3.803321687 +9.881845675 4.001753074 +9.957265507 4.207103188 +10.10350 4.61816441 +10.24228875 5.021928137 +10.410785 5.528922116 +10.63105014 6.237552611 +10.86503901 7.049164946 +11.13387651 8.061395715 +11.38170419 9.080734725 +11.60957717 10.0976095 +11.8195621 11.11087015 +12.01415805 12.12273009 +12.19446706 13.12911881 +12.36283488 14.13005143 +12.51995943 15.12442647 +12.66935165 16.11579786 +12.81007653 17.10486711 +12.94391933 18.09019724 +13.07237096 19.0755345 +13.1949312 20.05820485 +13.32639946 21.14015386 +13.51103315 22.72198464 +13.69095764 24.31474541 +13.87325086 25.94197347 +14.05668986 27.58107954 +14.24189955 29.21911493 +14.45529297 31.0435872 +14.71310716 33.15361727 +15.10856187 36.16515301 +15.54177718 39.16494333 +16.01885961 42.16002193 +16.5427227 45.15075969 +17.11695755 48.14860829 +17.52725932 50.1456511 +18.64965429 55.14566494 +19.89781828 60.1434804 +21.25761587 65.13728124 +22.71931573 70.14353926 +24.26164205 75.14741315 +25.87046285 80.14389681 +27.53314172 85.14013394 +29.23531558 90.13490689 +30.9691481 95.12797829 +32.72753293 100.1229978 +36.27911766 110.110687 +39.85278169 120.1148387 +43.41870181 130.1173515 +46.96443291 140.1164923 +50.48288963 150.1148961 +53.97146147 160.1096025 +57.43175462 170.1069592 +60.86523374 180.1062916 +64.27479903 190.1032814 +67.66523646 200.1075773 +71.03671919 210.1139431 +74.39215164 220.1093504 +77.73577068 230.1108131 +81.07100223 240.1174299 +84.3953144 250.1080443 +87.71790769 260.1094722 +91.03856598 270.1123165 +94.35407656 280.1091028 +97.67693531 290.1226426 +100.9949832 300.1250442 +104.3179636 310.129495 +105.9796676 315.1276046 +107.6379454 320.1110806 +109.6422158 326.1268823 +111.0285935 330.2873083 + diff --git a/tecs/inp/r10410.inp b/tecs/inp/r10410.inp new file mode 100644 index 0000000..2fe087b --- /dev/null +++ b/tecs/inp/r10410.inp @@ -0,0 +1,78 @@ +sens=r10410 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +12.58068823 3.598806592 +12.66306084 3.803442312 +12.7410223 4.001680131 +12.8210338 4.20709764 +12.97710152 4.618235636 +13.1230898 5.022066963 +13.29867076 5.528799323 +13.52929365 6.237803077 +13.77508522 7.048934695 +14.0576336 8.062176278 +14.31773149 9.080256293 +14.55677242 10.09779666 +14.77662013 11.11102988 +14.97981346 12.12292899 +15.16826951 13.12994855 +15.3446071 14.13025492 +15.50884301 15.12513888 +15.66392514 16.1156102 +15.81066881 17.10374642 +15.95077541 18.09019031 +16.08462175 19.07454745 +16.21359962 20.05822306 +16.35073534 21.14237772 +16.5449868 22.72232486 +16.73482941 24.31226008 +16.92775484 25.93997908 +17.12305555 27.57929224 +17.32211024 29.22035018 +17.55294293 31.04373335 +17.83386905 33.15392272 +18.26843841 36.16462578 +18.74828892 39.16600646 +19.2817418 42.16202069 +19.86905005 45.151956 +20.51666968 48.14943787 +20.98003721 50.14554243 +22.25058732 55.1451726 +23.66833689 60.14434928 +25.21554413 65.13988696 +26.87946909 70.1441475 +28.63762957 75.14621884 +30.47197022 80.14332999 +32.36866037 85.14028546 +34.31154667 90.13418258 +36.2901667 95.12906136 +38.29519638 100.1218635 +42.35015193 110.1119297 +46.42928475 120.1158606 +50.49939958 130.1172013 +54.5449155 140.1161408 +58.55936918 150.1136936 +62.54034881 160.1100822 +66.48828165 170.1071216 +70.40623874 180.1059648 +74.29591264 190.1031048 +78.16494783 200.1090007 +82.01248451 210.1129226 +85.84042483 220.1097379 +89.65721885 230.1112076 +93.46273224 240.1166241 +97.25778359 250.1091999 +101.0479148 260.1080664 +104.8374411 270.1144818 +108.6223805 280.1089581 +112.4145757 290.1237288 +116.2017584 300.122388 +119.9960341 310.13087 +121.891559 315.1259639 +123.784515 320.1104011 +126.0719231 326.1321421 +127.6521371 330.2883009 diff --git a/tecs/inp/r10411.inp b/tecs/inp/r10411.inp new file mode 100644 index 0000000..bd076f5 --- /dev/null +++ b/tecs/inp/r10411.inp @@ -0,0 +1,79 @@ +sens=r10411 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +11.15241065 3.598549137 +11.23534187 3.803801167 +11.31417869 4.001440484 +11.39446382 4.207125102 +11.55083746 4.618284438 +11.69842223 5.021909944 +11.87649662 5.528810983 +12.11219681 6.237523663 +12.36703307 7.048919689 +12.66213424 8.061683764 +12.93411426 9.080763591 +13.18400196 10.0972527 +13.41515005 11.11236792 +13.62886869 12.12261162 +13.82741367 13.12828524 +14.01251087 14.12897739 +14.18572384 15.12566897 +14.34898385 16.11534564 +14.50367713 17.10325811 +14.65146126 18.09073308 +14.79249557 19.07446221 +14.92791938 20.05810414 +15.07178961 21.14144212 +15.27497374 22.72337602 +15.47341191 24.31361868 +15.67373418 25.94066733 +15.87501014 27.58063058 +16.07999454 29.2214453 +16.31390726 31.04173729 +16.59872316 33.15457836 +17.03404068 36.16366638 +17.5114942 39.16653005 +18.03687617 42.16192419 +18.6133981 45.15116657 +19.24715751 48.1484099 +19.69888489 50.14523557 +20.9337894 55.14464977 +22.30776135 60.14418669 +23.80703205 65.14028307 +25.41612949 70.14212492 +27.11585546 75.14581757 +28.88798858 80.14199972 +30.72056809 85.14054741 +32.597439 90.13576567 +34.50920781 95.12947398 +36.4461102 100.1222304 +40.36410719 110.111688 +44.30568855 120.1163428 +48.24088591 130.117383 +52.15368827 140.1159503 +56.03751264 150.1148139 +59.88873729 160.109784 +63.70904405 170.1066634 +67.50096353 180.1053116 +71.26508067 190.1040357 +75.01105085 200.1092107 +78.73559294 210.1115566 +82.44189545 220.1104795 +86.13644857 230.110938 +89.82284715 240.1166013 +93.49682661 250.1088672 +97.16763987 260.1074244 +100.8380921 270.1118291 +104.5031782 280.1110746 +108.1752369 290.1234121 +111.8428997 300.1248295 +115.5181419 310.1320373 +117.3533456 315.1268508 +119.1870942 320.1113579 +121.4010369 326.1289334 +122.9334825 330.2865207 + diff --git a/tecs/inp/r10413.inp b/tecs/inp/r10413.inp new file mode 100644 index 0000000..edfe1fe --- /dev/null +++ b/tecs/inp/r10413.inp @@ -0,0 +1,80 @@ +sens=r10413 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +11.42559142 3.598385454 +11.51171143 3.803268005 +11.59353158 4.00157268 +11.67688406 4.207329437 +11.82837068 4.618144037 +11.98394694 5.021858348 +12.17018175 5.528789092 +12.41496844 6.237407002 +12.67676917 7.049918401 +12.97681666 8.062010991 +13.25382567 9.080662996 +13.50835617 10.09774919 +13.74296812 11.11225719 +13.96076974 12.12325441 +14.16237372 13.12900439 +14.34991632 14.12937794 +14.52687058 15.12553459 +14.69279042 16.11656119 +14.84977516 17.10273663 +14.9998211 18.08966786 +15.14319204 19.07490412 +15.2802414 20.05761844 +15.42750157 21.13974046 +15.63309244 22.72136546 +15.8342691 24.31297152 +16.03710799 25.94238429 +16.24060934 27.57905532 +16.44705583 29.22007694 +16.68264142 31.03924792 +16.96834168 33.154185 +17.40474518 36.16469158 +17.88252873 39.167185 +18.40609557 42.1601927 +18.98205423 45.14999317 +19.61161709 48.148469 +20.06265581 50.14456657 +21.29013015 55.14342488 +22.65571481 60.14400512 +24.14456426 65.13972115 +25.74032261 70.14359461 +27.42759318 75.14666394 +29.1857745 80.14139051 +31.00465734 85.13905494 +32.86713162 90.13551272 +34.76469983 95.12921124 +36.68657447 100.122786 +40.57669938 110.1125852 +44.49072096 120.1168373 +48.39791863 130.1181727 +52.28333375 140.1163239 +56.14094126 150.1161882 +59.965605 160.1110684 +63.75889725 170.1076962 +67.5243713 180.1055757 +71.26170491 190.102184 +74.98010225 200.108561 +78.67818533 210.1126084 +82.35693215 220.1089513 +86.02412177 230.109857 +89.68288095 240.114188 +93.32885021 250.1083083 +96.97121127 260.1089139 +100.6135982 270.1128213 +104.2488495 280.1090995 +107.8915544 290.124649 +111.531171 300.1243045 +115.1764906 310.1293198 +116.9972804 315.1256513 +118.8149278 320.1110566 +121.0114513 326.1298075 +122.530488 330.2868637 + + diff --git a/tecs/inp/r3509.inp b/tecs/inp/r3509.inp new file mode 100644 index 0000000..bc2835a --- /dev/null +++ b/tecs/inp/r3509.inp @@ -0,0 +1,69 @@ +sens=r3509 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +form=loglog +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +1.53 1.001 +1.592 1.3 +1.654 1.7 +1.668 1.8 +1.685 1.9 +1.696 2 +1.729 2.2 +1.78 2.5 +1.85 3 +1.99 4 +2.014 4.21 +2.066 4.6 +2.116 5 +2.176 5.5 +2.234 6 +2.3 6.6 +2.362 7.2 +2.43 7.9 +2.504 8.7 +2.573 9.5 +2.645 10.4 +2.72 11.4 +2.796 12.5 +2.873 13.7 +2.95 15 +3.029 16.4 +3.11 18 +3.191 19.7 +3.277 21.6 +3.365 23.7 +3.458 26 +3.558 28.5 +3.666 31.2 +3.793 34.2 +3.941 37.5 +4.118 41.1 +4.336 45.1 +4.605 49.5 +4.93 54.3 +5.319 59.5 +5.788 65.2 +6.349 71.5 +6.904 77.348 +7.634 84.8 +8.471 93 +9.412 102 +10.453 111.8 +11.607 122.6 +12.865 134.4 +14.241 147.4 +15.729 161.6 +17.347 177.2 +19.1 194.3 +20.999 213 +23.066 233.5 +25.321 256 +27.037 273.15 +29.724 300 +32.733 330 + + diff --git a/tecs/inp/r3510.inp b/tecs/inp/r3510.inp new file mode 100644 index 0000000..f53a160 --- /dev/null +++ b/tecs/inp/r3510.inp @@ -0,0 +1,69 @@ +sens=r3510 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +form=loglog +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +1.433 1.001 +1.515 1.3 +1.597 1.7 +1.626 1.8 +1.638 1.9 +1.65 2 +1.681 2.2 +1.728 2.5 +1.812 3 +1.962 4 +1.989 4.21 +2.04 4.6 +2.09 5 +2.151 5.5 +2.209 6 +2.274 6.6 +2.337 7.2 +2.405 7.9 +2.479 8.7 +2.547 9.5 +2.62 10.4 +2.695 11.4 +2.771 12.5 +2.848 13.7 +2.925 15 +3.005 16.4 +3.085 18 +3.167 19.7 +3.253 21.6 +3.341 23.7 +3.434 26 +3.534 28.5 +3.643 31.2 +3.769 34.2 +3.918 37.5 +4.095 41.1 +4.313 45.1 +4.582 49.5 +4.909 54.3 +5.298 59.5 +5.767 65.2 +6.33 71.5 +6.885 77.348 +7.615 84.8 +8.451 93 +9.392 102 +10.433 111.8 +11.586 122.6 +12.843 134.4 +14.219 147.4 +15.707 161.6 +17.324 177.2 +19.077 194.3 +20.975 213 +23.041 233.5 +25.296 256 +27.011 273.15 +29.697 300 +32.705 330 + + diff --git a/tecs/inp/rdr11.cfg b/tecs/inp/rdr11.cfg new file mode 100644 index 0000000..c65f94c --- /dev/null +++ b/tecs/inp/rdr11.cfg @@ -0,0 +1,6 @@ + sensA.type=m sensA.curve=rx1976 sensA.scale=0.01 + dev="LTF dilution cryostat" + tlimit=12.0 resist=708 maxPower=0.01 powfact=0.03 + prop=50 int=10 deriv=0 + lscfg="INCRV C,0;LINEAR C:2,0.01,1,2;DISPFLD 2,C,4;DISPFLD 3,A,3;DISPLAY:3" + diff --git a/tecs/inp/rdr12.cfg b/tecs/inp/rdr12.cfg new file mode 100644 index 0000000..5351238 --- /dev/null +++ b/tecs/inp/rdr12.cfg @@ -0,0 +1,6 @@ + sensA.type=m sensA.curve=rx1611 sensA.scale=0.01 + dev="LTF dilution cryostat" + tlimit=12.0 resist=708 maxPower=0.01 powfact=0.03 + prop=50 int=10 deriv=0 + lscfg="INCRV C,0;LINEAR C:2,0.01,1,2;DISPFLD 2,C,4;DISPFLD 3,A,3;DISPLAY:3" + diff --git a/tecs/inp/rhfe0734.inp b/tecs/inp/rhfe0734.inp new file mode 100644 index 0000000..dae0435 --- /dev/null +++ b/tecs/inp/rhfe0734.inp @@ -0,0 +1,124 @@ +sens=rhfe0734 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing ++1.68 0.5831 ++1.73 0.8616 ++1.78 1.1426 ++1.83 1.4276 ++1.88 1.7179 ++1.93 2.0148 ++1.98 2.3195 ++2.03 2.6331 ++2.08 2.957 ++2.13 3.292 ++2.18 3.6391 ++2.23 3.9993 ++2.28 4.3734 ++2.33 4.7622 ++2.38 5.1668 ++2.43 5.5881 ++2.48 6.0273 ++2.53 6.4856 ++2.58 6.9644 ++2.63 7.465 ++2.68 7.9888 ++2.73 8.5374 ++2.78 9.1123 ++2.83 9.7149 ++2.88 10.3469 ++2.93 11.0099 ++2.98 11.7059 ++3.03 12.4366 ++3.08 13.2041 ++3.13 14.0107 ++3.18 14.8583 ++3.23 15.7491 ++3.28 16.685 ++3.33 17.6671 ++3.38 18.6961 ++3.43 19.7717 ++3.48 20.8922 ++3.53 22.0546 ++3.58 23.254 ++3.63 24.4842 ++3.68 25.7372 ++3.73 27.0041 ++3.78 28.275 ++3.83 29.5403 ++3.88 30.7913 ++3.93 32.0212 ++3.98 33.2277 ++4.03 34.4064 ++4.08 35.5549 ++4.13 36.6724 ++4.18 37.7591 ++4.23 38.8156 ++4.28 39.8428 ++4.33 40.8421 ++4.43 42.7622 ++4.53 44.5869 ++4.63 46.3269 ++4.73 47.992 ++4.83 49.5908 ++4.93 51.1309 ++5.03 52.6189 ++5.13 54.0603 ++5.23 55.4602 ++5.33 56.8226 ++5.43 58.1513 ++5.53 59.4494 ++5.63 60.7198 ++5.73 61.9649 ++5.83 63.1869 ++5.93 64.3876 ++6.03 65.5689 ++6.13 66.7323 ++6.23 67.8791 ++6.33 69.0106 ++6.43 70.1279 ++6.53 71.232 ++6.63 72.324 ++6.73 73.4046 ++6.83 74.4746 ++6.93 75.5348 ++7.03 76.5858 ++7.13 77.6282 ++7.23 78.6626 ++7.33 79.6895 ++7.43 80.7094 ++7.53 81.7228 ++7.63 82.7301 ++7.73 83.7316 ++7.83 84.7278 ++7.93 85.7189 ++8.03 86.7054 ++8.13 87.6875 ++8.23 88.6655 ++8.33 89.6396 ++9.33 99.2177 ++10.33 108.6138 ++11.33 117.9369 ++12.33 127.252 ++13.33 136.5978 ++14.33 145.9964 ++15.33 155.4592 ++16.33 164.9901 ++17.33 174.5886 ++18.33 184.251 ++19.33 193.9718 ++20.33 203.7444 ++21.33 213.5617 ++22.33 223.4166 ++23.33 233.3019 ++24.33 243.211 ++25.33 253.1376 ++26.33 263.076 ++27.33 273.0207 ++29.33 292.9108 ++31.33 312.7801 ++33.33 332.6028 + diff --git a/tecs/inp/rhfe4140.inp b/tecs/inp/rhfe4140.inp new file mode 100644 index 0000000..671266c --- /dev/null +++ b/tecs/inp/rhfe4140.inp @@ -0,0 +1,53 @@ +sens=rhfe4140 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +1.58190 1.468 +1.67400 1.993 +1.80593 2.791 +1.87062 3.208 +1.98346 3.979 +2.01446 4.201 +2.17064 5.409 +2.35384 7.032 +2.45031 7.993 +2.63333 10.061 +2.84964 13.002 +3.03325 16.021 +3.23588 20.015 +3.45195 24.998 +3.55119 27.449 +3.65991 30.129 +3.87224 35.144 +4.10610 40.104 +4.68439 50.174 +5.43016 60.491 +6.25613 70.218 +7.22886 80.535 +8.24755 90.660 +9.29999 100.749 +11.9067 125.232 +14.6048 150.712 +17.1906 175.593 +19.7720 200.866 +22.2457 225.394 +24.7721 250.638 +27.0084 273.062 +27.0370 273.347 +29.7624 300.665 +32.154 325 +34.638 350 +37.136 375 +39.652 400 +42.189 425 +44.747 450 +47.329 475 +49.937 500 +60.644 600 +71.825 700 +83.522 800 + + diff --git a/tecs/inp/rhfe8119.inp b/tecs/inp/rhfe8119.inp new file mode 100644 index 0000000..5833129 --- /dev/null +++ b/tecs/inp/rhfe8119.inp @@ -0,0 +1,66 @@ +sens=rhfe8119 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +1.6835 1.0 +1.7566 1.408 +1.7745 1.508 +1.7925 1.609 +1.8617 2.006 +1.9298 2.41 +1.9932 2.8 +2.0569 3.208 +2.1158 3.602 +2.1776 4.032 +2.2019 4.207 +2.2559 4.607 +2.3591 5.42 +2.4535 6.224 +2.5469 7.085 +2.6428 8.044 +2.7344 9.041 +2.8239 10.097 +2.9026 11.099 +3.0388 13.018 +3.1086 14.103 +3.2263 16.105 +3.3306 18.075 +3.4277 20.081 +3.5359 22.497 +3.6426 25.036 +3.7436 27.529 +3.8446 30.018 +3.9485 32.539 +4.0556 35.035 +4.2955 40.16 +4.8847 50.442 +5.599 60.391 +6.443 70.418 +7.3254 79.886 +8.3393 90.091 +9.3943 100.318 +12.1072 126.038 +14.6989 150.738 +17.2882 175.872 +19.8227 200.897 +22.3245 225.909 +25.0177 253.046 +27.0043 273.132 +27.033 273.422 +29.7561 300.957 +32.138 325 +34.625 350 +37.126 375 +39.645 400 +42.185 425 +44.747 450 +47.333 475 +49.944 500 +60.669 600 +71.872 700 +83.594 800 + + diff --git a/tecs/inp/rhfe8244.inp b/tecs/inp/rhfe8244.inp new file mode 100644 index 0000000..c0d6c77 --- /dev/null +++ b/tecs/inp/rhfe8244.inp @@ -0,0 +1,65 @@ +sens=rhfe8244 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +1.725 1.000 +1.8003 1.405 +1.8182 1.505 +1.8369 1.608 +1.9076 2.011 +1.9742 2.406 +2.0379 2.798 +2.1019 3.207 +2.1613 3.603 +2.2206 4.016 +2.2472 4.208 +2.3013 4.609 +2.4027 5.406 +2.496 6.2 +2.5855 7.02 +2.6865 8.027 +2.7792 9.035 +2.867 10.073 +2.9446 11.062 +3.0836 13.023 +3.148 14.022 +3.2661 16.025 +3.374 18.062 +3.4691 20.026 +3.5803 22.515 +3.6853 25.021 +3.786 27.512 +3.8865 29.992 +3.9919 32.551 +4.0991 35.048 +4.3341 40.073 +4.9331 50.537 +5.6366 60.342 +6.4825 70.406 +7.3813 80.053 +8.4119 90.424 +9.4424 100.416 +12.0995 125.632 +14.6813 150.259 +17.2466 175.171 +19.7776 200.18 +22.4707 227.132 +24.7622 250.24 +27.0121 273.003 +27.0474 273.361 +29.7123 300.333 +32.154 325 +34.638 350 +37.136 375 +39.652 400 +42.189 425 +44.747 450 +47.329 475 +49.937 500 +60.644 600 +71.825 700 +83.522 800 + diff --git a/tecs/inp/rhfe8733.inp b/tecs/inp/rhfe8733.inp new file mode 100644 index 0000000..be0f80f --- /dev/null +++ b/tecs/inp/rhfe8733.inp @@ -0,0 +1,51 @@ +sens=rhfe8733 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +type=RhFe ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +1.5 0.3 +1.8843 1.403 +1.9039 1.512 +1.9202 1.602 +1.9943 2.027 +2.0584 2.406 +2.1234 2.807 +2.1851 3.203 +2.2447 3.602 +2.3004 3.99 +2.3296 4.201 +2.384 4.606 +2.4846 5.399 +2.579 6.204 +2.6712 7.055 +2.7701 8.05 +2.8585 9.015 +2.9456 10.045 +3.0235 11.038 +3.163 13.009 +3.2269 14.005 +3.3462 16.034 +3.4507 18.011 +3.5494 20.058 +3.6584 22.508 +3.7656 25.076 +3.8655 27.552 +3.9648 30.013 +4.0684 32.538 +4.1735 34.997 +4.4278 40.426 +5.0004 50.424 +5.7174 60.443 +6.558 70.46 +7.4811 80.374 +8.4707 90.355 +9.5417 100.762 +12.1855 125.915 +14.8417 151.328 +17.57 177.929 +19.9341 201.373 +22.4906 227.031 +25.0243 252.655 +27.0197 272.902 +27.0698 273.411 +29.6913 300.022 + diff --git a/tecs/inp/ruox.inp b/tecs/inp/ruox.inp new file mode 100644 index 0000000..7fb5e42 --- /dev/null +++ b/tecs/inp/ruox.inp @@ -0,0 +1,68 @@ +sens=ruox +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=2 ! setpoint limit (automatic if omitted) +type=Special ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +excit=10uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +form=loglog +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +230000 1 +226072 1.5 +222012 2 +210329 3 +198151 4 +187643 5 +178843 6 +171468 7 +165280 8 +160065 9 +155637 10 +151767 11 +148389 12 +145436 13 +142813 14 +140481 15 +138397 16 +136518 17 +134812 18 +133271 19 +131859 20 +130555 21 +129358 22 +128254 23 +127220 24 +126230 25 +125316 26 +124477 27 +123702 28 +122973 29 +122284 30 +121633 31 +121016 32 +120429 33 +119872 34 +119367 35 +118841 36 +118253 37 +117738 38 +117316 39 +116914 40 +113657 50 +111329 60 +109586 70 +108602 77 +108231 80 +107147 90 +106248 100 +104529 125 +103291 150 +102362 175 +101669 200 +101148 225 +100773 250 +100556 270 +100530 273 +100001 295 +100000 295.01 +50000 300 + diff --git a/tecs/inp/rx1611.inp b/tecs/inp/rx1611.inp new file mode 100644 index 0000000..683c1c5 --- /dev/null +++ b/tecs/inp/rx1611.inp @@ -0,0 +1,89 @@ +sens=rx1611 +unit=V ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=2 ! setpoint limit (automatic if omitted) +type=Special ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +excit=30uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +range=2 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (volts, cKelvin) +0.1 1206.521654 +0.105 993.8222225 +0.1103 824.4082243 +0.1158 691.0146685 +0.1216 583.2109748 +0.1277 495.6595691 +0.1341 424.1693739 +0.1408 365.4568244 +0.1478 316.9499646 +0.1552 276.1386601 +0.163 241.7266404 +0.1712 212.626728 +0.1798 187.9352325 +0.1888 166.905356 +0.1982 148.9221064 +0.2081 133.3368629 +0.2185 119.8072354 +0.2294 108.0366429 +0.2409 97.68815706 +0.2529 88.65305941 +0.2655 80.68121887 +0.2788 73.58832758 +0.2927 67.31900363 +0.3073 61.72973563 +0.3227 56.71224548 +0.3388 52.23482387 +0.3557 48.21039972 +0.3735 44.57191657 +0.3922 41.28323672 +0.4118 38.31003269 +0.4324 35.60812694 +0.454 33.15299196 +0.4767 30.91215327 +0.5005 28.86745908 +0.5255 26.99446317 +0.5518 25.27322246 +0.5794 23.69261318 +0.6084 22.23685759 +0.6388 20.89692543 +0.6707 19.66021856 +0.7042 18.51614313 +0.7394 17.45569276 +0.7764 16.47112933 +0.8152 15.55795099 +0.856 14.70755522 +0.8988 13.91657457 +0.9437 13.17986919 +0.9909 12.49152745 +1.0404 11.84919396 +1.0924 11.24811677 +1.147 10.68535851 +1.2044 10.15734895 +1.2646 9.662651321 +1.3278 9.198237347 +1.3942 8.761545253 +1.4639 8.350940465 +1.5371 7.9643521 +1.614 7.599982053 +1.6947 7.256655057 +1.7794 6.932848325 +1.8684 6.626884532 +1.9618 6.337944626 +2.0599 6.064660729 +2.1629 5.806107119 +2.271 5.561426086 +2.3846 5.329430748 +2.5038 5.109661957 +2.629 4.901140994 +2.7605 4.703186509 +2.8985 4.515313629 +3.0434 4.33680883 +3.1956 4.16705561 +3.3554 4.005611036 +3.5232 3.851970924 +3.6994 3.705686023 +3.8844 3.566351517 +4.0786 3.433598749 +4.2825 3.307029581 +4.4966 3.18629209 +4.7214 3.071071466 +4.9575 2.961038374 + diff --git a/tecs/inp/rx1976.inp b/tecs/inp/rx1976.inp new file mode 100644 index 0000000..9068974 --- /dev/null +++ b/tecs/inp/rx1976.inp @@ -0,0 +1,63 @@ +sens=rx1976 +unit=mV ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=2 ! setpoint limit (automatic if omitted) +type=Special ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +range=0 +excit=30uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +curv ! curve mV,K (200 kOhm Range) +607.88 0.02 +593.99 0.021 +567.92 0.023 +543.86 0.025 +490.69 0.03 +445.36 0.035 +406.08 0.04 +371.81 0.045 +341.79 0.05 +254.67 0.07 +203.01 0.09 +170.69 0.11 +148.94 0.13 +133.29 0.15 +118.96 0.175 +108.21 0.20 +99.84 0.225 +93.09 0.25 +82.81 0.30 +75.29 0.35 +69.53 0.40 +64.95 0.45 +61.22 0.50 +55.49 0.60 +51.31 0.70 +48.11 0.80 +45.59 0.90 +43.56 1.00 +39.83 1.25 +37.29 1.50 +35.43 1.75 +34.01 2.00 +32.87 2.25 +31.94 2.50 +31.16 2.75 +30.50 3.00 +29.92 3.25 +29.42 3.50 +28.97 3.75 +28.57 4.00 +28.27 4.20 +27.45 5.00 +26.77 6.00 +25.82 8.00 +25.20 10.00 +24.60 13.00 +24.10 17.00 +23.71 22.00 +23.38 29.00 +23.15 37.00 +22.91 50.00 +22.75 67.00 +22.62 90.00 +22.51 120.00 +22.00 300.00 + diff --git a/tecs/inp/rxdil.inp b/tecs/inp/rxdil.inp new file mode 100644 index 0000000..fd8b3f7 --- /dev/null +++ b/tecs/inp/rxdil.inp @@ -0,0 +1,62 @@ +sens=rxdil +unit=mV ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=2 ! setpoint limit (automatic if omitted) +type=Special ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +excit=30uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +range=2000 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (volts, cKelvin) +607.88 0.02 +593.99 0.021 +567.92 0.023 +543.86 0.025 +490.69 0.03 +445.36 0.035 +406.08 0.04 +371.81 0.045 +341.79 0.05 +254.67 0.07 +203.01 0.09 +170.69 0.11 +148.94 0.13 +133.29 0.15 +118.96 0.175 +108.21 0.20 +99.84 0.225 +93.09 0.25 +82.81 0.30 +75.29 0.35 +69.53 0.40 +64.95 0.45 +61.22 0.50 +55.49 0.60 +51.31 0.70 +48.11 0.80 +45.59 0.90 +43.56 1.00 +39.83 1.25 +37.29 1.50 +35.43 1.75 +34.01 2.00 +32.87 2.25 +31.94 2.50 +31.16 2.75 +30.50 3.00 +29.92 3.25 +29.42 3.50 +28.97 3.75 +28.57 4.00 +28.27 4.20 +27.45 5.00 +26.77 6.00 +25.82 8.00 +25.20 10.00 +24.60 13.00 +24.10 17.00 +23.71 22.00 +23.38 29.00 +23.15 37.00 +22.91 50.00 +22.75 67.00 +22.62 90.00 +22.51 120.00 +22.00 300.00 diff --git a/tecs/inp/std1.inp b/tecs/inp/std1.inp new file mode 100644 index 0000000..6fe5488 --- /dev/null +++ b/tecs/inp/std1.inp @@ -0,0 +1,2 @@ +sens=std1 +curv=1 diff --git a/tecs/inp/std4.inp b/tecs/inp/std4.inp new file mode 100644 index 0000000..5d7aaf7 --- /dev/null +++ b/tecs/inp/std4.inp @@ -0,0 +1,2 @@ +sens=std4 +curv=4 diff --git a/tecs/inp/std6.inp b/tecs/inp/std6.inp new file mode 100644 index 0000000..87845e0 --- /dev/null +++ b/tecs/inp/std6.inp @@ -0,0 +1,2 @@ +sens=std6 +curv=6 diff --git a/tecs/inp/sup4t.cfg b/tecs/inp/sup4t.cfg new file mode 100644 index 0000000..4e9c9bf --- /dev/null +++ b/tecs/inp/sup4t.cfg @@ -0,0 +1,5 @@ + sensA.type=m sensA.curve=ruox + sensB.type=h + dev="4 T vertical cryomagnet" + tlimit=273 resist=440 maxPower=5 full=4.6 + prop=20 int=3 deriv=0 diff --git a/tecs/inp/tubby.cfg b/tecs/inp/tubby.cfg new file mode 100644 index 0000000..0c5a071 --- /dev/null +++ b/tecs/inp/tubby.cfg @@ -0,0 +1,6 @@ + sensA.type=m sensA.curve=x67 + sensB.type=t sensB.curve=std4 + sensD.type=s sensD.curve=x23167 + dev="11 T horizontal SANS cryomagnet" + tlimit=310 resist=50 maxpower=12.5 + prop=10 int=10 deriv=0 diff --git a/tecs/inp/tubby2.cfg b/tecs/inp/tubby2.cfg new file mode 100644 index 0000000..f5bce39 --- /dev/null +++ b/tecs/inp/tubby2.cfg @@ -0,0 +1,4 @@ + sensC.type=s sensC.curve=x17627 + dev="rotatable sample stick for 11 T cryomagnet" + tlimit=310 resist=50 maxpower=12.5 + prop=10 int=10 deriv=0 diff --git a/tecs/inp/type_c.inp b/tecs/inp/type_c.inp new file mode 100644 index 0000000..cbaee24 --- /dev/null +++ b/tecs/inp/type_c.inp @@ -0,0 +1,157 @@ +sens=type_c +unit=mV +type=TC ! kinked at 333.15 (scale=2) +curv +-0.135 263.15 +0.135 283.15 +0.273 293.15 +0.412 303.15 +0.554 313.15 +0.699 323.15 +0.845 333.15 +0.994 338.15 +1.144 343.15 +1.297 348.15 +1.451 353.15 +1.607 358.15 +1.766 363.15 +1.925 368.15 +2.087 373.15 +2.25 378.15 +2.415 383.15 +2.581 388.15 +2.749 393.15 +2.919 398.15 +3.089 403.15 +3.261 408.15 +3.435 413.15 +3.609 418.15 +3.785 423.15 +3.962 428.15 +4.141 433.15 +4.32 438.15 +4.5 443.15 +4.682 448.15 +4.864 453.15 +5.047 458.15 +5.231 463.15 +5.416 468.15 +5.602 473.15 +5.788 478.15 +5.976 483.15 +6.164 488.15 +6.352 493.15 +6.541 498.15 +6.731 503.15 +6.922 508.15 +7.113 513.15 +7.304 518.15 +7.496 523.15 +7.688 528.15 +7.881 533.15 +8.074 538.15 +8.268 543.15 +8.461 548.15 +8.655 553.15 +8.85 558.15 +9.044 563.15 +9.239 568.15 +9.434 573.15 +9.629 578.15 +9.824 583.15 +10.02 588.15 +10.215 593.15 +10.411 598.15 +10.606 603.15 +10.802 608.15 +10.997 613.15 +11.193 618.15 +11.388 623.15 +11.584 628.15 +11.779 633.15 +11.974 638.15 +12.169 643.15 +12.364 648.15 +12.559 653.15 +12.753 658.15 +12.948 663.15 +13.142 668.15 +13.336 673.15 +13.53 678.15 +13.723 683.15 +13.916 688.15 +14.109 693.15 +14.302 698.15 +14.494 703.15 +14.686 708.15 +14.878 713.15 +15.069 718.15 +15.26 723.15 +15.451 728.15 +15.641 733.15 +15.831 738.15 +16.02 743.15 +16.209 748.15 +16.397 753.15 +16.585 758.15 +16.773 763.15 +16.96 768.15 +17.147 773.15 +17.333 778.15 +17.519 783.15 +17.704 788.15 +17.889 793.15 +18.074 798.15 +18.257 803.15 +18.623 813.15 +18.987 823.15 +19.349 833.15 +19.709 843.15 +20.066 853.15 +20.422 863.15 +20.775 873.15 +21.125 883.15 +21.474 893.15 +21.82 903.15 +22.163 913.15 +22.505 923.15 +22.844 933.15 +23.18 943.15 +23.514 953.15 +23.846 963.15 +24.175 973.15 +24.502 983.15 +24.827 993.15 +25.149 1003.15 +25.468 1013.15 +25.785 1023.15 +26.1 1033.15 +26.413 1043.15 +26.723 1053.15 +27.03 1063.15 +27.335 1073.15 +27.638 1083.15 +27.938 1093.15 +28.236 1103.15 +28.531 1113.15 +28.824 1123.15 +29.115 1133.15 +29.403 1143.15 +29.688 1153.15 +29.971 1163.15 +30.252 1173.15 +30.53 1183.15 +30.806 1193.15 +31.079 1203.15 +31.349 1213.15 +31.617 1223.15 +31.882 1233.15 +32.145 1243.15 +32.404 1253.15 +32.661 1263.15 +32.915 1273.15 +33.167 1283.15 +33.415 1293.15 +33.66 1303.15 + + diff --git a/tecs/inp/variox.cfg b/tecs/inp/variox.cfg new file mode 100644 index 0000000..043af09 --- /dev/null +++ b/tecs/inp/variox.cfg @@ -0,0 +1,5 @@ + sensA.type=m sensA.curve=x12533 + dev="variox cryostat" + tlimit=375 resist=25 maxpower=25 + prop=20 int=10 deriv=0 + loop=2 diff --git a/tecs/inp/x09882.inp b/tecs/inp/x09882.inp new file mode 100644 index 0000000..fe057b4 --- /dev/null +++ b/tecs/inp/x09882.inp @@ -0,0 +1,92 @@ +sens=x09882 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +14797.9 1.19193 +12448.4 1.29974 +10982.6 1.38715 +8547.47 1.59428 +7041.63 1.79221 +5911 2.00599 +5115.55 2.21219 +4531.17 2.41069 +4078.98 2.6051 +3727.92 2.79063 +3402.6 2.99993 +3128.16 3.21371 +2913.34 3.41252 +2734.11 3.60403 +2569.37 3.80774 +2431.76 4.0002 +2312.38 4.1892 +2096.39 4.59514 +1922.56 4.99537 +1744.81 5.50526 +1549.77 6.22335 +1383.86 7.02472 +1222.31 8.06177 +1100.15 9.09066 +1002.21 10.1355 +924.021 11.1589 +859.364 12.1735 +804.651 13.185 +758.845 14.162 +718.001 15.1556 +681.881 16.1464 +650.369 17.1142 +621.743 18.0865 +596.067 19.0522 +572.129 20.0353 +548.69 21.0945 +516.935 22.695 +490.347 24.2048 +465.176 25.8072 +442.439 27.4145 +422.126 29.018 +401.43 30.8186 +379.561 32.9565 +352.698 35.9509 +329.394 38.968 +309.122 41.9784 +291.451 44.9523 +275.567 47.9705 +266.007 49.9734 +244.814 54.9644 +226.895 59.9372 +211.835 64.8041 +198.257 69.8265 +186.421 74.8073 +175.994 79.76 +166.615 84.7645 +158.17 89.757 +150.595 94.7278 +143.445 99.88 +131.348 109.891 +121.126 119.886 +112.336 129.879 +104.767 139.858 +98.1002 149.874 +92.2394 159.86 +87.0447 169.871 +82.4096 179.84 +78.2514 189.848 +74.5122 199.87 +71.1115 209.86 +68.0321 219.844 +65.2143 229.889 +62.6401 239.915 +60.2922 249.884 +58.1205 259.897 +56.124 269.929 +54.28 279.941 +52.5664 289.964 +50.9743 300.009 +49.4965 310.068 +48.7925 315.086 +48.1168 320.089 +47.3448 326.091 +46.8369 330.089 + diff --git a/tecs/inp/x09883.inp b/tecs/inp/x09883.inp new file mode 100644 index 0000000..205cbcc --- /dev/null +++ b/tecs/inp/x09883.inp @@ -0,0 +1,92 @@ +sens=x09883 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +50697.2 1.19172 +40559.1 1.2997 +34512.9 1.38772 +25063.8 1.59429 +19577.5 1.79224 +15681.2 2.00579 +13072.2 2.21208 +11222.3 2.41069 +9847.35 2.6034 +8791.26 2.7906 +7846.7 3.00005 +7069.93 3.21374 +6474.44 3.41239 +5988.04 3.60402 +5544.72 3.80786 +5182.73 4.00017 +4871.97 4.1891 +4322.43 4.59508 +3890.99 4.99554 +3458.11 5.50564 +2996.38 6.22351 +2615.51 7.0249 +2254.83 8.06193 +1988.83 9.09068 +1780.29 10.1358 +1617.51 11.1589 +1484.58 12.1733 +1373.99 13.1848 +1282.45 14.1616 +1202 15.1558 +1131.5 16.1467 +1070.43 17.1145 +1015.81 18.0864 +967.127 19.0523 +922.097 20.0348 +878.301 21.0942 +819.492 22.695 +771.027 24.2035 +725.442 25.8078 +684.833 27.4152 +648.656 29.0175 +612.282 30.8184 +574.104 32.9566 +527.93 35.951 +488.247 38.9681 +454.161 41.9788 +424.745 44.9516 +398.466 47.9702 +382.78 49.9734 +348.448 54.9642 +319.762 59.9372 +295.798 64.8036 +274.497 69.8262 +256.115 74.8066 +240.064 79.7602 +225.652 84.764 +212.863 89.7568 +201.482 94.7284 +190.788 99.8804 +172.849 109.891 +157.882 119.887 +145.172 129.88 +134.301 139.858 +124.826 149.873 +116.577 159.861 +109.293 169.871 +102.863 179.841 +97.1221 189.85 +91.9646 199.871 +87.3432 209.859 +83.1778 219.842 +79.3655 229.891 +75.9226 239.917 +72.7733 249.883 +69.8839 259.896 +67.2351 269.927 +64.7933 279.942 +62.5416 289.965 +60.4496 300.008 +58.5077 310.066 +57.5961 315.084 +56.712 320.09 +55.6983 326.087 +55.0466 330.089 + diff --git a/tecs/inp/x09941.inp b/tecs/inp/x09941.inp new file mode 100644 index 0000000..fd57ebb --- /dev/null +++ b/tecs/inp/x09941.inp @@ -0,0 +1,79 @@ +sens=x09941 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +89109.92656 3.592342734 +75927.84882 3.80771172 +66873.53337 3.992385149 +58461.84522 4.203659534 +44177.58035 4.711746931 +36572.40042 5.100198746 +29499.39651 5.611691713 +22954.09467 6.309052944 +17974.18138 7.115644217 +13888.58545 8.139806747 +11049.51828 9.232270241 +9014.528883 10.37906504 +7650.452644 11.44719648 +6625.778004 12.50353575 +5832.554093 13.54768562 +5202.695698 14.5772028 +4707.313975 15.55929899 +4291.544831 16.54255772 +3945.424009 17.49967384 +3650.35765 18.44649696 +3395.003004 19.38338852 +3166.788192 20.33590603 +2961.395028 21.30691433 +2692.155406 22.77910137 +2440.49331 24.41886806 +2236.687306 25.98587322 +2061.626067 27.54995251 +1907.050891 29.14138508 +1758.477449 30.91228008 +1606.203424 33.02730751 +1428.689702 35.99930763 +1283.046021 38.97810364 +1161.33904 41.98565865 +1059.899025 44.95008087 +972.8716648 47.94148254 +921.8402765 49.92553711 +813.9183038 54.87852478 +727.6791559 59.77289772 +657.3901952 64.61587906 +597.3237814 69.57008362 +545.9993931 74.58304977 +502.235637 79.57922745 +464.7514845 84.53449631 +431.8887078 89.51391983 +403.4046886 94.43180466 +376.4541741 99.69680786 +333.2715871 109.7288055 +298.4388825 119.7237396 +269.6344771 129.7141037 +245.6040149 139.6854935 +225.5918325 149.4456711 +207.8105273 159.5582657 +192.8477201 169.3871689 +179.54412 179.4086685 +168.028657 189.2752991 +157.8098318 199.1471634 +148.5936477 209.1398315 +140.4454005 219.0371552 +133.0699767 228.9918213 +126.4626969 238.8810654 +120.4248519 248.837532 +114.9800847 258.7176971 +109.9841984 268.6493378 +105.4154935 278.5511017 +101.2011797 288.5041351 +97.36067783 298.3769836 +93.82776671 308.21138 +92.11573271 313.2369537 +90.48969767 318.2412415 +88.57005094 324.3699188 +87.17269938 329.0235748 + diff --git a/tecs/inp/x10045.inp b/tecs/inp/x10045.inp new file mode 100644 index 0000000..2562584 --- /dev/null +++ b/tecs/inp/x10045.inp @@ -0,0 +1,93 @@ +sens=x10045 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +74663.91424 0.833452742 +60860.05098 0.94945966 +49551.87681 1.077803432 +35363.88586 1.32313617 +27025.56488 1.558155166 +21164.07675 1.807418904 +17439.43364 2.03304067 +14660.90306 2.26104489 +12674.48887 2.474474502 +11040.01571 2.699494433 +9785.229203 2.916614022 +8788.251677 3.12854605 +7989.704459 3.332865003 +7286.655618 3.552242447 +6732.86304 3.758944594 +6251.098886 3.968357998 +5847.432327 4.16875188 +5191.478606 4.561898582 +4648.86278 4.968968542 +4096.7535 5.492187484 +3531.813507 6.205857585 +3061.567702 7.009732318 +2632.586667 8.013117487 +2308.809844 9.034165571 +2050.115691 10.10054065 +1856.065086 11.11342812 +1697.939632 12.11838913 +1566.241253 13.12607813 +1456.905801 14.10203743 +1361.213594 15.09700775 +1277.653195 16.0933466 +1205.321893 17.06789303 +1140.225621 18.05500221 +1082.497021 19.03311348 +1029.299845 20.03519344 +978.7301404 21.09197235 +909.7052218 22.72586918 +853.6474417 24.24230862 +800.4013622 25.88646126 +754.2905397 27.49036598 +712.4078269 29.14169598 +670.7126389 30.97229099 +627.7691435 33.09676743 +575.1713405 36.13175392 +530.9271979 39.13507843 +493.6372768 42.07116508 +460.4204351 45.08211136 +431.344044 48.07953453 +413.5443388 50.11058044 +375.6941402 55.06404877 +343.7844255 60.05997467 +316.5557099 65.08597946 +293.3070433 70.08469391 +273.2720797 75.05005646 +255.8364317 79.95571518 +240.2177908 84.94446182 +226.3417365 89.90671921 +213.7399247 94.94441986 +202.290575 100.0309563 +182.836437 110.0102921 +166.6070332 120.016922 +152.8936908 130.0197296 +141.1122505 140.0428009 +130.9833926 150.0209808 +122.1217608 160.0074768 +114.3245474 170.0121689 +107.4602859 179.9772949 +101.3318808 189.9621048 +95.84227734 199.9853439 +90.91929929 209.9731979 +87.21012645 218.2335968 +82.43730345 229.9926758 +78.78173797 239.9560928 +75.43740052 249.9537582 +72.39056663 259.9496765 +69.58110202 269.9509277 +66.99775356 279.9595947 +64.61902665 289.9429169 +62.42460824 299.9438019 +60.37761496 309.9502869 +59.41308694 314.9428101 +58.49246424 319.9327393 +57.41458757 325.8934326 +56.75585142 329.7308502 + + diff --git a/tecs/inp/x10409.inp b/tecs/inp/x10409.inp new file mode 100644 index 0000000..2c0cc55 --- /dev/null +++ b/tecs/inp/x10409.inp @@ -0,0 +1,81 @@ +sens=x10409 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +32269 2.9 +20748.23736 3.603200555 +18579.47154 3.804014087 +16787.76559 4.006860971 +15312.0953 4.206260443 +12878.53597 4.621938705 +11165.60106 5.008944988 +9488.065966 5.520080328 +7822.402491 6.221029282 +6511.52182 7.015725851 +5367.730437 8.012619019 +4547.8505 9.028389454 +3941.31213 10.05083227 +3483.009321 11.05512524 +3121.047033 12.05727196 +2824.662495 13.06689167 +2585.652442 14.04817963 +2378.793212 15.05108452 +2202.553608 16.05706978 +2051.669948 17.04423904 +1920.122874 18.04127312 +1804.411269 19.02977657 +1699.495361 20.03870296 +1600.184447 21.11633015 +1470.090201 22.73399639 +1365.536983 24.24896431 +1267.256013 25.89503288 +1183.944345 27.48793411 +1109.317628 29.10398102 +1035.857301 30.92041111 +961.0568252 33.03728104 +870.4233581 36.06695747 +795.1136505 39.0746727 +732.5889862 42.01421165 +677.4377467 45.02629662 +630.0009583 48.02737236 +601.1675257 50.06132126 +540.4813148 55.02171707 +490.1353054 60.01608086 +447.7458778 65.0472908 +412.614513 69.94781113 +382.1132871 74.89925385 +355.1316233 79.93727493 +331.7406269 84.91990662 +311.1618975 89.87853622 +292.6475904 94.90999222 +275.8925548 99.9990654 +247.7818855 109.9829636 +224.5444307 119.9845352 +205.0093904 129.9849472 +188.4524514 140.0073547 +174.2845269 149.9874802 +161.9983605 159.9749832 +151.2042924 169.985466 +141.7478565 179.9493103 +133.3809171 189.9470749 +125.8860681 199.9535294 +119.1794129 209.9433517 +113.1612303 219.9225845 +107.6761902 229.9573059 +102.753304 239.9341965 +98.25500897 249.9317551 +94.14265231 259.9379425 +90.37198068 269.9463196 +86.90447594 279.9547577 +83.71326247 289.9455261 +80.77006452 299.9459534 +78.04586532 309.9586639 +76.75843584 314.9595947 +75.5204243 319.9495544 +74.1057045 325.9043579 +73.21666644 329.7353821 + + diff --git a/tecs/inp/x12532.inp b/tecs/inp/x12532.inp new file mode 100644 index 0000000..72a53b8 --- /dev/null +++ b/tecs/inp/x12532.inp @@ -0,0 +1,92 @@ +sens=x12532 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=30uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +70362.79975 1.212527454 +57354.12647 1.302272379 +46697.37477 1.403238893 +33326.70199 1.600960016 +25468.72112 1.795867503 +19944.89184 2.00802362 +16434.81178 2.204471231 +13816.34216 2.406850576 +11944.35802 2.599458814 +10404.04086 2.805486679 +9221.538007 3.00683713 +8281.992703 3.205510736 +7529.446863 3.398802876 +6866.898089 3.60289824 +6358.310835 3.787422657 +5869.022151 3.994391799 +5435.666264 4.207564354 +5048.762029 4.432380199 +4538.253606 4.784216642 +3914.242563 5.342155457 +3300.345086 6.1004107 +2852.151097 6.871144295 +2432.277393 7.865599394 +2104.024357 8.939789295 +1891.65792 9.848791122 +1709.086747 10.8249917 +1546.544011 11.9003787 +1433.74055 12.79861736 +1330.790008 13.76333618 +1236.964242 14.78599024 +1158.932854 15.77061892 +1094.433622 16.69752789 +1034.852929 17.65495396 +980.4768503 18.63900185 +931.1575654 19.63551426 +877.4284261 20.84920597 +815.0188765 22.46425533 +763.3323477 24.00939465 +714.2919854 25.68263149 +672.6664451 27.29566765 +635.4227663 28.91499805 +594.7482643 30.9173727 +558.0807072 32.97071648 +509.2143732 36.1684494 +471.6113012 39.07764816 +437.804997 42.11110878 +408.8444735 45.10894012 +382.8528407 48.18277168 +367.2296644 50.23297501 +334.2280013 55.20708084 +306.6669189 60.1606102 +282.6831175 65.24242783 +263.0523013 70.10311127 +245.7696072 75.00517273 +230.2783714 80.00709915 +216.3068241 85.11901474 +204.236498 90.08152008 +193.5017279 95.00956726 +183.0021768 100.3596878 +166.1378977 110.3379211 +151.9435045 120.3833733 +139.8754191 130.4784241 +129.680753 140.4299698 +120.6604451 150.5546036 +112.8963027 160.5837402 +106.0233471 170.6487656 +99.8972362 180.78125 +94.50981669 190.7928619 +89.64252042 200.860321 +85.26064276 210.9817581 +81.31788864 221.0397568 +77.77070909 231.033371 +74.47131628 241.2135544 +71.49486847 251.315155 +68.76514076 261.3838501 +66.26072797 271.4606934 +63.96949118 281.4693451 +61.81970992 291.6225433 +59.83227113 301.7844849 +57.99467905 311.8901367 +57.13732908 316.9467773 +56.30362245 321.9956055 +55.50368464 326.9982605 + + diff --git a/tecs/inp/x12533.inp b/tecs/inp/x12533.inp new file mode 100644 index 0000000..7f2a1a3 --- /dev/null +++ b/tecs/inp/x12533.inp @@ -0,0 +1,90 @@ +sens=x12533 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +58491.11567 1.212535322 +47949.5449 1.302323103 +39259.49409 1.40324533 +28281.43621 1.600896776 +21767.98069 1.795822322 +17155.67121 2.008253574 +14213.75553 2.204490304 +12007.63886 2.406743169 +10415.31809 2.599679828 +9105.003941 2.805752277 +8097.388389 3.006976485 +7291.357363 3.205610991 +6646.490487 3.398921728 +6076.028335 3.602926254 +5637.018504 3.787533283 +5214.064508 3.994657993 +4839.768732 4.207356453 +4501.690135 4.432101488 +4057.668994 4.784009218 +3511.923839 5.342074394 +2973.614912 6.100896835 +2579.128549 6.871365786 +2207.384439 7.865557909 +1915.850175 8.940035343 +1726.748344 9.848879814 +1563.465412 10.82483435 +1418.13084 11.9001646 +1316.964373 12.79871416 +1224.187029 13.76333618 +1139.695628 14.78597641 +1069.281285 15.77101898 +1010.884223 16.69764805 +957.2041233 17.6546526 +907.944238 18.63812733 +863.1087092 19.63531017 +814.3069506 20.84896278 +757.6393844 22.4640255 +710.4887602 24.00959301 +665.7070891 25.68195915 +627.583247 27.29504395 +593.4598081 28.91486263 +556.2805114 30.91711807 +522.5368408 32.97060394 +477.5900412 36.16845131 +442.8664029 39.07749367 +411.6814887 42.11124992 +384.9241731 45.10907555 +360.8523969 48.1827774 +346.3993674 50.23285484 +315.6773941 55.20724106 +290.0937236 60.16088295 +267.7935066 65.242836 +249.4506493 70.1031723 +233.2979124 75.00526047 +218.8083315 80.00709915 +205.717029 85.11898804 +194.3976616 90.08143997 +184.3289633 95.00944519 +174.4566698 100.3590927 +158.5832207 110.3372612 +145.2116141 120.3833885 +133.8192793 130.4760437 +124.1684502 140.4295197 +115.6706335 150.5550842 +108.2798297 160.5835495 +101.75565 170.6484222 +95.95185322 180.7810669 +90.8262136 190.7918854 +86.2172275 200.8603973 +82.03414533 210.9830551 +78.2895644 221.0397034 +74.89527823 231.0341873 +71.75384718 241.2140121 +68.9091264 251.3133316 +66.30965093 261.3838348 +63.91098586 271.4609528 +61.72845994 281.4719086 +59.67628607 291.6222687 +57.78058314 301.7855835 +56.02719573 311.8906708 +55.19537744 316.946228 +54.39166232 321.9963684 +53.62604513 326.9980164 diff --git a/tecs/inp/x12905.inp b/tecs/inp/x12905.inp new file mode 100644 index 0000000..35c640d --- /dev/null +++ b/tecs/inp/x12905.inp @@ -0,0 +1,155 @@ +sens=x12905 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +12126.7 1.4 +10474.9 1.5 +9167.68 1.6 +8118.49 1.7 +7266.4 1.8 +6566.56 1.9 +5984.89 2 +5495.55 2.1 +5079.27 2.2 +4721.32 2.3 +4410.66 2.4 +4138.66 2.5 +3898.73 2.6 +3685.6 2.7 +3495.13 2.8 +3323.95 2.9 +3169.36 3 +3029.1 3.1 +2901.33 3.2 +2784.5 3.3 +2677.29 3.4 +2578.6 3.5 +2487.48 3.6 +2403.11 3.7 +2324.8 3.8 +2251.92 3.9 +2183.95 4 +2060.92 4.2 +1952.57 4.4 +1856.5 4.6 +1770.74 4.8 +1693.73 5 +1624.2 5.2 +1561.13 5.4 +1503.63 5.6 +1451.01 5.8 +1402.66 6 +1297.34 6.5 +1209.65 7 +1135.4 7.5 +1071.67 8 +1016.26 8.5 +967.592 9 +924.447 9.5 +885.899 10 +851.205 10.5 +819.79 11 +791.181 11.5 +764.995 12 +740.91 12.5 +718.686 13 +698.12 13.5 +678.996 14 +661.11 14.5 +644.343 15 +628.606 15.5 +613.803 16 +599.837 16.5 +586.63 17 +574.117 17.5 +562.238 18 +550.939 18.5 +540.174 19 +529.9 19.5 +520.081 20 +501.678 21 +484.734 22 +469.064 23 +454.514 24 +440.955 25 +428.28 26 +416.397 27 +405.227 28 +394.702 29 +384.763 30 +375.36 31 +366.447 32 +357.984 33 +349.935 34 +342.27 35 +334.959 36 +327.978 37 +321.303 38 +314.915 39 +308.793 40 +297.283 42 +286.654 44 +276.805 46 +267.65 48 +259.116 50 +251.14 52 +243.668 54 +236.652 56 +230.05 58 +223.825 60 +209.71 65 +197.346 70 +186.416 75 +181.699 77.35 +176.668 80 +167.922 85 +160.02 90 +152.839 95 +146.283 100 +140.272 105 +134.739 110 +129.628 115 +124.893 120 +120.493 125 +116.393 130 +112.564 135 +108.98 140 +105.619 145 +102.459 150 +99.4844 155 +96.6792 160 +94.0294 165 +91.523 170 +89.1489 175 +86.8973 180 +84.7593 185 +82.7268 190 +80.7927 195 +78.9503 200 +77.1935 205 +75.5169 210 +73.9154 215 +72.3845 220 +70.9197 225 +69.5173 230 +68.1735 235 +66.8851 240 +65.6488 245 +64.4619 250 +63.3217 255 +62.2255 260 +61.1711 265 +60.1563 270 +59.5364 273.15 +59.1791 275 +58.2376 280 +57.3299 285 +56.4544 290 +55.6095 295 +54.7938 300 +54.0058 305 +53.2442 310 +52.5078 315 +51.7955 320 +51.106 325 + diff --git a/tecs/inp/x13089.inp b/tecs/inp/x13089.inp new file mode 100644 index 0000000..3aa0105 --- /dev/null +++ b/tecs/inp/x13089.inp @@ -0,0 +1,92 @@ +sens=x13089 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +23282.77032 1.201411964 +18940.37089 1.302915409 +15980.25114 1.398594966 +11836.80508 1.596837978 +9256.530986 1.797479418 +7590.003117 1.99155689 +6348.429816 2.197731075 +5461.271104 2.398754188 +4814.160875 2.590508994 +4261.59355 2.800302629 +3841.97375 3.00037014 +3502.177602 3.198451903 +3204.414778 3.408019548 +2985.156946 3.5919942 +2772.80929 3.798749503 +2606.618466 3.988047225 +2439.745949 4.205178466 +2175.91509 4.622859343 +1978.218735 5.025752554 +1778.846939 5.532288885 +1567.62827 6.240796506 +1388.105765 7.052960837 +1222.295551 8.06591284 +1097.750703 9.084500202 +1000.575337 10.10162877 +923.0118454 11.11366005 +858.7399834 12.12674717 +805.1048002 13.13159579 +759.4896453 14.13032082 +719.7374792 15.12575443 +684.8875483 16.11531839 +653.9039283 17.10483438 +626.1042046 18.0910195 +601.1725797 19.07285116 +578.4081318 20.05485689 +555.4977106 21.13791045 +525.5258216 22.72069291 +498.9067392 24.31406216 +474.5338365 25.9431995 +452.5122922 27.58075597 +432.7118898 29.21788543 +412.7786152 31.03756006 +391.8866621 33.15210641 +365.8757877 36.16130008 +343.3465339 39.16073827 +323.5020423 42.15611312 +306.0795805 45.14730855 +290.4274025 48.1496581 +280.9539983 50.14686068 +259.7524678 55.15029909 +241.6520931 60.14985227 +225.9751806 65.14270755 +212.301462 70.14672582 +200.1956819 75.14768803 +189.4641248 80.144897 +179.8519787 85.14407764 +171.177525 90.14201951 +163.2852432 95.13715956 +156.1098042 100.1338452 +143.4554918 110.1307274 +132.731907 120.1431776 +123.4890012 130.1513103 +115.4046281 140.1584345 +108.3717376 150.1663621 +102.0966968 160.1706214 +96.54502474 170.1749181 +91.55527681 180.1771922 +87.07974778 190.1795571 +83.02579701 200.1891904 +79.34465699 210.2007401 +75.99834184 220.2047128 +72.93989789 230.1996634 +70.14202598 240.1476549 +67.58874631 250.0540863 +65.21781761 260.009652 +63.01636375 270.0084065 +60.97362115 279.9977651 +59.07873602 290.0239166 +57.31555389 300.0431617 +55.67170328 310.0632294 +54.89017786 315.0699284 +54.12998781 320.0632601 +53.27391016 326.0861151 +52.68451986 330.2348667 + diff --git a/tecs/inp/x13090.inp b/tecs/inp/x13090.inp new file mode 100644 index 0000000..d76b55d --- /dev/null +++ b/tecs/inp/x13090.inp @@ -0,0 +1,93 @@ +sens=x13090 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +17567.87648 1.201366951 +14456.91319 1.302862619 +12318.44286 1.398092685 +9269.380756 1.596958259 +7344.684998 1.797326926 +6085.680579 1.99159442 +5139.052338 2.197274569 +4451.500522 2.398702837 +3949.487228 2.590664118 +3517.826085 2.799921785 +3186.625233 3.000394356 +2918.648758 3.198511655 +2682.019504 3.408070547 +2506.09826 3.592113857 +2335.93761 3.79924143 +2201.478624 3.98818411 +2066.622624 4.205386724 +1853.180966 4.622492963 +1691.598232 5.025609187 +1528.363648 5.532537741 +1354.239931 6.241173787 +1204.801541 7.052924483 +1066.439601 8.066313222 +961.6540911 9.084471548 +879.739935 10.10172926 +813.9899552 11.11426358 +759.5276654 12.12693966 +713.75932 13.13219241 +674.7297442 14.13019832 +640.6012119 15.12792955 +610.800334 16.11502493 +584.155119 17.10573197 +560.2563531 18.09046006 +538.6713548 19.07448296 +518.935928 20.05723879 +499.0815475 21.13868801 +473.0276046 22.72352506 +449.9217476 24.31285101 +428.6705654 25.9434019 +409.4784335 27.58167715 +392.1591011 29.2183984 +374.5988053 31.03853152 +356.3344353 33.15331734 +333.3134754 36.16111773 +313.4358598 39.16051532 +295.8657258 42.15603267 +280.4155859 45.14697453 +266.4453231 48.14962387 +258.0607089 50.14646139 +239.0870297 55.14961906 +222.9183156 60.14920991 +208.8952652 65.1429801 +196.5938527 70.14636425 +185.6994357 75.14756889 +176.0294407 80.14633986 +167.3142547 85.14293465 +159.4617491 90.14215397 +152.3314065 95.13894766 +145.8157304 100.1335855 +134.3188267 110.1315292 +124.5154172 120.1437255 +116.0660846 130.1527898 +108.6755652 140.1586574 +102.2012563 150.1654138 +96.45301562 160.170481 +91.31824148 170.1750129 +86.72731251 180.1773922 +82.5798662 190.1782318 +78.82235604 200.1880453 +75.40375573 210.2018025 +72.30526311 220.2043004 +69.47473293 230.2003122 +66.86851231 240.14454 +64.48339454 250.0538287 +62.2722194 260.0092416 +60.22026932 270.0083784 +58.31241678 279.9985487 +56.54399696 290.0247998 +54.89903782 300.0458261 +53.35356358 310.065352 +52.62386051 315.0655902 +51.92029427 320.0639526 +51.10076883 326.0873737 +50.55494992 330.2364089 + + diff --git a/tecs/inp/x14126.inp b/tecs/inp/x14126.inp new file mode 100644 index 0000000..35a7b15 --- /dev/null +++ b/tecs/inp/x14126.inp @@ -0,0 +1,92 @@ +sens=x14126 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=100uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +48909.42119 1.198814073 +39478.64149 1.298890646 +32655.67027 1.399317517 +23777.61131 1.598591967 +18347.05763 1.798464485 +14794.46314 1.996405533 +12106.52367 2.213300659 +10501.32121 2.39012286 +9044.163542 2.600616884 +7950.602165 2.806675147 +7123.44307 3.002098031 +6434.202788 3.2017479 +5848.208621 3.408073724 +5377.137423 3.606077897 +4973.982437 3.8049725 +4639.558689 3.995986413 +4350.82437 4.184664697 +3815.362429 4.617576588 +3422.428496 5.020661486 +3033.827203 5.527511656 +2623.779185 6.239758825 +2279.100257 7.04759816 +1963.507729 8.059801919 +1728.803623 9.078109962 +1547.561803 10.09677201 +1403.715964 11.11273188 +1286.606531 12.12167047 +1189.23653 13.12453082 +1106.547354 14.12381291 +1035.888279 15.11985926 +974.3303273 16.10972338 +920.2597131 17.09782746 +872.3103887 18.0822547 +829.1331731 19.07168714 +790.3635731 20.05645269 +751.7222399 21.14461417 +702.0199867 22.7299385 +658.3198587 24.32727919 +618.9188315 25.9641512 +583.9822824 27.61177817 +552.937056 29.24369689 +522.0009694 31.06771639 +490.2602116 33.17965602 +451.2022063 36.19065895 +418.149764 39.17224876 +389.659018 42.16193212 +364.7839704 45.16085727 +342.8982687 48.16033799 +329.7181351 50.15747817 +300.9592854 55.15264858 +276.6869612 60.15748127 +256.0938261 65.15407878 +238.3537867 70.14910661 +222.9320448 75.13908883 +209.4254498 80.13604129 +196.8107966 85.35463398 +186.5734931 90.13025157 +176.9558751 95.12590706 +168.2813076 100.1225448 +152.250726 110.7848577 +140.4725006 120.1172644 +129.7513566 130.1143951 +120.4896887 140.1175942 +112.469236 150.1152298 +105.4353025 160.1123861 +99.22042061 170.1129194 +93.70505336 180.1291118 +88.79217493 190.1268875 +84.3852042 200.1358775 +80.40399604 210.1504478 +76.80807278 220.1466991 +73.54535744 230.1453812 +70.57240888 240.1452482 +67.85190266 250.1313828 +65.34188262 260.1430643 +63.05109241 270.1389497 +60.93156052 280.1369803 +58.97479149 290.1087349 +57.15810997 300.1306211 +55.47751852 310.123022 +54.6821052 315.1323896 +53.91751058 320.1335907 +53.03187432 326.100001 +52.4592998 330.1146566 + diff --git a/tecs/inp/x14130.inp b/tecs/inp/x14130.inp new file mode 100644 index 0000000..6c1850f --- /dev/null +++ b/tecs/inp/x14130.inp @@ -0,0 +1,90 @@ +sens=x14130 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +54712.84623 1.198798723 +43934.75655 1.298680177 +36145.68598 1.399140842 +26124.24812 1.598338282 +20019.7937 1.798864072 +16054.53916 1.997087653 +13082.22191 2.213840208 +11320.36815 2.389975134 +9710.445363 2.601477021 +8512.931571 2.807233166 +7612.121222 3.002608441 +6862.376758 3.2024249 +6225.652075 3.408153723 +5715.902389 3.606324617 +5280.089053 3.804946968 +4918.589025 3.996036298 +4607.035201 4.184784886 +4030.8182 4.616858111 +3608.024448 5.021396509 +3192.409828 5.528382765 +2753.884576 6.240477346 +2387.699682 7.049333293 +2052.652469 8.0607863 +1804.130589 9.078278512 +1612.202315 10.09828776 +1460.610187 11.11263828 +1337.345199 12.12196388 +1235.150445 13.12392341 +1148.598592 14.12477159 +1074.062971 15.12004292 +1009.823028 16.1097552 +952.987497 17.09840478 +902.6985387 18.08411936 +857.6926533 19.06990691 +817.1433978 20.0569545 +776.7364534 21.1466037 +724.9780754 22.72883755 +679.3006823 24.32375404 +638.3511135 25.95910253 +602.0081568 27.61171849 +569.7386681 29.24321805 +537.4810331 31.06710089 +504.504492 33.18017581 +463.9699549 36.18981414 +429.7053422 39.17308763 +400.1752242 42.16198937 +374.4503395 45.16036471 +351.7558244 48.16049583 +338.1687431 50.15638442 +308.292727 55.15315767 +283.3013008 60.15840032 +262.0374628 65.15576602 +243.7016658 70.15053822 +227.8079642 75.13845443 +213.8528405 80.13558721 +200.9878821 85.35312249 +190.4118598 90.12971562 +180.5179608 95.12598319 +171.5796501 100.1237694 +155.0837311 110.7824018 +143.0224377 120.1163016 +131.9778498 130.11536 +122.4808094 140.1167267 +114.2362018 150.1150876 +107.0314836 160.1124478 +100.674167 170.1124464 +95.02394114 180.1280123 +89.99370834 190.1285747 +85.46763974 200.138367 +81.41176772 210.1510543 +77.73092808 220.1473245 +74.39260818 230.14511 +71.34150942 240.1427862 +68.56668583 250.1299288 +66.01134763 260.143567 +63.67209493 270.1397898 +61.50727813 280.1365374 +59.50351123 290.1111445 +57.65395952 300.1320196 +55.93945627 310.1238382 +55.12054701 315.1305491 +54.33395869 320.1319831 +53.43439626 326.1011039 +52.84982047 330.1161609 + + diff --git a/tecs/inp/x14231.inp b/tecs/inp/x14231.inp new file mode 100644 index 0000000..5831118 --- /dev/null +++ b/tecs/inp/x14231.inp @@ -0,0 +1,89 @@ +sens=x14231 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +45346.09176 1.198717153 +36706.00173 1.298616179 +30407.09586 1.399152924 +22223.29963 1.598426911 +17175.65133 1.799308766 +13877.32694 1.997886019 +11390.09764 2.214142275 +9906.509898 2.389526577 +8539.145773 2.601747251 +7516.284525 2.807291184 +6744.498808 3.002487122 +6100.009293 3.202475086 +5551.381013 3.408289164 +5108.853651 3.606142735 +4731.042051 3.80500669 +4416.159886 3.996132283 +4143.794235 4.185137213 +3640.535495 4.616513504 +3268.12937 5.022147341 +2899.676365 5.528662912 +2512.606636 6.240495878 +2185.580383 7.048665902 +1886.592014 8.061087557 +1663.486413 9.078580603 +1490.913956 10.09831729 +1353.808309 11.11262662 +1241.978882 12.12053341 +1149.175518 13.12453255 +1070.200846 14.12385451 +1002.590927 15.11930797 +943.6033917 16.10992155 +891.7175592 17.09784756 +845.6352302 18.08488235 +804.3306007 19.07335027 +767.1307438 20.05756306 +730.1316279 21.14546834 +682.2281523 22.72983276 +640.2446923 24.32652476 +602.3359845 25.96250613 +568.6695509 27.61161933 +538.8443318 29.24410485 +508.9742411 31.06754222 +478.3257114 33.18021519 +440.5589996 36.18972271 +408.6376322 39.17322288 +381.0960781 42.16172046 +356.9619405 45.16110987 +335.7847002 48.16065735 +323.0015773 50.15751877 +295.0585709 55.15427778 +271.5202017 60.15845647 +251.4849869 65.1554738 +234.261859 70.15087616 +219.2208675 75.13817156 +206.0170192 80.13574238 +193.8353068 85.35591401 +183.8447324 90.12851069 +174.4541594 95.12557876 +165.9511715 100.1241728 +150.2884406 110.7809236 +138.8086112 120.1158899 +128.2784478 130.1156516 +119.2281279 140.1168039 +111.3536703 150.1159926 +104.4582753 160.1113105 +98.36914182 170.1119695 +92.95834383 180.1280541 +88.13033956 190.1264348 +83.79340557 200.1354211 +79.87162555 210.1502982 +76.35426251 220.1464909 +73.13678899 230.1446765 +70.20472384 240.142717 +67.52770935 250.1298551 +65.07150159 260.1424032 +62.80585804 270.1413526 +60.72207723 280.1360821 +58.80254217 290.1099663 +57.01318852 300.1296204 +55.36154863 310.1251632 +54.56232509 315.1323273 +53.81080087 320.1337028 +52.93912804 326.1023799 +52.36765678 330.1165788 + diff --git a/tecs/inp/x14667.inp b/tecs/inp/x14667.inp new file mode 100644 index 0000000..e349552 --- /dev/null +++ b/tecs/inp/x14667.inp @@ -0,0 +1,53 @@ +sens=x14667 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +15213.49 1.407016 +13018.43 1.5035 +11293.78 1.601262 +7083.645 2.006758 +5077.505 2.408741 +3940.486 2.808387 +3226.933 3.201544 +2720.156 3.609121 +2364.470 4.004881 +2216.706 4.209672 +1979.804 4.607776 +1639.450 5.406221 +1408.674 6.202614 +1238.024 7.018838 +1075.552 8.090369 +965.5173 9.070532 +878.9260 10.05435 +811.1776 11.00538 +702.1754 13.01645 +660.2551 14.00823 +590.8182 16.03379 +537.7225 18.01233 +493.8470 20.03132 +450.0727 22.50681 +413.7147 25.02309 +383.6522 27.51456 +357.7065 30.04403 +335.9463 32.50384 +316.5779 35.01109 +283.8034 40.1232 +237.4676 50.04377 +204.4723 60.18116 +180.2791 70.24019 +160.4228 81.00268 +146.9475 90.11372 +133.9208 100.8123 +111.2495 125.8419 +95.20267 151.2575 +83.41541 176.6167 +74.72184 200.9261 +67.59927 226.0847 +61.54781 252.7727 +57.69399 273.2733 +57.65295 273.5096 +53.45707 300.0828 + diff --git a/tecs/inp/x15601.inp b/tecs/inp/x15601.inp new file mode 100644 index 0000000..eadd4c8 --- /dev/null +++ b/tecs/inp/x15601.inp @@ -0,0 +1,92 @@ +sens=x15601 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=30uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +13604.48856 1.20333653 +11665.64228 1.305934489 +10183.15218 1.408226731 +8087.603889 1.613824203 +6827.337287 1.797387439 +5839.358443 1.997115842 +5108.869366 2.195938254 +4522.777879 2.403898387 +4098.673363 2.595145218 +3720.440689 2.804801632 +3426.548233 3.002637615 +3172.142385 3.207165732 +2957.568114 3.410672617 +2786.502821 3.597047831 +2617.049237 3.809513862 +2480.524581 4.005539327 +2349.48735 4.216695852 +2147.062928 4.607323711 +1981.010544 4.995333731 +1807.765227 5.490941893 +1614.41075 6.197303618 +1442.842896 7.008253227 +1282.513024 8.009234903 +1158.51687 9.015276621 +1059.514129 10.02189812 +978.9929281 11.02239089 +911.3697047 12.02302081 +853.7041695 13.02573401 +804.1425469 14.02120649 +760.678927 15.02431191 +722.2727909 16.02142117 +687.9529241 17.01647479 +657.2331197 18.01294873 +629.1885823 19.01058983 +603.8472402 20.00647611 +578.3107733 21.10560491 +545.1511899 22.70233974 +515.7878041 24.29811828 +485.1881724 26.18595303 +462.4867018 27.75735284 +441.5310886 29.34718904 +422.9697905 30.90601805 +400.3383064 32.99931665 +371.0810041 36.11659889 +347.1102132 39.07861488 +325.926885 42.06094461 +306.633104 45.1643442 +290.8022656 48.02870658 +280.7987365 50.00903686 +255.2424351 55.80283614 +237.9410059 60.44038422 +221.974431 65.3859753 +207.5414614 70.51725494 +195.3814327 75.46793868 +184.462935 80.44899073 +174.85362 85.37089566 +165.9814568 90.41368923 +158.0874721 95.35853726 +150.9531904 100.2997285 +138.5925202 110.0320374 +127.3457082 120.5214065 +118.3855018 130.300157 +110.6221255 140.0255777 +103.6354754 150.0334193 +97.48505862 160.0311561 +92.01812421 170.0349327 +87.16707108 180.0358242 +82.79937075 190.03318 +78.87480219 200.0258735 +75.30320773 210.0410303 +72.08480453 220.0638022 +69.14450743 230.0603278 +66.45718355 240.0582532 +63.99049624 250.0593421 +61.7157779 260.0571313 +59.62625857 270.0603652 +57.69355583 280.0563142 +55.91116052 290.0570078 +54.24715549 300.0543043 +52.70434938 310.042649 +51.97398136 315.0441578 +51.26971605 320.0519038 +50.49959985 325.7129911 +50.13643343 328.4507039 + diff --git a/tecs/inp/x17627.inp b/tecs/inp/x17627.inp new file mode 100644 index 0000000..7a50a16 --- /dev/null +++ b/tecs/inp/x17627.inp @@ -0,0 +1,58 @@ +sens=x17627 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +35.5745979 325 +35.64921737 324 +36.83155035 309 +38.14081773 294 +39.59588005 279 +41.21734373 264 +43.03283913 249 +45.07544262 234 +47.38381238 219 +50.00921069 204 +53.01759216 189 +56.49239668 174 +60.54245115 159 +65.31606311 144 +71.01825549 129 +77.95428634 114 +86.59244451 99 +97.69897334 84 +112.621161 69 +125.1670452 59.5 +141.4881278 50 +152.2684756 45 +165.1657524 40 +180.929757 35 +200.7150787 30 +221.8400733 25.8 +245.4821962 22.1 +271.6376721 18.9 +299.9576897 16.2 +331.0548845 13.9 +366.2013998 11.9 +402.7263073 10.3 +444.1707955 8.9 +490.5575905 7.7 +541.1030726 6.7 +593.4580155 5.9 +652.4842006 5.2 +717.7777636 4.6 +787.6621925 4.1 +858.3412811 3.7 +948.0691174 3.3 +1033.213329 3 +1140.328556 2.7 +1228.655135 2.5 +1335.580286 2.3 +1467.87813 2.1 +1546.678327 2 +1739.40214 1.8 +2169.002237 1.5 +2372.684537 1.4 + diff --git a/tecs/inp/x2060.inp b/tecs/inp/x2060.inp new file mode 100644 index 0000000..1198474 --- /dev/null +++ b/tecs/inp/x2060.inp @@ -0,0 +1,91 @@ +sens=x2060 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +68000 1.0 +44881.28899 1.2 +36817.49567 1.309 +31135.18899 1.403 +21987.20345 1.604 +16114.99662 1.8 +12258.05661 1.996 +9918.666931 2.168 +7915.149596 2.385 +6521.88091 2.604 +5617.346366 2.796 +4894.762604 3 +4329.19174 3.206 +3898.635478 3.402 +3541.829 3.6 +3258.390355 3.79 +2984.005729 4.008 +2766.634389 4.208 +2446.004452 4.583 +2155.218862 5.037 +1900.670937 5.555 +1642.521599 6.262 +1428.551021 7.074 +1234.644114 8.097 +1092.227708 9.12 +980.9691976 10.168 +894.9346698 11.189 +825.2867872 12.198 +767.6953785 13.194 +719.0106414 14.182 +677.2773451 15.159 +640.4098623 16.138 +608.3465142 17.103 +579.6429399 18.071 +553.709856 19.038 +529.6610169 20.026 +506.2778453 21.091 +474.856356 22.692 +448.7524681 24.208 +424.6284501 25.792 +402.9983074 27.367 +383.0390317 29.007 +363.2532965 30.805 +342.3719529 32.938 +320.7389826 35.453 +295.3162837 38.904 +276.640478 41.85 +260.0577328 44.825 +245.1701481 47.852 +236.2055933 49.856 +216.3050767 54.918 +199.7722596 59.894 +185.5735149 64.889 +173.2922053 69.877 +162.4378675 74.916 +153.0620054 79.837 +144.6319839 84.804 +137.0163323 89.804 +127.6014751 96.795 +120.8444611 102.471 +109.8273514 113.175 +103.8928657 119.86 +96.20883586 129.725 +89.42109592 139.773 +83.5152527 149.804 +78.34370646 159.81 +73.77685637 169.797 +69.71875787 179.768 +66.09775467 189.689 +62.84505418 199.59 +59.90371916 209.464 +57.26569688 219.289 +54.85259174 229.086 +52.65354288 238.856 +50.64578201 248.587 +48.80362619 258.316 +47.10439353 268.003 +45.54155793 277.656 +44.10190663 287.254 +42.75989139 296.854 +41.52116147 306.381 +40.92174382 311.132 +40.35810065 315.861 +39.70434603 321.478 +39.27574259 325.239 + diff --git a/tecs/inp/x22637.inp b/tecs/inp/x22637.inp new file mode 100644 index 0000000..d5e8ff5 --- /dev/null +++ b/tecs/inp/x22637.inp @@ -0,0 +1,92 @@ +sens=x22637 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +18271.2735 1.201775141 +15018.14259 1.300003299 +12605.42404 1.40085118 +9394.553378 1.601518556 +7401.753356 1.800588297 +6063.804617 2.00089626 +5127.39976 2.199746754 +4427.569053 2.40054614 +3896.293416 2.600827287 +3476.895591 2.801647183 +3146.876058 2.998488632 +2870.170528 3.198498904 +2641.391928 3.39935432 +2445.764126 3.60131308 +2283.079332 3.799687432 +2141.048458 3.999064872 +2018.06725 4.197064807 +1800.707637 4.623543342 +1636.78931 5.031690261 +1474.576811 5.541711582 +1301.169012 6.258624854 +1154.402875 7.074764656 +1018.703818 8.09763414 +916.5851289 9.125836635 +836.9551696 10.15287494 +773.2778002 11.17256297 +721.0656387 12.18348114 +677.3611143 13.18806219 +639.9091774 14.18633821 +607.5672194 15.17619408 +579.1056183 16.1599519 +553.8568077 17.13925751 +531.171311 18.11776676 +510.5787006 19.09728447 +491.8443726 20.07569906 +472.9042854 21.157037 +448.191885 22.7335822 +425.987672 24.33191482 +406.1050945 25.93328988 +387.2413051 27.62506921 +370.6239395 29.27045936 +354.2813013 31.06318005 +336.7642427 33.19925181 +314.7227201 36.23889705 +296.0544997 39.22649748 +279.4366367 42.22265752 +264.8321789 45.2110573 +251.684706 48.20360607 +243.8031803 50.17443204 +225.8049714 55.20840321 +210.5182225 60.20668174 +197.2789371 65.20244007 +185.6830724 70.19302182 +175.4146329 75.18086928 +166.2653967 80.17471307 +158.0776999 85.16716708 +150.6335412 90.16538024 +143.9156408 95.15676739 +137.7605299 100.1549775 +126.9241599 110.1368995 +117.6652736 120.1389241 +109.6987039 130.1331501 +102.7274906 140.127387 +96.59503167 150.125788 +91.16813593 160.1192973 +86.31446102 170.1184308 +81.96220962 180.1316335 +78.04036796 190.1287944 +74.49414632 200.1308997 +71.25876685 210.1378263 +68.32457177 220.1329382 +65.63171779 230.1298374 +63.15928982 240.1293974 +60.88298571 250.116388 +58.78101015 260.122836 +56.8332323 270.1157907 +55.02981573 280.1134787 +53.37177817 289.993198 +51.80786848 299.9964879 +50.3335795 310.0947302 +49.64399515 315.085561 +48.97316762 320.1072636 +48.19629135 326.0931932 +47.70969706 329.9594996 + diff --git a/tecs/inp/x22642.inp b/tecs/inp/x22642.inp new file mode 100644 index 0000000..b3cfdcf --- /dev/null +++ b/tecs/inp/x22642.inp @@ -0,0 +1,93 @@ +sens=x22642 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +20949.3626 1.200558176 +17142.9063 1.2990458 +14325.67427 1.400094323 +10628.7221 1.600354686 +8328.213609 1.800458762 +6803.546799 1.999945639 +5731.873767 2.199864218 +4940.65276 2.399949312 +4330.984543 2.60132227 +3857.40887 2.802170737 +3486.514394 2.997921455 +3174.010868 3.198500507 +2915.081847 3.400102792 +2697.195239 3.601991996 +2512.764348 3.800901174 +2354.201594 3.999362758 +2216.399445 4.196865673 +1973.304717 4.622532516 +1789.847086 5.03108069 +1608.625165 5.541186582 +1414.676805 6.258439055 +1250.941706 7.075924839 +1099.630157 8.097559324 +986.1149219 9.126078494 +897.8271964 10.15106462 +826.9951282 11.17243575 +769.1549568 12.18421334 +720.7324382 13.18825545 +679.3908307 14.1861226 +643.5388053 15.17988834 +612.4155154 16.16082752 +584.6004467 17.14417399 +559.9074202 18.11842752 +537.3817655 19.09741076 +516.9993187 20.07483115 +496.4660843 21.15487823 +469.6512201 22.73421312 +445.6652682 24.33113366 +423.4131996 26.00318866 +404.1492243 27.62373651 +386.4991902 29.26893058 +368.5293039 31.12888947 +350.1577143 33.25121425 +327.4963929 36.23847414 +307.7740796 39.24203196 +290.7398659 42.2251891 +275.476593 45.24235575 +262.0314365 48.22151844 +253.8891827 50.20924761 +235.6492828 55.19975706 +220.053175 60.2093487 +206.6650459 65.20248926 +194.9585829 70.19514644 +184.611347 75.18110487 +175.4292709 80.17496236 +167.1949548 85.16653408 +159.742773 90.16306236 +152.9686861 95.15643799 +146.8111269 100.1546576 +135.9501515 110.136391 +126.6734872 120.1372263 +118.6582154 130.1321856 +111.6603199 140.125834 +105.4683055 150.1240735 +99.96697679 160.1175167 +95.05353372 170.1170899 +90.62527887 180.1296282 +86.63311615 190.1270962 +83.00203888 200.1288058 +79.69253549 210.1356682 +76.6622933 220.1314841 +73.88857675 230.1278107 +71.33370241 240.1289393 +68.9747872 250.114868 +66.78673913 260.1221042 +64.76193431 270.1158305 +62.86547048 280.1133864 +61.12969734 289.9883915 +59.48791478 299.9920827 +57.93529154 310.0938564 +57.20329528 315.0859786 +56.49582879 320.1068376 +55.68098623 326.0911299 +55.16772341 329.9601461 + + diff --git a/tecs/inp/x22643.inp b/tecs/inp/x22643.inp new file mode 100644 index 0000000..6810be6 --- /dev/null +++ b/tecs/inp/x22643.inp @@ -0,0 +1,90 @@ +sens=x22643 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +40697.08045 1.200383665 +32366.30601 1.2988459 +26383.16465 1.399640145 +18764.54287 1.600069469 +14218.36962 1.80050257 +11309.71813 1.999921521 +9310.413119 2.199675427 +7872.095589 2.400568686 +6795.33757 2.600953457 +5962.609252 2.802593743 +5323.474481 2.998229728 +4794.331253 3.198505442 +4357.913367 3.399830909 +3994.078516 3.602332232 +3691.652802 3.800667475 +3432.841672 3.998683453 +3209.821742 4.197187559 +2822.23232 4.621843846 +2532.594291 5.030985671 +2250.53672 5.540687851 +1953.269749 6.258439883 +1705.721848 7.075941677 +1481.133789 8.098835821 +1314.245602 9.126648666 +1186.533955 10.14986572 +1084.981688 11.17301858 +1002.603853 12.18417435 +934.1416119 13.19101128 +876.3895136 14.18585788 +826.5482802 15.17706002 +783.2998658 16.16022176 +744.9464033 17.14217167 +710.9439736 18.11800801 +680.1821007 19.09720393 +652.3914442 20.0747849 +624.5349218 21.15438192 +588.3443957 22.73386551 +556.1428977 24.33193314 +526.4145806 26.002926 +500.7972046 27.62437142 +477.360904 29.26865318 +453.6405139 31.12609073 +429.5001282 33.25137513 +399.9196226 36.23897961 +374.7006974 39.19177939 +352.1673551 42.22483594 +332.4688788 45.24107441 +315.216519 48.22703392 +304.713183 50.21675469 +281.5005622 55.19829595 +261.7370771 60.20969768 +244.85282 65.20275807 +230.1376412 70.19558102 +217.2143738 75.18138801 +205.731756 80.17372851 +195.465736 85.16757871 +186.2543223 90.16260766 +177.9088112 95.15600235 +170.3011786 100.1545625 +157.0005871 110.136432 +145.6465035 120.1369457 +135.8938165 130.1311705 +127.4100026 140.1258235 +119.9448724 150.1232762 +113.3502458 160.1168189 +107.4521231 170.1169615 +102.1569958 180.1293003 +97.39647105 190.1276327 +93.09014666 200.127944 +89.15387509 210.1342407 +85.58302245 220.1308113 +82.30165038 230.127 +79.28757604 240.1281036 +76.51133626 250.1159095 +73.93968659 260.1207012 +71.56220586 270.1135658 +69.34834911 280.1135234 +67.31986072 289.989674 +65.400923 299.9941845 +63.58838316 310.0938826 +62.73896639 315.0851786 +61.91140488 320.1069728 +60.95482497 326.0894131 +60.35592944 329.9615505 + diff --git a/tecs/inp/x22644.inp b/tecs/inp/x22644.inp new file mode 100644 index 0000000..c9649da --- /dev/null +++ b/tecs/inp/x22644.inp @@ -0,0 +1,92 @@ +sens=x22644 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +16007.79518 1.200721786 +13255.8808 1.298891069 +11205.15286 1.39943304 +8443.928222 1.599937175 +6702.327773 1.800442288 +5534.122213 2.00019607 +4704.584196 2.199969718 +4084.913232 2.400603038 +3610.312949 2.600633851 +3230.256645 2.802896079 +2936.389321 2.998094443 +2686.653219 3.198715722 +2478.1989 3.399484728 +2300.553298 3.602485184 +2151.36877 3.800490872 +2022.540635 3.998439887 +1908.79865 4.197156641 +1709.313903 4.621681363 +1557.368026 5.030523733 +1406.421873 5.540281439 +1243.706071 6.25898771 +1105.603956 7.076289652 +977.4489794 8.098257051 +880.4428612 9.126725378 +804.8003471 10.14989046 +743.7218062 11.1730348 +693.7309884 12.18383727 +651.4548886 13.19332605 +615.7657565 14.18572326 +584.5828244 15.17662749 +557.2403338 16.16073706 +532.9508371 17.14074973 +511.1072589 18.11815111 +491.3416812 19.09726974 +473.3439969 20.07459081 +455.2101691 21.15478955 +431.4309748 22.73367042 +410.1806618 24.3324661 +390.407091 26.00456745 +373.2423216 27.6242651 +357.4650865 29.26937996 +341.3901179 31.1270676 +324.8832171 33.25128091 +304.5451078 36.23921994 +287.1316191 39.19190152 +271.3027429 42.22413357 +257.4885798 45.23979471 +245.297921 48.23143543 +237.8548894 50.22289595 +221.3051609 55.19735291 +207.0981627 60.20938313 +194.8252865 65.20351886 +184.1071589 70.19674071 +174.6169591 75.18080073 +166.126924 80.17225392 +158.5229665 85.16939558 +151.626774 90.16147891 +145.4056367 95.15586553 +139.6765896 100.1540934 +129.6293513 110.1362537 +120.9858687 120.1370202 +113.5180198 130.13073 +106.9678656 140.1252385 +101.1878636 150.1234354 +96.03408894 160.1165839 +91.42205476 170.1168663 +87.26057763 180.1290119 +83.5052218 190.1274068 +80.09071577 200.1278156 +76.96422711 210.1345051 +74.10488591 220.1302898 +71.49685195 230.1260865 +69.07286887 240.1285934 +66.84323633 250.1146862 +64.77194872 260.1210378 +62.85425529 270.1122296 +61.06392683 280.1125128 +59.42108067 289.9881766 +57.86899725 299.992933 +56.40163103 310.0918565 +55.70314445 315.0849843 +55.03104128 320.106081 +54.25379641 326.0894698 +53.76781249 329.9611435 + diff --git a/tecs/inp/x23167.inp b/tecs/inp/x23167.inp new file mode 100644 index 0000000..2679a43 --- /dev/null +++ b/tecs/inp/x23167.inp @@ -0,0 +1,93 @@ +sens=x23167 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +13256 1.2667 +12339.6 1.3079 +10612.8 1.39837 +7934.84 1.60472 +6312.15 1.80457 +5224.59 2.00258 +4433.62 2.2052 +3863.64 2.40137 +3426.28 2.59562 +3067.44 2.79823 +2778.05 3.00127 +2541.71 3.20258 +2346.56 3.40243 +2184.08 3.59835 +2042.33 3.79824 +1918.02 4.00071 +1813.42 4.19502 +1694.48 4.45245 +1537 4.86219 +1381.08 5.37833 +1215.82 6.10426 +1077.33 6.92914 +950.998 7.9563 +856.643 8.98452 +783.22 10.0107 +724.578 11.0289 +676.273 12.0438 +635.753 13.0532 +601.137 14.0575 +571.214 15.0536 +544.709 16.0521 +521.305 17.0418 +500.196 18.0334 +481.084 19.0239 +463.678 20.0156 +446.061 21.113 +423.091 22.7127 +402.738 24.3079 +384.836 25.8768 +368.433 27.4697 +353.481 29.0617 +338.199 30.8555 +322.143 32.9398 +301.914 35.9259 +284.313 38.9125 +268.731 41.9037 +254.904 44.8993 +242.513 47.8951 +234.929 49.9002 +218.03 54.9006 +203.575 59.8998 +191.007 64.8988 +179.981 69.9006 +170.203 74.9064 +161.499 79.9104 +153.673 84.9088 +146.601 89.9149 +140.162 94.9156 +134.278 99.9209 +123.944 109.916 +115.077 119.911 +107.406 129.936 +100.731 139.921 +94.837 149.926 +89.5989 159.934 +84.9318 169.936 +80.7333 179.94 +76.9532 189.936 +73.4975 200.03 +70.4028 209.958 +67.5519 219.963 +64.9471 229.952 +62.5757 239.834 +60.3399 249.974 +58.2975 259.981 +56.4271 269.906 +54.6748 279.898 +53.0525 289.876 +51.5345 299.863 +50.1175 309.88 +49.465 314.737 +48.6236 321.219 +47.6911 328.739 +47.0917 333.74 + + diff --git a/tecs/inp/x24506.inp b/tecs/inp/x24506.inp new file mode 100644 index 0000000..a1f9161 --- /dev/null +++ b/tecs/inp/x24506.inp @@ -0,0 +1,92 @@ +sens=x24506 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +19268.81299 1.203132044 +15988.04386 1.303857052 +13566.54215 1.402030678 +10243.19932 1.601888887 +8134.292037 1.803798062 +6746.85603 1.999044471 +5702.253839 2.205960091 +4983.821262 2.397173365 +4403.141857 2.595654544 +3927.751689 2.8016119 +3559.813757 2.999462194 +3262.793275 3.194307942 +2994.957662 3.403767784 +2781.772177 3.60147407 +2599.977578 3.797968133 +2434.783052 4.003600074 +2300.250245 4.194131586 +2049.480323 4.628205525 +1860.226486 5.039219527 +1688.994948 5.503198119 +1489.501802 6.19708145 +1331.975694 6.915892862 +1165.987553 7.926817183 +1041.245148 8.938735462 +944.0649791 9.947593381 +866.0653267 10.94840287 +801.7814871 11.94882804 +747.4756795 12.94795075 +701.1868301 13.94712368 +661.0722017 14.94301187 +625.7591056 15.9426341 +594.4989405 16.93930437 +566.5092705 17.93828753 +541.2722135 18.93904446 +518.3207266 19.94215642 +495.3646603 21.0537636 +465.5788563 22.67392604 +439.2508664 24.30347965 +416.3304337 25.9065248 +395.9496162 27.50607791 +377.6984907 29.09411524 +359.2355844 30.8775603 +340.081641 32.94894203 +316.0619719 35.92019875 +295.47926 38.89758748 +277.4319333 41.89049517 +261.4512412 44.90209998 +247.3730123 47.92599291 +238.7112077 49.95521855 +219.8294133 55.01767396 +203.767392 60.11225849 +190.3283808 65.10837357 +178.5337098 70.13699411 +168.2447998 75.16468223 +159.131346 80.1789729 +151.0552683 85.18924189 +143.7333266 90.19958571 +137.1671351 95.20842634 +131.1872847 100.2149656 +120.7557448 110.2089779 +111.926522 120.1979462 +104.3242104 130.2076795 +97.75251312 140.1804214 +91.9832616 150.1599848 +86.89677329 160.1476145 +82.35212364 170.1262403 +78.29519329 180.1139973 +74.65337852 190.0908422 +71.35636785 200.0908858 +68.35265459 210.0774018 +65.62382183 220.0825998 +63.1274985 230.0704903 +60.84286108 240.0905455 +58.73780843 250.0935493 +56.79306615 260.0989924 +54.99712606 270.1077013 +53.34068806 280.0892052 +51.79011752 290.1195942 +50.36440152 300.043781 +49.027488 310.035648 +48.39763591 314.9962369 +47.6297072 321.2613963 +46.74933639 328.7765688 +46.18820427 333.7714114 + diff --git a/tecs/inp/x29630.inp b/tecs/inp/x29630.inp new file mode 100644 index 0000000..2f9e530 --- /dev/null +++ b/tecs/inp/x29630.inp @@ -0,0 +1,54 @@ +sens=x29630 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +48169.55684 1.4156 +39885.13082 1.5093 +33567.18472 1.6042 +18364.12385 2.025 +12342.47911 2.4072 +8837.044892 2.8225 +6892.748828 3.2075 +5551.237926 3.6128 +4511.413877 4.0785 +4292.582418 4.2035 +3718.163227 4.5988 +2896.451846 5.4278 +2394.808056 6.2113 +2036.162241 7.0161 +1689.6744 8.1367 +1470.891066 9.1364 +1295.118698 10.2046 +1167.106277 11.2029 +986.8745682 13.092 +917.2628875 14.0398 +797.0667942 16.1077 +708.1149979 18.1232 +638.1213707 20.1642 +572.8689276 22.5405 +516.7157547 25.102 +473.3055661 27.5305 +434.3482604 30.1509 +403.209548 32.6337 +377.515195 35.0112 +329.2506256 40.5518 +268.6438857 50.546 +227.6556026 60.5653 +198.3103954 70.4865 +174.8129501 81.0062 +158.1702861 90.4686 +143.4637897 100.7613 +117.0960187 126.0159 +99.40357853 150.7981 +86.65511265 175.2525 +76.27183281 201.6172 +68.46032724 227.2484 +62.66842138 250.8951 +58.17674094 273.0018 +58.08212813 273.5107 +53.61355351 300.0167 +49 330 + diff --git a/tecs/inp/x29746.inp b/tecs/inp/x29746.inp new file mode 100644 index 0000000..7537ae2 --- /dev/null +++ b/tecs/inp/x29746.inp @@ -0,0 +1,55 @@ +sens=x29746 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=325 ! setpoint limit (automatic if omitted) +type=cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +49333.99112 1.4116 +40387.72213 1.5146 +34106.41201 1.6114 +19665.68338 2.0075 +13089.00524 2.4137 +9648.784253 2.8112 +7540.340823 3.2138 +6185.056903 3.6051 +5157.829585 4.0308 +4828.585225 4.2045 +4206.629648 4.6054 +3333.444448 5.4221 +2771.772271 6.2256 +2352.775098 7.0895 +2020.773552 8.0461 +1766.784452 9.0416 +1561.889887 10.1022 +1409.284365 11.112 +1193.773279 13.0209 +1100.352113 14.1043 +963.5767971 16.1061 +860.437102 18.0749 +776.8800497 20.0802 +696.4273278 22.4982 +628.8912647 25.0358 +574.5343399 27.5292 +529.1929279 30.0186 +490.2369315 32.5414 +457.1533064 35.0344 +401.8032932 40.1605 +324.0503704 50.4402 +273.4616415 60.4027 +236.7071199 70.4182 +210.2098946 79.8848 +187.6771203 90.0922 +169.5349149 100.3197 +136.4565509 126.0394 +114.9441142 150.7499 +99.12060202 175.8608 +87.23339294 200.8987 +78.00312012 225.9038 +70.09231157 253.0469 +65.28864108 273.1334 +65.2239137 273.4244 +59.74857798 300.9599 +54.5 330 + + diff --git a/tecs/inp/x31317.inp b/tecs/inp/x31317.inp new file mode 100644 index 0000000..caa2cf4 --- /dev/null +++ b/tecs/inp/x31317.inp @@ -0,0 +1,88 @@ +sens=x31317 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +82645.04651 1.199380518 +64126.00275 1.298983307 +51197.62425 1.399889713 +35263.77563 1.599540201 +26071.85628 1.797932254 +20118.18057 2.000494957 +16184.30878 2.199612368 +13417.51113 2.396242026 +11336.19482 2.597685984 +9769.236133 2.798075327 +8542.396095 2.999811154 +7577.740269 3.199405252 +6783.94807 3.401293259 +6134.21376 3.60175609 +5595.138081 3.799990474 +5135.595311 3.999180846 +4722.036217 4.209088273 +4356.418748 4.428235084 +3796.164938 4.838048719 +3259.105741 5.357779456 +2713.664592 6.092663717 +2278.316934 6.925028047 +1901.991682 7.956841317 +1633.666957 8.995301998 +1433.16295 10.03364726 +1279.198931 11.06286955 +1156.850467 12.08271225 +1057.711346 13.09383104 +975.50515 14.09917436 +906.596783 15.09314923 +847.2113197 16.09044568 +795.908983 17.07738271 +751.0174567 18.06444332 +711.0889145 19.0547303 +675.517752 20.04142352 +640.2913637 21.13482803 +595.5434204 22.7292068 +556.6423386 24.34286391 +522.4661562 25.97762332 +492.3172681 27.61724859 +465.9268054 29.25216279 +439.8213293 31.07297084 +413.3367955 33.17772797 +381.0835156 36.18239178 +353.9509338 39.17571067 +330.7912817 42.16657397 +310.7531539 45.15650283 +293.2348398 48.14493538 +282.5396344 50.14678658 +259.6461174 55.14071271 +240.4021871 60.13470811 +224.1399926 65.13058811 +210.1565506 70.12923843 +197.886053 75.13416903 +187.1786009 80.13334701 +177.6977592 85.12760009 +169.1654064 90.12489881 +161.5066917 95.12039842 +154.5680394 100.1094 +142.4110889 110.1959462 +132.3162883 120.0890848 +123.5403647 130.1085056 +115.978895 140.0869674 +109.3201532 150.0813152 +103.4273849 160.0791163 +98.21872475 170.0680089 +93.52573862 180.0600124 +89.31975297 190.0431993 +85.50532224 200.0455259 +82.03548657 210.0395283 +78.86033603 220.0375806 +75.97035375 230.0197551 +73.30910046 240.031542 +70.85269921 250.0256842 +68.58839825 260.0246538 +66.48302149 270.0214982 +64.53311922 279.9987828 +62.71281686 290.0170467 +61.03721363 299.9243403 +59.4596642 309.9000623 +58.71737263 314.854573 +57.79864904 321.1185813 +56.76395577 328.6205713 +56.10178078 333.6085882 diff --git a/tecs/inp/x31318.inp b/tecs/inp/x31318.inp new file mode 100644 index 0000000..c027a24 --- /dev/null +++ b/tecs/inp/x31318.inp @@ -0,0 +1,88 @@ +sens=x31318 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +68901.47634 1.199185718 +54081.43382 1.301378052 +44005.8983 1.400855368 +31187.09197 1.600104575 +23697.51082 1.796223603 +18691.53476 1.998912916 +15098.13673 2.214764615 +12937.92316 2.394879788 +11104.32496 2.597481119 +9702.020108 2.799417332 +8571.764655 3.007900004 +7715.245921 3.204730142 +7031.171555 3.395432764 +6415.995354 3.600310422 +5919.918489 3.796294884 +5521.041358 3.979304182 +5061.977975 4.225638666 +4483.494755 4.611529181 +4008.941635 5.011672166 +3540.482956 5.517897684 +3048.232196 6.227571851 +2639.041604 7.034029338 +2267.062828 8.04634519 +1992.349055 9.063490939 +1781.077523 10.07962894 +1613.777322 11.09297079 +1477.714539 12.10127778 +1364.847951 13.10538917 +1269.40033 14.10586867 +1187.915923 15.10110419 +1116.842934 16.09644 +1054.406923 17.08897197 +998.9541992 18.08039699 +949.4166726 19.07003328 +904.6361826 20.06329727 +860.1500223 21.15779035 +803.3540132 22.74255345 +753.5774083 24.33493529 +707.5990554 26.00820405 +666.0030406 27.73113987 +629.7822557 29.41826033 +594.0696375 31.28900292 +557.8293186 33.43443556 +513.9414868 36.45280188 +476.9204972 39.44297129 +445.1743299 42.41080319 +417.3985464 45.38871698 +392.8015178 48.37451803 +378.0766669 50.36156313 +345.5000095 55.36269868 +318.0662466 60.37737512 +294.8204914 65.38853846 +274.8213431 70.39783353 +257.4057119 75.39383335 +242.0920638 80.38431773 +228.5592609 85.37796285 +216.4206187 90.36779573 +205.5124009 95.35751232 +195.6841096 100.3408723 +178.4243274 110.418124 +164.1832093 120.299264 +151.9310153 130.2957426 +141.3698714 140.2839856 +132.1704573 150.2704162 +124.0745392 160.2586005 +116.9306289 170.2448579 +110.5690206 180.2362745 +104.8731694 190.2324162 +99.73109029 200.2311703 +95.09898824 210.2236387 +90.88713924 220.2126668 +87.05478879 230.2263582 +83.55342163 240.230668 +80.3412173 250.2191886 +77.3826322 260.2320041 +74.66405151 270.217955 +72.14039561 280.2343633 +69.80262604 290.2226393 +67.62829511 300.2359035 +65.61243834 310.2333849 +64.65254205 315.2372397 +63.7257676 320.2384933 +62.65699711 326.2391757 +61.97081919 330.2296647 diff --git a/tecs/inp/x31319.inp b/tecs/inp/x31319.inp new file mode 100644 index 0000000..f7e580d --- /dev/null +++ b/tecs/inp/x31319.inp @@ -0,0 +1,88 @@ +sens=x31319 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +74612.85388 1.199177409 +58386.64483 1.301570868 +47328.18302 1.401206711 +33389.0605 1.600154454 +25251.51975 1.796271028 +19853.36353 1.998863704 +15981.8145 2.214728702 +13665.706 2.394652313 +11700.25482 2.597328594 +10204.96249 2.799452766 +8999.267151 3.008040376 +8088.007617 3.204904214 +7362.583739 3.395151541 +6710.552988 3.60021517 +6184.67101 3.796167475 +5763.34408 3.979268794 +5276.812602 4.225676067 +4667.424115 4.611364746 +4167.683873 5.011155404 +3674.774425 5.517561186 +3157.987056 6.227548652 +2729.915028 7.034245052 +2341.355814 8.046491772 +2054.717537 9.062851416 +1834.926721 10.07966189 +1660.652671 11.0923442 +1519.296938 12.10112585 +1401.938347 13.10508252 +1303.328587 14.10512148 +1218.753407 15.10217752 +1145.141221 16.09542672 +1080.513994 17.08885726 +1023.309896 18.08008347 +972.2475024 19.07019839 +925.9029508 20.06410171 +880.2406599 21.15634949 +821.4824985 22.74172478 +770.14506 24.33439044 +722.8942371 26.00827627 +680.0805518 27.7284403 +642.7703852 29.41766295 +606.0615251 31.28938151 +568.9244923 33.43505211 +523.8324484 36.4529057 +485.8292366 39.44344431 +453.2665031 42.41063217 +424.8057062 45.38852269 +399.6584609 48.37524014 +384.5766683 50.36139685 +351.2093935 55.3629944 +323.213084 60.37757918 +299.3923578 65.38969589 +279.0132967 70.39838662 +261.2082978 75.39322701 +245.6297306 80.38595885 +231.8122076 85.37788855 +219.4789035 90.36686926 +208.3645562 95.35916614 +198.3370301 100.3408302 +180.7734707 110.4173909 +166.3000853 120.2994698 +153.8525668 130.2950154 +143.0942507 140.2842564 +133.7598728 150.2699244 +125.5466639 160.2576112 +118.2904307 170.2441348 +111.8322938 180.2364885 +106.0430206 190.2335043 +100.8394115 200.2312462 +96.13350443 210.2240529 +91.8833451 220.2130353 +87.98821748 230.2262285 +84.42619095 240.2301713 +81.17492859 250.2168459 +78.17915716 260.2310834 +75.42211632 270.2179533 +72.86331817 280.232442 +70.49932305 290.2234447 +68.30021534 300.2353677 +66.26123623 310.2307031 +65.29062152 315.2350135 +64.35142033 320.2376337 +63.26816822 326.2381502 +62.57752995 330.2274114 diff --git a/tecs/inp/x31320.inp b/tecs/inp/x31320.inp new file mode 100644 index 0000000..e78dac7 --- /dev/null +++ b/tecs/inp/x31320.inp @@ -0,0 +1,88 @@ +sens=x31320 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +type=Cernox ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +47776.06056 1.199198167 +38163.67518 1.301472419 +31462.01446 1.401578934 +22867.30445 1.600174737 +17697.07994 1.796230622 +14182.80361 1.998798661 +11617.60705 2.214605381 +10056.90064 2.394447642 +8712.755603 2.597195799 +7678.576958 2.799911201 +6834.550554 3.00837786 +6192.465252 3.204905043 +5676.11641 3.395031492 +5209.047198 3.59990882 +4827.729216 3.796295623 +4522.101468 3.979050186 +4166.431185 4.22562774 +3716.657781 4.611304774 +3344.330169 5.011333094 +2973.764799 5.517810502 +2581.937354 6.227539629 +2252.390468 7.033583311 +1950.507339 8.046393956 +1725.790311 9.063358337 +1551.509204 10.07960146 +1412.701018 11.09193531 +1299.294377 12.10118071 +1204.799867 13.10469862 +1124.697768 14.10500889 +1055.675914 15.1010893 +995.514503 16.09535821 +942.4314655 17.08844874 +895.1286184 18.07983805 +852.7719486 19.06994856 +814.4203936 20.06368569 +776.3126368 21.15603198 +727.265171 22.74213598 +684.1599545 24.33415231 +644.3060313 26.00826302 +608.0233319 27.73096739 +576.4101078 29.41725959 +545.0375944 31.28963752 +513.2734832 33.43510408 +474.5962591 36.45331663 +441.7886635 39.44333088 +413.5929949 42.41036091 +388.8059905 45.38900958 +366.8842513 48.375086 +353.6729778 50.36091314 +324.3639224 55.36349998 +299.7346427 60.37700251 +278.6812151 65.38867621 +260.4951447 70.39844562 +244.6978711 75.39355044 +230.695818 80.38512344 +218.2759105 85.37795287 +207.1516012 90.36681168 +197.1868792 95.35837347 +188.1040758 100.3395941 +172.1578547 110.4183281 +158.9748754 120.2996678 +147.5815278 130.2952362 +137.727079 140.2841253 +129.1185112 150.2692389 +121.5389602 160.2577876 +114.8296799 170.2444285 +108.8287854 180.2368407 +103.4425159 190.2327769 +98.60578681 200.2304708 +94.21141942 210.2236698 +90.23553062 220.2125551 +86.58030888 230.2277661 +83.25574143 240.23083 +80.20227544 250.2180352 +77.3855594 260.2317977 +74.79145382 270.2193909 +72.38321253 280.2336986 +70.14799547 290.2229491 +68.07617245 300.2372723 +66.14304515 310.2322127 +65.22236663 315.2374946 +64.33962721 320.2386422 +63.3164124 326.2368582 +62.65607917 330.2299146 diff --git a/tecs/inp/z030114.inp b/tecs/inp/z030114.inp new file mode 100644 index 0000000..6c36195 --- /dev/null +++ b/tecs/inp/z030114.inp @@ -0,0 +1,67 @@ +sens=z030114 +unit=Ohm ! sensor format (mV,V,Ohm), log formats are choosen automatically +!tlim=3250 ! setpoint limit (automatic if omitted) +type=C ! sensor type (Special,Si,GaAlAs,Pt250,Pt500,Pt2500,RhFe,C,Cernox,RuOx,Ge) (special if omitted) +!excit=300uA ! (off,30nA,100nA,300nA,1uA,3uA,10uA,30uA,100uA,300uA,1mA,10mV,1mV) (if omitted: default from sensor type) +!range=0 ! range in sensor units (if rang=0: determine range from table, if omitted: default from sensor type) +form=loglog +curv ! curve (sensor,temp/K) follows, must be ordered, but can be increasing or decreasing +7648.1 1.4745 +7197.9 1.5035 +6260.3 1.6022 +5522.5 1.7084 +4949.6 1.8062 +4464.5 1.8998 +3972.3 2.0088 +3247 2.211 +2731.2 2.4097 +2339.2 2.6156 +2058.7 2.8087 +1831 3.0063 +1562.9 3.3066 +1360 3.6039 +1152.1 4.0042 +1020.9 4.3323 +917.19 4.6551 +825.64 5.0141 +722.6 5.5186 +644.91 6.0149 +531.85 7.0282 +455.52 8.0262 +399.1 9.0341 +357.79 10.002 +286.16 12.501 +242.7 14.958 +211.27 17.569 +189.13 20.119 +169.22 23.232 +153.02 26.642 +139.23 30.499 +129.38 34.113 +121.06 37.908 +113.89 41.867 +108.04 46.054 +103.24 49.949 +97.819 55.114 +93.356 60.074 +89.546 64.945 +86.122 69.922 +83.087 74.929 +80.293 80.139 +75.959 89.602 +72.171 99.514 +68.786 109.9 +65.991 119.82 +61.366 139.58 +57.467 160.28 +54.38 180 +51.734 199.9 +49.442 219.83 +47.343 239.72 +45.471 260.1 +43.772 280.4 +42.983 290.42 +42.303 299.51 +41.908 305.15 +36 450 + diff --git a/tecs/instr_hosts.c b/tecs/instr_hosts.c index 5e1e787..3e4e231 100644 --- a/tecs/instr_hosts.c +++ b/tecs/instr_hosts.c @@ -8,19 +8,19 @@ typedef struct { char *instr; char *host; int port; char *user; int cod; } Instrument; static Instrument list[]={ - { "DMC", "lnsa05.psi.ch", 9753, "DMC" , 1}, - { "TOPSI", "pc4120.psi.ch", 9753, "TOPSI" , 1}, - { "SANS", "sans.psi.ch", 9753, "SANS" , 1}, + { "DMC", "pc4629.psi.ch", 9753, "DMC" , 1}, + { "MORPHEUS", "pc4120.psi.ch", 9753, "MORPHEUS" , 1}, + { "SANS", "pc3965.psi.ch", 9753, "SANS" , 1}, { "SANS2", "sans2.psi.ch", 9753, "SANS2" , 1}, - { "HRPT", "lnsa11.psi.ch", 9753, "HRPT" , 1}, + { "HRPT", "pc4630.psi.ch", 9753, "HRPT" , 1}, { "TRICS", "lnsa18.psi.ch", 9753, "TRICS" , 1}, { "AMOR", "lnsa14.psi.ch", 9753, "AMOR" , 1}, { "FOCUS", "lnsa16.psi.ch", 9753, "FOCUS" , 1}, { "TASP", "pc4478.psi.ch", 9753, "TASP", 1}, { "RITA", "pc4345.psi.ch", 9753, NULL , 0}, - { "PREP", "lnsa15.psi.ch", 9751, "lnsg" , 2}, + { "PREP", "lns1se.psi.ch", 9753, "admin" , 0}, + { "AREA", "lns1se.psi.ch", 9751, "admin" , 0}, { "PREP2", "lnsa15.psi.ch", 9756, "lnsg" , 2}, - { "AREA", "lnsa15.psi.ch", 9757, "lnsg" , 2}, { "TEST", "lnsa15.psi.ch", 9755, "lnslib", 2} }; diff --git a/tecs/make_gen b/tecs/make_gen index 6a3037d..e28ca6a 100644 --- a/tecs/make_gen +++ b/tecs/make_gen @@ -31,8 +31,15 @@ libtecsl.a: $(CLI_OBJ) all: libtecsl.a TecsServer TecsClient keep_running six -test: tecs_cli.c - echo $(VPATH) $C +CFGDIR=/afs/psi.ch/project/sinq/common/lib/tecs/cfg/ + +-include make_crv +-include src/make_crv + +$(SRC)make_crv: make_crv.tcsh inp/lsc.codes $(ALLINP) + $(SRC)make_crv.tcsh $(SRC)inp/lsc.codes + +# use target all_crv to make all curves in inp directory TecsServer: $(SERV_OBJ) $(HARDSUPLIB) $(FORTIFYOBJ) $(CC) $(CFLAGS) -o $@ $Q -lm @@ -41,7 +48,7 @@ lsc331: lsc331.o coc_server.o tecs_lsc.o tecs_serial.o coc_logfile.o \ $(LIBR_OBJ) $(HARDSUPLIB) $(FORTIFYOBJ) $(CC) $(CFLAGS) -o $@ $Q -lm -TecsClient: $(TECLI_OBJ) $(FORTIFYOBJ) +TecsClient: $(TECLI_OBJ) $(FORTIFYOBJ) pgplus/libpgplus.a $(FC) -o $@ $Q $(PGLIB) $(RDLIB) $(HARDSUPLIB): @@ -51,18 +58,8 @@ $(HARDSUPLIB): libtecs.so: tecs_c.c $(CLI_OBJ) $(FORTIFYOBJ) $(CC) $(CFLAGS) -shared -o $@ $Q -# -- for Tru64 Unix only -conv: strings.f90 conv.f90 sys_cmdpar.o str.o - f90 -o conv $Q - -config: tecs tecs/tecs.cfg - -tecs: conv src/cfg/*.inp - ./conv all - touch tecs - -tecs/tecs.cfg: src/cfg/*.cfg - cp src/cfg/*.cfg tecs/ +ccrv: conv.f sys_cmdpar.o str.o cvt.o + $(FC) $(FFLAGS) -o ccrv $Q # -- needs special include tecs_serial.o: tecs_serial.c diff --git a/tecs/makefile_alpha b/tecs/makefile_alpha index 9bf4268..6ea743a 100644 --- a/tecs/makefile_alpha +++ b/tecs/makefile_alpha @@ -16,8 +16,8 @@ ARFLAGS = cr # -- system dependent routines SYS_OPEN = _alpha -# -- PGPLOT library -PGLIB =$(PGPLOT_DIR)/libpgplot.a -L/usr/X11R6/lib -lX11 +# -- PGPLOT library additions +PGLIB = -L/usr/X11R6/lib -lX11 # -- readline library RDLIB =-lreadline -ltermcap diff --git a/tecs/makefile_linux b/tecs/makefile_linux index b3f7ebc..31e2d3b 100644 --- a/tecs/makefile_linux +++ b/tecs/makefile_linux @@ -13,15 +13,13 @@ SICS=$(SRC).. CC = gcc FC = g77 CFLAGS = -DLINUX -g $(DFORTIFY) -I../.. -FFLAGS = -u -fvxt -g +FFLAGS = -Wimplicit -g ARFLAGS = cr # -- system dependent routines -# -- PGPLOT library -#PGPLOT =/afs/psi.ch/project/sinq/linux/pgplot/ -PGPLOT =/afs/psi.ch/user/z/zolliker/pgplot/ -PGLIB =$(PGPLOT)/libpgplot.a -L/usr/X11R6/lib -lX11 +# -- PGPLOT library additions +PGLIB = -L/usr/X11R6/lib -lX11 # -- library for ASYNSRV HARDSUPLIB=../hardsup/libhlib.a diff --git a/tecs/myc_buf.c b/tecs/myc_buf.c index 8c0e51b..c4b6dec 100644 --- a/tecs/myc_buf.c +++ b/tecs/myc_buf.c @@ -154,8 +154,9 @@ int StrPut(StrBuf *buf, const char *str, int sep) { } } } - if (pos+l >= buf->dsize) - ERR_MSG("buffer too short"); + if (pos+l >= buf->dsize) { + ERR_MSG("buffer too short"); + } if (quote!='\0') { buf->buf[pos]=quote; pos++; strcpy(buf->buf + pos, str); diff --git a/tecs/six.c b/tecs/six.c index 57b9ea5..2cce3f4 100644 --- a/tecs/six.c +++ b/tecs/six.c @@ -259,6 +259,7 @@ int setrights(int gotolevel) { } else { deflevel=2; } +/* if (NULL != strstr(instr, "TASP")) { if (user1[0]=='\0') { str_copy(user1,"Spy"); @@ -269,6 +270,7 @@ int setrights(int gotolevel) { str_copy(pswd2,"007"); } } +*/ if (gotolevel==0) gotolevel=deflevel; if (gotolevel==1) { if (user1[0]=='\0') { diff --git a/tecs/str.f b/tecs/str.f index 5bd82c1..59afed8 100644 --- a/tecs/str.f +++ b/tecs/str.f @@ -129,3 +129,250 @@ pos=0 end +!! + subroutine STR_SPLIT(STR, DELIM, START, ENDE) !! +!! +!! split string into sequences separated by DELIM +!! for the first sequence set ENDE=0 and START=0 (or START=n for other start position n+1) +!! result: end of list: ENDE=-1 +!! empty sequence: START=ENDE+1 +!! normal sequence: STR(START:ENDE) without delimiter +!! +!! if ENDE has not a legal value, nothing happens + + character STR*(*), DELIM*(*) !! (in) string, delimiter + integer START, ENDE !! (in/out) start/end position + + integer i + + if (ende .lt. 0 .or. ende .ge. len(str) .or. start .lt. 0) then + ende=-1 + RETURN + endif + if (ende .ne. 0) start=ende+len(delim) + if (start .ge. len(str)) then + if (start .gt. len(str)) then + ende=-1 + RETURN + endif + i=0 + else + i=index(str(start+1:), delim) + endif + if (i .eq. 0) then + ende=len(str) + else + ende=start+i-1 + endif + start=start+1 + end + +!! + subroutine STR_GET_ELEM(STR, POS, ELEM) !! +!! +!! reads next element ELEM from string STR(POS:). Elements are separated by +!! spaces combined with one control-char (assume tab) or one comma. +!! return ' ' when STR(POS:) contains only whitespace or when pos is to high +!! + character STR*(*) !! (in) input string + character ELEM*(*) !! (out) element read + integer POS !! (in/out) read position + + integer start + + +1 if (pos .gt. len(str)) then + elem=' ' + RETURN + endif + if (str(pos:pos) .eq. ' ') then + pos=pos+1 + goto 1 + endif + start=pos +2 if (str(pos:pos) .gt. ' ' .and. str(pos:pos) .ne. ',') then + pos=pos+1 + if (pos .le. len(str)) then + goto 2 + endif + pos=pos-1 + endif + if (str(pos:pos) .eq. ',' .or. str(pos:pos) .lt. ' ') then + if (start .eq. pos) then + elem=str(start:pos) + else + elem=str(start:pos-1) + endif + pos=pos+1 + RETURN + endif + elem=str(start:pos-1) + if (str(pos:) .eq. ' ') RETURN +3 if (str(pos:pos) .eq. ' ') then + pos=pos+1 + if (pos .gt. len(str)) stop 'STR_GET_ELEM: assertion failed' + goto 3 + endif + if (str(pos:pos) .eq. ',' .or. str(pos:pos) .lt. ' ') then + pos=pos+1 + endif + end + +!! + integer function STR_FIND_ELEM(STR, ELEM) !! +!! +!! find column index of element ELEM (case insensitive) +!! only the first 64 chars of each element are checked +!! 0 is returned when not found +!! + character STR*(*), ELEM*(*) + character ups*64, upe*64 + integer pos, idx + + pos=1 + call str_upcase(upe, elem) + idx=0 + + call str_get_elem(str, pos, ups) + do while (ups .ne. ' ') + idx=idx+1 + call str_upcase(ups, ups) + if (ups .eq. upe) then + str_find_elem=idx + RETURN + endif + call str_get_elem(str, pos, ups) + enddo + str_find_elem=0 + RETURN + end + +!! + subroutine STR_SUBSTITUTE(RESULT, STR, OLD, NEW) !! +!! +!! replace all occurences of substring OLD in STR by NEW +!! special case: if NEW=CHAR(0) then a null length string is replaced +!! + character RESULT*(*), STR*(*) !! (out), (in) strings (must either be equal or not overlap) + character OLD*(*), NEW*(*) !! substrings (in) + + integer i,j,k + + i=0 + j=index(str, old)-1 + if (len(new) .eq. 1 .and. new(1:1) .eq. char(0)) then + k=0 + do while (j .ge. 0) + if (j .gt. 0) result(k+1:k+j)=str(i+1:i+j) + i=i+j+len(old) + k=k+j + if (i .ge. len(str)) then + if (k .lt. len(result)) result(k+1:)=' ' + RETURN + endif + j=index(str(i+1:), old)-1 + enddo + if (k .lt. len(result)) result(k+1:)=str(i+1:) + elseif (len(old) .ge. len(new)) then + k=0 + do while (j .ge. 0) + if (j .gt. 0) result(k+1:k+j)=str(i+1:i+j) + i=i+j+len(old) + k=k+j + result(k+1:k+len(new))=new + k=k+len(new) + if (i .ge. len(str)) then + if (k .lt. len(result)) result(k+1:)=' ' + RETURN + endif + j=index(str(i+1:), old)-1 + enddo + if (k .lt. len(result)) result(k+1:)=str(i+1:) + else + result=str + do while (j .ne. 0) + i=i+j + result(i+1:)=new//result(i+len(old)+1:) + i=i+len(new) + if (i .ge. len(str)) RETURN + j=index(str(i+1:), old)-1 + enddo + endif + end + + subroutine STR_CRC(CRC,BUF) !! +!! +!! Computes a 16-bit Cyclic Redundancy Check for an character string BUF. +!! Before the first call CRC should be intitalized (i.e. to 0) - +!! between subsequent call it should left untouched. + + integer CRC !! (in/out) CRC code + character BUF*(*) !! characters + + + integer init,ireg,i,j,icrctb(0:255),ichr,ib1,ib2,ib3 + character*1 creg(4) + save icrctb,init,ib1,ib2,ib3 + equivalence (creg,ireg) ! used to get at the 4 bytes in an integer. + data init /0/ + + integer crc1, crc2 + + if (init.eq.0) then ! initialize tables? + init=1 + ireg=256*(256*ichar('3')+ichar('2'))+ichar('1') + do j=1,4 ! figure out which component of creg addresses which byte of ireg. + if (creg(j).eq.'1') ib1=j + if (creg(j).eq.'2') ib2=j + if (creg(j).eq.'3') ib3=j + enddo + do j=0,255 ! create CRCs of all characters. + ireg=j*256 + + do i=1,8 ! Here is where 8 one-bit shifts, and some XORs with the generator polynomial, are done. + ichr=ichar(creg(ib2)) + ireg=ireg+ireg + creg(ib3)=char(0) + if(ichr.gt.127)ireg=ieor(ireg,4129) + enddo + + icrctb(j)=ireg + enddo + endif + ireg=crc + crc1=ichar(creg(ib1)) + crc2=ichar(creg(ib2)) + + do j=1,len(buf) ! Main loop over the characters + ireg=icrctb(ieor(ichar(buf(j:j)),crc2)) + crc2=ieor(ichar(creg(ib2)),crc1) + crc1=ichar(creg(ib1)) + enddo + creg(ib1)=char(crc1) + creg(ib2)=char(crc2) + crc=ireg + return + end + +!! + subroutine STR_CRC_COMP(CRC, CHR) !! +!! +!! encode CRC (16 bit) as 3 characters in CHR +!! + integer CRC !! (in) + character CHR*3 !! (out) + + integer n,j + character*41 cs/'0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ$+-&_'/ + + if (crc .lt. 0 .or. crc .gt. 65535) stop 'STR_CRC_COMP: illegal CRC' + n=crc + j=mod(n,41) + chr(1:1)=cs(j+1:j+1) + n=n/41 + j=mod(n,41) + chr(2:2)=cs(j+1:j+1) + j=n/41 + chr(3:3)=cs(j+1:j+1) + end + diff --git a/tecs/tecs.c b/tecs/tecs.c index 7b3697c..78c0df8 100644 --- a/tecs/tecs.c +++ b/tecs/tecs.c @@ -21,6 +21,7 @@ #endif #define TABLE_FILE "tecs.cfg" +#define LSC_CODES "lsc.codes" #define LOGLIFETIME 24*3600 static SerChannel *ser=NULL; @@ -36,17 +37,18 @@ typedef struct { char ch[4]; float t, t0, t1, t2, min, max, band; /* temperatures */ float scale; /* scale for extreme ranges */ - float kink; /* for T > kink scale is used + float kink; /* for T > kink values are scaled kink > RT for thermocouples going to more than 1500 K */ - float lim; /* range limit (used when two sensors present) */ + float lim; /* precise range limit (used when two sensors are present) */ float alarm; int customAlarm; int stat1, stat2; /* reading status summary */ int present; /* 0: sensor inactive, 1: sensor configured, -1: sensor parameters read */ int readStat; /* reading status */ int dispfld; - char dispfmt; char curve[32]; /* name of curve file */ + char type[4]; + char dispfmt; char typ; } SensorT; @@ -88,6 +90,7 @@ typedef struct _Plug { int codChanged; /* code has changed */ int codDefined; /* code is not yet confirmed */ char device[16]; /* device name */ + char descr[80]; } Plug; static Plug @@ -107,7 +110,7 @@ static float powFact=1, /* power factor (for external power supplies) */ resist=10, /* heater resistance */ tShift=0, /* setpoint shift */ - full, /* full value for helium level */ + empty, full, /* empty/full value for helium level */ prop, integ, deriv, /* pid */ maxShift=2, /* maximal shift in when controlMode=2 */ maxOver=0, /* maximal overshoot in when controlMode=2 */ @@ -189,9 +192,9 @@ static char alarmHistory[N_SENSORS], swap[4], dev[80], - dev0[80], - dev1[80], devHelp[10000], + update[32], /* update script option */ + lscfg[256], /* lsc commands for configuration */ controlChannel[4]="A"; static char @@ -283,6 +286,7 @@ int InstalCurve(SensorT *sensor, char *devArg) { *e, /* cache part after found entry */ *res, *t; int i, n, c1, c2; + char ch; char used[60]; FILE *fil; @@ -394,6 +398,16 @@ int InstalCurve(SensorT *sensor, char *devArg) { if (e!=NULL) { *e='\0'; e++; } } } + + if (num > 20 && strlen(chead) > 10) { /* replace name by a more meaningful */ + for (i=0; i<10 && i20) i=12; /* check only from 12th character (CRC) for user curves */ if (head[0]!='\0' && LscEqPar(head+i, chead+i)) { /* header matches: select sensor type and curve */ @@ -534,34 +548,53 @@ int ReadTable(void) { OnError: return -1; } +void InitSensor(SensorT *s) { + s->t=DATA_UNDEF; + s->scale=1; + s->kink=0; + s->lim=0; + s->alarm=0; + s->customAlarm=0; + s->present=0; + s->curve[0]='\0'; + s->type[0]='\0'; +} + int PrepInput(char *label) { char *t, *e; char nam[16], chans[8], typ; + char buf[256]; int i, j, l; SensorT *s; + char *cfg; - ERR_I(ReadTable()); - t=strstr(table, label); - if (t==NULL) ERR_MSG("device not found"); - e=strchr(t, '\''); - if (e==NULL || e>strchr(t,'\n')) ERR_MSG("missing ' or device name in table file"); - t=e+1; + if (label[0]=='\'') { + str_copy(nam, label+1); + nam[strlen(nam)-1]='\0'; /* strip off quote */ + } else { + str_copy(nam, label); + } + str_copy(buf, binDir); + str_append(buf, nam); + str_append(buf, ".cfg"); + cfg=str_read_file(buf); + if (cfg==NULL) { /* will be obsolete */ + ERR_I(ReadTable()); + t=strstr(table, label); + if (t==NULL) ERR_MSG("device not found"); + e=strchr(t, '\''); + if (e==NULL || e>strchr(t,'\n')) ERR_MSG("missing ' or device name in table file"); + t=e+1; + } if (plug==&plug0) { - sensA.present=0; - sensB.present=0; - sensA.scale=1; - sensB.scale=1; - sensA.kink=0; - sensB.kink=0; - sensA.lim=0; - sensB.lim=0; - sensA.alarm=0; - sensB.alarm=0; + InitSensor(&sensA); + InitSensor(&sensB); slope=0; ramp=0; controlMode=0; powFact=1; config[0]='\0'; + lscfg[0]='\0'; tLimit=0; tMaxLimit=0; keepT=0; @@ -570,43 +603,49 @@ int PrepInput(char *label) { initMaxPower=1; resist=10; } else { - sensC.present=0; - sensD.present=0; - sensC.scale=1; - sensD.scale=1; - sensC.kink=0; - sensD.kink=0; - sensC.lim=0; - sensD.lim=0; - sensC.alarm=0; - sensD.alarm=0; + InitSensor(&sensC); + InitSensor(&sensD); } + empty=0; dev[0]='\0'; str_copy(heUnits, "%"); - i=sscanf(t, "%12s%n", nam, &l); - if (i<1) ERR_MSG("missing device name"); - nam[strlen(nam)-1]='\0'; /* strip off quote */ - t+=l; - str_copy(chans, "____"); - i=sscanf(t, "%8s%n", chans, &l); - if (i<1) ERR_MSG("missing chans"); - t+=l; + if (cfg==NULL) { /* will be obsolete */ + i=sscanf(t, "%12s%n", nam, &l); + if (i<1) ERR_MSG("missing device name"); + nam[strlen(nam)-1]='\0'; /* strip off quote */ + t+=l; + str_copy(chans, "____"); + i=sscanf(t, "%8s%n", chans, &l); + if (i<1) ERR_MSG("missing chans"); + t+=l; - /* interprete settings until '+' appeares (after whitespace) */ - ERR_P(CocReadVars(t, '+')); + /* interprete settings until '+' appeares (after whitespace) */ + ERR_P(CocReadVars(t, '+')); + if (strlen(chans)>4) ERR_MSG("no more than 4 channels allowed"); + } else { + ERR_P(CocReadVars(cfg, '\0')); + } if (loop!=2) loop=1; - if (strlen(chans)>4) ERR_MSG("no more than 4 channels allowed"); if (plug==&plug0) { j=0; - str_copy(dev0, dev); } else { j=2; - str_copy(dev1, dev); } - if (chans[0]>'0' && chans[0]<='4') { - nScan=chans[0]-'0'; + str_copy(plug->descr, dev); + if (cfg==NULL) { /* will be obsolete */ + sensA.type[0]=chans[0]; + sensA.type[1]='\0'; + sensB.type[0]=chans[1]; + sensB.type[1]='\0'; + sensC.type[0]=chans[2]; + sensC.type[1]='\0'; + sensD.type[0]=chans[3]; + sensD.type[1]='\0'; + } + if (sensA.type[0]>'0' && sensA.type[0]<='4') { + nScan=sensA.type[0]-'0'; for (i=4;i<4+nScan;i++) { s=sensors[i]; s->present=-1; @@ -614,7 +653,7 @@ int PrepInput(char *label) { if (s->scale==0.0) s->scale=1.0; s->typ='1'+i-4; } - chans[0]='_'; + sensA.type[0]='\0'; for (i=4+nScan; it=DATA_UNDEF; sensors[i]->present=0; @@ -634,7 +673,7 @@ int PrepInput(char *label) { } for (i=j; itype[0]; if (typ=='_') typ='\0'; if (NULL==strchr("mnslhxftk", typ)) ERR_MSG("unknown channel type code"); if (typ!='\0') { @@ -976,9 +1015,10 @@ int ReadTemp(void) { if (s->typ=='h') { hlev = s->t1; /* take minimum only */ - if (full>0) { - if (hlev0) { - he=hlev*100.0/full; + if (full!=empty) { + hlev=(hlev-empty)/(full-empty); + if (hlev<1.0 && hlev>0.0) { + he=hlev*100.0; s->t=he; tfill = tim % (24*3600) / 60; /* min since midnight */ dfill = mycDate(tim) % 10000; /* fill date without year */ @@ -1266,11 +1306,11 @@ void CalcMaxPower(void) { pr=pa; for (j=5; j>0; j--) { if (pquo) { + if (p/pr>=quo) { quo=p/pr; pw=pr; iAmp=i; iRange=j; } - } else if (pquo) { + } else if (p<=plim || pw==0) { + if (pr/p>=quo) { quo=pr/p; pw=pr; iAmp=i; iRange=j; } } @@ -1506,9 +1546,10 @@ void AssignTypes(void) { } } else { cryo.sensor1=samp.sensor1; - cryo.sensor2=samp.sensor2; } - } else if (samp.sensor1==NULL) { + cryo.sensor2=cryo.sensor1; + } + if (samp.sensor1==NULL) { samp.sensor1=cryo.sensor1; samp.sensor2=cryo.sensor2; } @@ -1608,7 +1649,7 @@ int Settings(void) { str_append(buf, "DISPLAY:[maxfld]"); ERR_P(LscCmd(ser, buf)); } - if (config[0] != '\0') { + if (config[0] != '\0') { /* obsolete */ str_copy(buf, binDir); str_append(buf, config); cfg=str_read_file(buf); @@ -1622,6 +1663,9 @@ int Settings(void) { FREE(cfg); } } + if (lscfg[0] != '\0') { + ERR_P(LscCmd(ser, lscfg)); + } if (settingsFlag) return 0; str_copy(statusBuf, "reading temperatures"); @@ -1638,8 +1682,11 @@ int Settings(void) { } int ConfigByCode(int plugNr) { - char buf[16]; - + char buf[256], nam[16]; + int c1, c2; + char *p; + FILE *fil; + plug=plugs[plugNr]; str_copy(plug->device,""); plug->devcmd=0; @@ -1649,8 +1696,23 @@ int ConfigByCode(int plugNr) { plug->sensor1->present=0; plug->sensor2->present=0; } else { - logfileOut(LOG_MAIN+LOG_STAT ,"configure plug%d for cod %+d\n", plugNr, plug->code); - sprintf(buf, "%+d,", plug->code); + str_copy(buf, binDir); + str_append(buf, LSC_CODES); + ERR_SP(fil=fopen(buf, "r")); + p=fgets(buf, sizeof(buf), fil); + c1=0; c2=0; + while (p!=NULL && plug->code != c1 && plug->code != c2) { + if (*p != '#') { + c1=0; c2=0; + sscanf(buf, "%15s %d %d", &nam, &c1, &c2); + } + p=fgets(buf, sizeof(buf), fil); + } + fclose(fil); + logfileOut(LOG_MAIN+LOG_STAT ,"configure plug%d for %s (code %d)\n", plugNr, nam, plug->code); + str_copy(buf, "'"); + str_append(buf, nam); + str_append(buf, "'"); ERR_I(PrepInput(buf)); } settingsFlag=1; @@ -1683,7 +1745,7 @@ int PeriodicTask(void) { char buf[256], lbuf[16]; char *next, *alms; int i, k, iret, cnt; - float t3[3], p, d, w, t, dif, htr0, mstep; + float t3[3], p, d, w, t, dif, htr0, mstep, fdif; if (nScan==0) { ERR_P(LscCmd(ser, "DIOST?>cod1,out1;DOUT 3,29;BUSY?>busy")); @@ -1892,11 +1954,12 @@ int PeriodicTask(void) { } logfileOut(LOG_MAIN, "adjusted mout=%.2f\n", mout); } - fbuf=htr-mout-prop/6*(setH-t); /* value of integrator (assume deriv=0) */ - if (fbuf > 99.8 && mout < 0 || - fbuf < 0.2 && mout > 0) { /* probably integrator overflow */ + fdif=FakeScale(ctlSens, tr)-t; + fbuf=htr-mout-prop/6*fdif; /* value of integrator (assume deriv=0) */ + if (fbuf > 99.8 && mout < 0 && fdif > 0 || + fbuf < 0.2 && mout > 0 && fdif < 0) { /* probably integrator overflow */ if (lastIntTim > 0) { - mout += (setH-t)*prop*integ/3000*(rdTim-lastIntTim); /* use mout for integral */ + mout += fdif*prop*integ/3000*(rdTim-lastIntTim); /* use mout for integral */ if (mout < -100) mout=-100; if (mout > 100) mout=100; ERR_P(LscCmd(ser, "MOUT [loop],[mout]")); @@ -1911,7 +1974,7 @@ int PeriodicTask(void) { } } if (cryo.sensor1!=samp.sensor1 && controlMode==2) { - d=(setH-t)/t; /* relative difference */ + d=fdif/t; /* relative difference */ w=exp(-d*d*230); /* gaussian */ /* if (w<0.1) tInt=0; reset when far from setpoint (more than 10 %) */ if (int2<1) int2=1; @@ -1965,6 +2028,7 @@ int PeriodicTask(void) { plug->codChanged=0; if (plug->code1==0) { logfileOut(LOG_MAIN, "plug%d unplugged\n", i); + str_copy(plug->descr,"unplugged"); } else { logfileOut(LOG_MAIN, "plugged %d on plug%d\n", plug->code1, i); } @@ -2428,14 +2492,14 @@ int StatusHdl(int mode, void *base, int fd) { } else { ERR_I(StrPut(&buf, device, ' ')); } - ERR_I(StrPut(&buf, dev0, StrNONE)); + ERR_I(StrPut(&buf, plug0.descr, StrNONE)); if (plug0.devcmd) { ERR_I(StrPut(&buf, " ", '*')); } if (p!=NULL) { ERR_I(StrPut(&buf, "\n ", ' ')); ERR_I(StrPut(&buf, p, ' ')); - ERR_I(StrPut(&buf, dev1, StrNONE)); + ERR_I(StrPut(&buf, plug1.descr, StrNONE)); if (plug1.devcmd) { ERR_I(StrPut(&buf, " ", '*')); } @@ -2448,7 +2512,7 @@ int StatusHdl(int mode, void *base, int fd) { } else { ERR_I(StrPut(&buf, "\ntarget", '=')); ERR_I(PutFloat(&buf, 5, set)); - if (ramp==0 || tr==setH) { + if (ramp==0 || tr==TrueScale(ctlSens, setH)) { ERR_I(StrPut(&buf, " K,", ' ')); } else { ERR_I(StrPut(&buf, " K ramping at", ' ')); @@ -2579,6 +2643,25 @@ int DevHelpHdl(int mode, void *base, int fd) { OnError: return -1; } +int UpdateHdl(int mode, void *base, int fd) { + char cmd[128]; + if (mode==COC_WR) { + return COC_DRD; + } else if (mode==COC_DRD) { + str_copy(cmd, "tecsinstall "); + str_lowcase(update, update); + str_append(cmd, update); + str_append(cmd, " "); + if (NULL==strstr(" cfg server sync ", cmd+11)) { + str_copy(update, "unknown"); + } else { + system(cmd); + } + } + return 0; + OnError: return -1; +} + int RemoteHdl(int mode, void *base, int fd) { if (mode==COC_WR) { return COC_DWR; @@ -2738,6 +2821,7 @@ int main(int argc, char *argv[]) { CocIntFld(SensorT, stat2, RD); CocStrFld(SensorT, ch, RD); CocStrFld(SensorT, curve, RD); + CocStrFld(SensorT, type, RD); CocDefFlt(maxPower, RW); CocHdl(MaxPowerHdl); CocDefFlt(slope, RW); CocHdl(MaxPowerHdl); @@ -2758,6 +2842,7 @@ int main(int argc, char *argv[]) { CocDefFlt(htr, RD); CocDefFlt(setH, RD); CocDefFlt(full, RW); + CocDefFlt(empty, RW); CocDefFlt(maxShift, RW); CocDefFlt(maxOver, RW); CocDefFlt(tm, RD); @@ -2798,9 +2883,9 @@ int main(int argc, char *argv[]) { CocDefStr(config, RD); CocDefStr(swap, RW); CocHdl(SwapHdl); CocDefStr(dev, RD); - CocDefStr(dev0, RD); - CocDefStr(dev1, RD); CocDefStr(devHelp, RD); CocHdl(DevHelpHdl); + CocDefStr(update, RW); CocHdl(UpdateHdl); + CocDefStr(lscfg, RD); CocDefInt(cod1, RD); CocDefInt(cod2, RD); diff --git a/tecs/tecs.tcl b/tecs/tecs.tcl index 6f19fe9..b819df8 100644 --- a/tecs/tecs.tcl +++ b/tecs/tecs.tcl @@ -1,3 +1,25 @@ -catch {evfactory del temperature} msg -evfactory new temperature tecs -SicsAlias temperature tt +#------------------------------------------------------------------------ +# tecs: a script to turn on and off temperature via tecs +# +# M. Zolliker, Jun 00 +#------------------------------------------------------------------------ + +ServerOption TecsPort 9753 + +#--------- some code to do proper initialization if necessary +set ret [catch {tecs} msg] +if {$ret != 0} { + Publish tecs User +} + +proc tecs { { arg1 "on"} { arg2 ""} { arg3 ""} } { + if {[string compare $arg1 "off"]==0 } { + evfactory del temperature + return "removed temperature" + } elseif {[string compare $arg1 "on"]==0 } { + evfactory new temperature tecs + return "installed temperature via TECS" + } else { + temperature $arg1 $arg2 $arg3 + } +} diff --git a/tecs/tecs_plot.f b/tecs/tecs_plot.f index f70a05f..9021031 100644 --- a/tecs/tecs_plot.f +++ b/tecs/tecs_plot.f @@ -133,7 +133,7 @@ tdif=myc_now()-t tdif=tdif-mod(tdif+1800*25, 3600)+1800 ! round to next full hour if (tdif .ne. 0) then - print *,'time difference ',tdif + print *,'time difference ',tdif/3600,' h' endif t=t+tdif if (showsets .eq. 1) then ! select only channels which have NOW a signal @@ -145,6 +145,7 @@ else if (showsets .eq. 2) then ! select all channels do im=1,nmax isx(im)=1 + focus(im)=unit(im) .eq. 1 enddo endif is=0 @@ -177,9 +178,9 @@ step=window/(dmax-2)+0.99 last=t first=t-min(dmax*step-1,nint(window)) - if (first .ne. t-nint(window)) then - print *,'t-shift',first-(t-nint(window)) - endif +! if (first .ne. t-nint(window)) then +! print *,'t-shift',first-(t-nint(window)) +! endif else if (mode .eq. zoom) then x2=(x1+x2+window)/2