home *** CD-ROM | disk | FTP | other *** search
/ The CDPD Public Domain Collection for CDTV 4 / CDPD_IV.bin / e / amiga_e_v2.1b / sources / utilities / d.e next >
Text File  |  1994-05-26  |  8KB  |  242 lines

  1. /* recursive directory tool
  2.  
  3.    examples: D dh0: COL=2 SIZE REC NOANSI
  4.              D docs: DO type >prt: %s
  5.              D emodules: REC TARGET=ram: DO showmodule %>%r.txt %s
  6.              D asm: TARGET=obj: DO genam %s -o%r.o
  7.  
  8.    %s is file (filename+path)
  9.    %f is file WITHOUT extension
  10.    %r is file without extension, but with leading <dir> replaced by
  11.       <target> (usefull if <commandline> allows for an outputfile)
  12.  
  13. BUGS:
  14. none left.
  15.  
  16. IMPROVEMENTS OVER OLD "D"
  17. - remarkably faster
  18. - recursive
  19. - calculates filesizes of whole directory trees
  20. - one, two and three columns
  21. - wildcards
  22. - better/faster sort
  23. - better coding: handles dirs of any size
  24. - lots of options through standard readargs()
  25. - powerfull script generation
  26. - uses nested exception handlers to keep track of missed
  27.   MatchEnd() calls on a CtrlC and sudden errors.
  28.  
  29. */
  30.  
  31. OPT OSVERSION=37
  32.  
  33. CONST MAXPATH=250
  34.  
  35. ENUM ER_NONE,ER_BADARGS,ER_MEM,ER_UTIL,ER_ITARG,ER_COML
  36. ENUM ARG_DIR,ARG_REC,ARG_COL,ARG_SIZE,ARG_NOSORT,ARG_NOFILES,
  37.      ARG_NODIRS,ARG_FULL,ARG_NOANSI,ARG_TARGET,ARG_COMMAND,NUMARGS
  38.  
  39. MODULE 'dos/dosasl', 'dos/dos', 'utility'
  40.  
  41. RAISE ER_MEM IF New()=NIL,      /* set common exceptions:                */
  42.       ER_MEM IF String()=NIL,      /* every call to these functions will be */
  43.       ERROR_BREAK IF CtrlC()=TRUE /* automatically checked against NIL,    */
  44.                   /* and the exception ER_MEM is raised    */
  45.  
  46. DEF dir,command,target,
  47.     recf=FALSE,col=3,comf=FALSE,sizef=FALSE,sortf=TRUE,filesf=TRUE,
  48.     fullf=FALSE,ansif=TRUE,dirsf=TRUE,dirw[100]:STRING,
  49.     rdargs=NIL,work[250]:STRING,work2[250]:STRING,dirno=0,
  50.     prtab[25]:LIST,prcopy[25]:LIST,workdir[250]:STRING
  51.  
  52. PROC main() HANDLE
  53.   DEF args[NUMARGS]:LIST,templ,x,lock,fib:fileinfoblock,s
  54.   IF (utilitybase:=OpenLibrary('utility.library',37))=NIL THEN Raise(ER_UTIL)
  55.   FOR x:=0 TO NUMARGS-1 DO args[x]:=0
  56.   templ:='DIR,REC/S,COL/K/N,SIZE/S,NOSORT/S,NOFILES/S,NODIRS/S,' +
  57.          'FULL/S,NOANSI/S,TARGET/K,DO/K/F'
  58.   rdargs:=ReadArgs(templ,args,NIL)
  59.   IF rdargs=NIL THEN Raise(ER_BADARGS)        /* initialise flags */
  60.   IF args[ARG_SIZE] THEN sizef:=TRUE        /* from command line args */
  61.   IF args[ARG_COL] THEN col:=Long(args[ARG_COL])
  62.   IF args[ARG_NOSORT] THEN sortf:=FALSE
  63.   IF args[ARG_NOANSI] THEN ansif:=FALSE
  64.   IF args[ARG_NOFILES] THEN filesf:=FALSE
  65.   IF args[ARG_NODIRS] THEN dirsf:=FALSE
  66.   IF args[ARG_REC] THEN recf:=TRUE
  67.   IF args[ARG_FULL] THEN fullf:=TRUE
  68.   target:=args[ARG_TARGET]
  69.   command:=args[ARG_COMMAND]
  70.   IF command THEN comf:=TRUE
  71.   IF (col<>1) AND (col<>2) THEN col:=3
  72.   IF target
  73.     x:=target+StrLen(target)-1
  74.     IF (x<target) OR ((x[]<>":") AND (x[]<>"/")) THEN Raise(ER_ITARG)
  75.   ENDIF
  76.   IF comf
  77.     sortf:=FALSE    /* read and convert commandline for scripts */
  78.     col:=1
  79.     filesf:=FALSE
  80.     dirsf:=FALSE
  81.     IF command[]=0 THEN Raise(ER_COML)
  82.     s:=command
  83.     WHILE x:=s[]++
  84.       IF x="%"
  85.         x:=s[]
  86.         SELECT x
  87.           CASE "s"; ListAdd(prtab,[1],1)        /* %s = fullpath */
  88.           CASE "f"; ListAdd(prtab,[work],1); s[]:="s"    /* %f = work     */
  89.           CASE "r"; ListAdd(prtab,[work2],1); s[]:="s"    /* %r = work2    */
  90.           DEFAULT; s[-1]:=" "
  91.         ENDSELECT
  92.       ENDIF
  93.     ENDWHILE
  94.   ENDIF
  95.   dir:=args[ARG_DIR]
  96.   IF dir THEN StrCopy(dirw,dir,ALL)
  97.   lock:=Lock(dirw,-2)
  98.   IF lock                  /* if yes, the prob. dir, else wildcard */
  99.     IF Examine(lock,fib) AND (fib.direntrytype>0)
  100.       AddPart(dirw,'#?',100)
  101.     ENDIF
  102.     UnLock(lock)
  103.   ENDIF
  104.   recdir(dirw)
  105.   Raise(ER_NONE)
  106. EXCEPT
  107.   IF rdargs THEN FreeArgs(rdargs)
  108.   IF utilitybase THEN CloseLibrary(utilitybase)
  109.   SELECT exception
  110.     CASE ER_BADARGS;            WriteF('Bad Arguments for D!\n')
  111.     CASE ER_MEM;                WriteF('No mem!\n')
  112.     CASE ER_COML;               WriteF('No commandline specified\n')
  113.     CASE ER_ITARG;              WriteF('Illegal target\n')
  114.     CASE ER_UTIL;               WriteF('Could not open "utility.library" v37\n')
  115.     CASE ERROR_BREAK;           WriteF('User terminated D\n')
  116.     CASE ERROR_BUFFER_OVERFLOW; WriteF('Internal error\n')
  117.     DEFAULT;                    PrintFault(exception,'Dos Error')
  118.   ENDSELECT
  119. ENDPROC
  120.  
  121. PROC recdir(dirr) HANDLE
  122.   DEF er,i:PTR TO fileinfoblock,size=0,anchor=NIL:PTR TO anchorpath,fullpath,
  123.       flist=NIL,first,entries=0,sortdone,next,nnext,prev,ascii,x,y,flist2=NIL,
  124.       esc1,esc2,ds:PTR TO LONG,isfirst=0
  125.   anchor:=New(SIZEOF anchorpath+MAXPATH)
  126.   anchor.breakbits:=4096
  127.   anchor.strlen:=MAXPATH-1
  128.   esc1:=IF ansif THEN '\e[1;32m' ELSE ''
  129.   esc2:=IF ansif THEN '\e[0;31m' ELSE ''
  130.   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]']
  131.   er:=MatchFirst(dirr,anchor)            /* collect all strings */
  132.   WHILE er=0
  133.     fullpath:=anchor+SIZEOF anchorpath
  134.     i:=anchor.info
  135.     ascii:=IF fullf THEN fullpath ELSE i.filename
  136.     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)
  137.     IF IF i.direntrytype>0 THEN dirsf ELSE filesf
  138.       first:=String(EstrLen(work))
  139.       StrCopy(first,work,ALL)
  140.       flist:=Link(first,flist)
  141.       INC entries
  142.     ENDIF
  143.     IF i.direntrytype<0 THEN size:=size+i.size
  144.     IF (i.direntrytype<0) AND comf        /* execute commandline */
  145.       ListCopy(prcopy,prtab,ALL)
  146.       IF comf THEN MapList({x},prcopy,prcopy,`IF x=1 THEN fullpath ELSE x)
  147.       StrCopy(work,fullpath,ALL)
  148.       x:=InStr(work,'.',0)
  149.       IF x<>-1 THEN SetStr(work,x)        /* find f% */
  150.       IF target
  151.         StrCopy(work2,target,ALL)
  152.         x:=work; y:=dirw        /* was dirr */
  153.         WHILE x[]++=y[]++ DO NOP
  154.         DEC x
  155.         StrAdd(work2,x,ALL)            /* find r% */
  156.       ELSE
  157.         StrCopy(work2,work,ALL)
  158.       ENDIF
  159.       IF isfirst++=0
  160.         StrCopy(workdir,work2,ALL)        /* see if makedir is needed */
  161.         SetStr(workdir,PathPart(work2)-work2)
  162.         x:=Lock(workdir,-2)
  163.         IF x THEN UnLock(x) ELSE WriteF('makedir \s\n',workdir)
  164.       ENDIF
  165.       Flush(stdout); VfPrintf(stdout,command,prcopy); Flush(stdout)
  166.       WriteF('\n')
  167.     ENDIF
  168.     IF recf AND (i.direntrytype>0)        /* do recursion(=tail) */
  169.       x:=StrLen(fullpath)
  170.       IF x+5<MAXPATH THEN CopyMem('/#?',fullpath+x,4)
  171.       size:=size+recdir(fullpath)
  172.       fullpath[x]:=0
  173.     ENDIF
  174.     er:=MatchNext(anchor)
  175.   ENDWHILE
  176.   IF er<>ERROR_NO_MORE_ENTRIES THEN Raise(er)
  177.   MatchEnd(anchor)
  178.   Dispose(anchor)
  179.   anchor:=NIL
  180.   flist:=Link(String(1),flist)
  181.   IF entries>2 AND sortf
  182.     REPEAT
  183.       sortdone:=TRUE                /* sort dirlist */
  184.       prev:=first:=flist
  185.       WHILE first:=Next(first)
  186.         IF next:=Next(first)
  187.           IF Stricmp(first,next)>0
  188.             nnext:=Next(next)
  189.             Link(prev,first:=Link(next,Link(first,nnext)))
  190.             sortdone:=FALSE
  191.           ENDIF
  192.         ENDIF
  193.         CtrlC()
  194.         prev:=first
  195.       ENDWHILE
  196.     UNTIL sortdone
  197.   ENDIF
  198.   IF col>1                    /* put dirlist in columns */
  199.     x:=entries/col
  200.     IF x*col<entries THEN INC x
  201.     first:=Next(flist)
  202.     next:=Forward(first,x)
  203.     nnext:=IF col=3 THEN Forward(next,x) ELSE NIL
  204.     flist2:=Link(String(1),flist2)
  205.     prev:=flist2
  206.     WHILE first AND (x-->=0)
  207.       StrCopy(work,first,ALL)
  208.       IF next
  209.         StrAdd(work,' ',1)
  210.         StrAdd(work,next,ALL)
  211.         IF nnext
  212.           StrAdd(work,' ',1)
  213.           StrAdd(work,nnext,ALL)
  214.         ENDIF
  215.       ENDIF
  216.       ascii:=String(EstrLen(work))
  217.       StrCopy(ascii,work,ALL)
  218.       Link(prev,prev:=ascii)
  219.       first:=Next(first)
  220.       IF next THEN next:=Next(next)
  221.       IF nnext THEN nnext:=Next(nnext)
  222.     ENDWHILE
  223.     DisposeLink(flist)
  224.     flist:=flist2
  225.   ENDIF
  226.   IF comf=FALSE                        /* display dir */
  227.     IF dirno THEN WriteF('\n')
  228.     WriteF(IF ansif THEN '\e[1mDirectory of: "\s"\e[0m\n' ELSE 'Directory of: "\s"\n',dirr)
  229.   ENDIF
  230.   first:=flist
  231.   WHILE first:=Next(first)
  232.     WriteF('\s\n',first)
  233.     CtrlC()
  234.   ENDWHILE
  235.   IF sizef THEN WriteF('BYTE SIZE: \d\n',size)
  236.   DisposeLink(flist)
  237.   INC dirno
  238. EXCEPT                                  /* nested exception handlers! */
  239.   IF anchor THEN MatchEnd(anchor)
  240.   Raise(exception)  /* this way, we call _all_ handlers in the recursion  */
  241. ENDPROC size        /* and thus calling MatchEnd() on all hanging anchors */
  242.