home *** CD-ROM | disk | FTP | other *** search
- /* recursive directory tool
-
- examples: D dh0: COL=2 SIZE REC NOANSI
- D docs: DO type >prt: %s
- D emodules: REC TARGET=ram: DO showmodule %>%r.txt %s
- D asm: TARGET=obj: DO genam %s -o%r.o
-
- %s is file (filename+path)
- %f is file WITHOUT extension
- %r is file without extension, but with leading <dir> replaced by
- <target> (usefull if <commandline> allows for an outputfile)
-
- BUGS:
- none left.
-
- IMPROVEMENTS OVER OLD "D"
- - remarkably faster
- - recursive
- - calculates filesizes of whole directory trees
- - one, two and three columns
- - wildcards
- - better/faster sort
- - better coding: handles dirs of any size
- - lots of options through standard readargs()
- - powerfull script generation
- - uses nested exception handlers to keep track of missed
- MatchEnd() calls on a CtrlC and sudden errors.
-
- */
-
- OPT OSVERSION=37
-
- CONST MAXPATH=250
-
- ENUM ER_NONE,ER_BADARGS,ER_MEM,ER_UTIL,ER_ITARG,ER_COML
- ENUM ARG_DIR,ARG_REC,ARG_COL,ARG_SIZE,ARG_NOSORT,ARG_NOFILES,
- ARG_NODIRS,ARG_FULL,ARG_NOANSI,ARG_TARGET,ARG_COMMAND,NUMARGS
-
- MODULE 'dos/dosasl', 'dos/dos', 'utility'
-
- RAISE ER_MEM IF New()=NIL, /* set common exceptions: */
- ER_MEM IF String()=NIL, /* every call to these functions will be */
- ERROR_BREAK IF CtrlC()=TRUE /* automatically checked against NIL, */
- /* and the exception ER_MEM is raised */
-
- DEF dir,command,target,
- recf=FALSE,col=3,comf=FALSE,sizef=FALSE,sortf=TRUE,filesf=TRUE,
- fullf=FALSE,ansif=TRUE,dirsf=TRUE,dirw[100]:STRING,
- rdargs=NIL,work[250]:STRING,work2[250]:STRING,dirno=0,
- prtab[25]:LIST,prcopy[25]:LIST,workdir[250]:STRING
-
- PROC main() HANDLE
- DEF args[NUMARGS]:LIST,templ,x,lock,fib:fileinfoblock,s
- IF (utilitybase:=OpenLibrary('utility.library',37))=NIL THEN Raise(ER_UTIL)
- FOR x:=0 TO NUMARGS-1 DO args[x]:=0
- templ:='DIR,REC/S,COL/K/N,SIZE/S,NOSORT/S,NOFILES/S,NODIRS/S,' +
- 'FULL/S,NOANSI/S,TARGET/K,DO/K/F'
- rdargs:=ReadArgs(templ,args,NIL)
- IF rdargs=NIL THEN Raise(ER_BADARGS) /* initialise flags */
- IF args[ARG_SIZE] THEN sizef:=TRUE /* from command line args */
- IF args[ARG_COL] THEN col:=Long(args[ARG_COL])
- IF args[ARG_NOSORT] THEN sortf:=FALSE
- IF args[ARG_NOANSI] THEN ansif:=FALSE
- IF args[ARG_NOFILES] THEN filesf:=FALSE
- IF args[ARG_NODIRS] THEN dirsf:=FALSE
- IF args[ARG_REC] THEN recf:=TRUE
- IF args[ARG_FULL] THEN fullf:=TRUE
- target:=args[ARG_TARGET]
- command:=args[ARG_COMMAND]
- IF command THEN comf:=TRUE
- IF (col<>1) AND (col<>2) THEN col:=3
- IF target
- x:=target+StrLen(target)-1
- IF (x<target) OR ((x[]<>":") AND (x[]<>"/")) THEN Raise(ER_ITARG)
- ENDIF
- IF comf
- sortf:=FALSE /* read and convert commandline for scripts */
- col:=1
- filesf:=FALSE
- dirsf:=FALSE
- IF command[]=0 THEN Raise(ER_COML)
- s:=command
- WHILE x:=s[]++
- IF x="%"
- x:=s[]
- SELECT x
- CASE "s"; ListAdd(prtab,[1],1) /* %s = fullpath */
- CASE "f"; ListAdd(prtab,[work],1); s[]:="s" /* %f = work */
- CASE "r"; ListAdd(prtab,[work2],1); s[]:="s" /* %r = work2 */
- DEFAULT; s[-1]:=" "
- ENDSELECT
- ENDIF
- ENDWHILE
- ENDIF
- dir:=args[ARG_DIR]
- IF dir THEN StrCopy(dirw,dir,ALL)
- lock:=Lock(dirw,-2)
- IF lock /* if yes, the prob. dir, else wildcard */
- IF Examine(lock,fib) AND (fib.direntrytype>0)
- AddPart(dirw,'#?',100)
- ENDIF
- UnLock(lock)
- ENDIF
- recdir(dirw)
- Raise(ER_NONE)
- EXCEPT
- IF rdargs THEN FreeArgs(rdargs)
- IF utilitybase THEN CloseLibrary(utilitybase)
- SELECT exception
- CASE ER_BADARGS; WriteF('Bad Arguments for D!\n')
- CASE ER_MEM; WriteF('No mem!\n')
- CASE ER_COML; WriteF('No commandline specified\n')
- CASE ER_ITARG; WriteF('Illegal target\n')
- CASE ER_UTIL; WriteF('Could not open "utility.library" v37\n')
- CASE ERROR_BREAK; WriteF('User terminated D\n')
- CASE ERROR_BUFFER_OVERFLOW; WriteF('Internal error\n')
- DEFAULT; PrintFault(exception,'Dos Error')
- ENDSELECT
- ENDPROC
-
- PROC recdir(dirr) HANDLE
- DEF er,i:PTR TO fileinfoblock,size=0,anchor=NIL:PTR TO anchorpath,fullpath,
- flist=NIL,first,entries=0,sortdone,next,nnext,prev,ascii,x,y,flist2=NIL,
- esc1,esc2,ds:PTR TO LONG,isfirst=0
- anchor:=New(SIZEOF anchorpath+MAXPATH)
- anchor.breakbits:=4096
- anchor.strlen:=MAXPATH-1
- esc1:=IF ansif THEN '\e[1;32m' ELSE ''
- esc2:=IF ansif THEN '\e[0;31m' ELSE ''
- ds:=['\s\l\s[50]\s <dir>','\l\s[47] \r\d[8]','\s\l\s[30]\s <dir>','\l\s[27] \r\d[8]','\s\l\s[19]\s <dir>','\l\s[17] \r\d[7]']
- er:=MatchFirst(dirr,anchor) /* collect all strings */
- WHILE er=0
- fullpath:=anchor+SIZEOF anchorpath
- i:=anchor.info
- ascii:=IF fullf THEN fullpath ELSE i.filename
- IF i.direntrytype>0 THEN StringF(work,ds[col-1*2],esc1,ascii,esc2) ELSE StringF(work,ds[col-1*2+1],ascii,i.size)
- IF IF i.direntrytype>0 THEN dirsf ELSE filesf
- first:=String(EstrLen(work))
- StrCopy(first,work,ALL)
- flist:=Link(first,flist)
- INC entries
- ENDIF
- IF i.direntrytype<0 THEN size:=size+i.size
- IF (i.direntrytype<0) AND comf /* execute commandline */
- ListCopy(prcopy,prtab,ALL)
- IF comf THEN MapList({x},prcopy,prcopy,`IF x=1 THEN fullpath ELSE x)
- StrCopy(work,fullpath,ALL)
- x:=InStr(work,'.',0)
- IF x<>-1 THEN SetStr(work,x) /* find f% */
- IF target
- StrCopy(work2,target,ALL)
- x:=work; y:=dirw /* was dirr */
- WHILE x[]++=y[]++ DO NOP
- DEC x
- StrAdd(work2,x,ALL) /* find r% */
- ELSE
- StrCopy(work2,work,ALL)
- ENDIF
- IF isfirst++=0
- StrCopy(workdir,work2,ALL) /* see if makedir is needed */
- SetStr(workdir,PathPart(work2)-work2)
- x:=Lock(workdir,-2)
- IF x THEN UnLock(x) ELSE WriteF('makedir \s\n',workdir)
- ENDIF
- Flush(stdout); VfPrintf(stdout,command,prcopy); Flush(stdout)
- WriteF('\n')
- ENDIF
- IF recf AND (i.direntrytype>0) /* do recursion(=tail) */
- x:=StrLen(fullpath)
- IF x+5<MAXPATH THEN CopyMem('/#?',fullpath+x,4)
- size:=size+recdir(fullpath)
- fullpath[x]:=0
- ENDIF
- er:=MatchNext(anchor)
- ENDWHILE
- IF er<>ERROR_NO_MORE_ENTRIES THEN Raise(er)
- MatchEnd(anchor)
- Dispose(anchor)
- anchor:=NIL
- flist:=Link(String(1),flist)
- IF entries>2 AND sortf
- REPEAT
- sortdone:=TRUE /* sort dirlist */
- prev:=first:=flist
- WHILE first:=Next(first)
- IF next:=Next(first)
- IF Stricmp(first,next)>0
- nnext:=Next(next)
- Link(prev,first:=Link(next,Link(first,nnext)))
- sortdone:=FALSE
- ENDIF
- ENDIF
- CtrlC()
- prev:=first
- ENDWHILE
- UNTIL sortdone
- ENDIF
- IF col>1 /* put dirlist in columns */
- x:=entries/col
- IF x*col<entries THEN INC x
- first:=Next(flist)
- next:=Forward(first,x)
- nnext:=IF col=3 THEN Forward(next,x) ELSE NIL
- flist2:=Link(String(1),flist2)
- prev:=flist2
- WHILE first AND (x-->=0)
- StrCopy(work,first,ALL)
- IF next
- StrAdd(work,' ',1)
- StrAdd(work,next,ALL)
- IF nnext
- StrAdd(work,' ',1)
- StrAdd(work,nnext,ALL)
- ENDIF
- ENDIF
- ascii:=String(EstrLen(work))
- StrCopy(ascii,work,ALL)
- Link(prev,prev:=ascii)
- first:=Next(first)
- IF next THEN next:=Next(next)
- IF nnext THEN nnext:=Next(nnext)
- ENDWHILE
- DisposeLink(flist)
- flist:=flist2
- ENDIF
- IF comf=FALSE /* display dir */
- IF dirno THEN WriteF('\n')
- WriteF(IF ansif THEN '\e[1mDirectory of: "\s"\e[0m\n' ELSE 'Directory of: "\s"\n',dirr)
- ENDIF
- first:=flist
- WHILE first:=Next(first)
- WriteF('\s\n',first)
- CtrlC()
- ENDWHILE
- IF sizef THEN WriteF('BYTE SIZE: \d\n',size)
- DisposeLink(flist)
- INC dirno
- EXCEPT /* nested exception handlers! */
- IF anchor THEN MatchEnd(anchor)
- Raise(exception) /* this way, we call _all_ handlers in the recursion */
- ENDPROC size /* and thus calling MatchEnd() on all hanging anchors */
-