Clear["@"]; (********** INPUT STARTS **********) dir0="e:\\html\\pictures\\archives"; test=0; (* 1 for testing *) mroll=100; (* max. possible number of rolls *) myear=1999; (* the last year *) mdots=20; (* number of dots on both sides from the central dot *) firstyear=1996; local=0; (* !=0 if original full-size images are stored locally *) host0="http://lepera.chem.purdue.edu"; (* if local==0 then name of the host were they are stored *) archive=If[test==0 && local==0, 1, 0]; (* whether to create archive *) (********** INPUT ENDS **********) (* Eliminates flanking blanks or new-lines of a string. *) Module[{s,s0,s9}, flankblank[s_String]:= If[s=="",s, If[s0=StringTake[s,1];s0==" "||s0=="\n",flankblank[StringDrop[s,1]], If[s9=StringTake[s,-1];s9==" "||s9=="\n",flankblank[StringDrop[s,-1]],s]]] ]; (* Printing *) Module[{s}, p[s_String]:=Write[of,s] ]; (* Reading links data file *) flinks=ToFileName[dir0,"links.txt"]; ldata=ReadList[flinks,Record,RecordSeparators -> {"#"}]; mldata=Length[ldata]; (* Defining root directory *) rootdir=""; Do[ndata=ldata[[n]]; nd=ReadList[StringToStream[ndata],Word]; If[nd[[1]]=="ROOTDIRECTORY", rootdir=nd[[2]]] ,{n,mldata}]; mrep=0; rootdir0="../.."; (* respectively to pictures/archives *) of=OpenWrite[ToFileName[dir0,"links.htm"],PageWidth->Infinity,FormatType->OutputForm]; ""//p; "
"//p; "The following list contains links that are automatically added to picture captions.
It was created from the data file links.txt automatically for easy view and testing of these links.
"//p;
Do[ndata=ldata[[n]];
mark=ReadList[StringToStream[ndata],Word]//First;
If[mark=="COMMENT" || mark=="ROOTDIRECTORY",Continue[]];
nd1=ReadList[StringToStream[ndata],Record,RecordSeparators->{"->"}];
If[Length[nd1]<2,Continue[]];
mrep++;
ref[mrep]=flankblank[StringReplace[nd1[[2]],{"ROOTDIRECTORY"->rootdir,"-NNNNN-"->"#"}]];
anchs=ReadList[StringToStream[nd1[[1]]],Record,RecordSeparators->{"!"}];
excl[mrep]=flankblank/@Drop[anchs,1]; (* Currently ignored *)
incl[mrep]=flankblank/@ReadList[StringToStream[anchs[[1]]],Record,RecordSeparators->{"|"}];
" yearpr<>"/"<>rollpr<>"/"<>fnpr<>".htm\">fnpr<>"-"<>rollpr<>" <---\"> yearne<>"/"<>rollne<>"/"<>fnne<>".htm\">fnne<>"-"<>rollne<>"\"> yearne<>"/"<>rollne<>"/"<>fnne<>".htm\">fnne<>"-"<>rollne<>" start the next roll\"> "<>caplink<>" #"<>fn<>"-"<>roll<>rolltit<>"
StringReplace[ref[mrep],rootdir->rootdir0]<>"\">"<>ToString[incl[mrep]]<>""<>
If[StringMatchQ[ref[mrep],"*"<>rootdir<>"*"]," (local)",""]//p
,{n,mldata}];
""//p;
Close[of];
(* icon's src *)
dot0="../../dot0.gif";
dot1="../../dot1.gif";
dot2="../../dot2.gif";
right0="../../right0.gif";
right1="../../right1.gif";
right2="../../right2.gif";
left0="../../left0.gif";
left1="../../left1.gif";
left2="../../left2.gif";
dot0a="../../dot0a.gif";
dot1a="../../dot1a.gif";
right0a="../../right0a.gif";
right1a="../../right1a.gif";
left0a="../../left0a.gif";
left1a="../../left1a.gif";
dots="../../dots.gif";
blanksrc="../../../../../blank.gif";
name0="d"<>ToString[mdots];
nameleft="d"<>ToString[mdots-1];
nameright="d"<>ToString[mdots+1];
(* Start scanning *)
If[test==1,{mroll,myear}={2,1996}];
npic=0;
Do[ (* year *) year=ToString[nyear];
Do[ (* roll *) roll=ToString[nroll];
dirslide=ToFileName[{dir0,"compress",year,roll,"jpeg"}];
If[FileType[dirslide]=!=Directory,Continue[]];
SetDirectory[dirslide];
fnames=FileNames["*.jpg"];
mf=Length[fnames];
(* Cycling through images *)
Do[fname=fnames[[nf]];
fn=StringDrop[fname,-4];
If[StringLength[fn]>3,Continue[],npic++];
years[npic]=year;rolls[npic]=roll;numbers[npic]=fn;
If[!NumberQ[startroll[nroll]],startroll[nroll]=npic];
endroll[nroll]=npic;
If[!NumberQ[startyear[nyear]],startyear[nyear]=npic];
endyear[nyear]=npic
,{nf,mf}]
,{nroll,mroll}],{nyear,firstyear,myear}];
mpic=npic;
Clear[npic];
dotact1[npic_]:=
If[rolls[npic]!=rolls[npic-1],right2,
If[rolls[npic]!=rolls[npic+1],left2,
dot2
]
];
dotpas[0]=dotact[0]=dotpas[mpic+1]=dotact[mpic+1]=blanksrc;
(* Cycle through all pic. *)
Do[
year=years[npic];roll=rolls[npic];fn=numbers[npic];
nroll=ToExpression[roll];
nyear=ToExpression[year];
{roll0,npic0}={roll,npic};
(***********)
(* Reading the title of the roll and the title of the slide from the file captions.txt *)
fn1=StringReplace[fn,"000"->"-1"];
nfn=ToExpression[fn1];
filecapt=ToFileName[{dir0,year,roll},"captions.txt"];
data=ReadList[filecapt,Record,RecordSeparators -> {"#"}];
mrec=Length[data];
rolltitle=gcaption=caption="";
Do[rec=data[[nrec]];
pos=StringPosition[rec,{" ","\n",":"}];
n=pos[[1,1]];
head=StringTake[rec,n-1];
sep=StringTake[rec,{n,n}];
content=StringDrop[rec,n]//flankblank;
(*Print[head];Print[sep];Print[content];*)
If[head=="ROLL",
If[rolltitle!="",Print["WARNING: several titles for the same roll encountered in the caption file "<>capt]];
rolltitle=content;Goto[9]];
If[sep=="\n"||sep==" ",
If[head==fn,
If[caption!="",Print["WARNING: several captions for the same slide "<>fn<>" encountered in the caption file "<>capt]];
caption=content;Goto[9]]];
If[sep==":",
head1=StringReplace[head,{"000"->"-1","-"->"+"}];
range=Flatten[Release[ToExpression["{"<>head1<>"}",InputForm,Hold]/.Plus->Range]];
If[MemberQ[range,nfn],
gcaption=gcaption<>"
\n"<>content;Goto[9]]];
Label[9],{nrec,mrec}];
gcaption=flankblank[gcaption];
gcapt=StringReplace[gcaption,{" "->"","""->""}];
While[StringMatchQ[gcapt,"*<*>*"],
n1=StringPosition[gcapt,"<"][[1,1]];
n2=StringPosition[gcapt,">"][[1,1]];
gcapt=If[n1
"}],caption]//flankblank;
cap=StringReplace[caplink,{"\n"->" "}];
capt=If[caption=="",gcaption,caption]//flankblank;
rolltit=If[caption=="","
"<>rolltitle,""];
(* Adding links where possible *)
Do[
pos=StringPosition[caplink,incl[nrep],Overlaps->False,IgnoreCase->True];
mpos=Length[pos];
If[mpos==0,Continue[]];
mcap=StringLength[caplink];
nref=ref[nrep];
Do[
{pos1,pos2}=pos[[npos]];
If[pos1!=1 && !StringMatchQ[ToUpperCase[StringTake[caplink,{pos1-1}]],"@"],Continue[]];
If[pos2!=mcap && !StringMatchQ[ToUpperCase[StringTake[caplink,{pos2+1}]],"@"],Continue[]];
caplink=StringInsert[caplink,"",pos2+1];
caplink=StringInsert[caplink,"nref<>"\">",pos1];
,{npos,mpos,1,-1}]
,{nrep,mrep}];
(* For testing
Print[" ------"];
Print[rolltitle];
Print[" ------"];
Print[caption];
Print[" ------"];
Print[gcaption];
Print[" ------"];
Print[gcapt];
*)
(* End reading from capt *)
(* *)
(* Defining mindot,maxdot,mindot0,maxdot0 ... *)
mindot=Max[-mdots,-npic+1];
maxdot=Min[mdots,mpic-npic];
mindot0=Max[-mdots,startroll[nroll]-npic];
maxdot0=Min[mdots,endroll[nroll]-npic];
mindot00=Max[-mdots,startyear[nyear]-npic];
maxdot00=Min[mdots,endyear[nyear]-npic];
minroll=rolls[npic+mindot]//ToExpression;
maxroll=rolls[npic+maxdot]//ToExpression;
minyear=years[npic+mindot]//ToExpression;
maxyear=years[npic+maxdot]//ToExpression;
(**)
(********************** Start writing HTML document ************************)
(* *)
of=OpenWrite[ToFileName[{dir0,"compress",year,roll},fn<>".htm"],PageWidth->Infinity,FormatType->OutputForm];
""//p;
""//p;
""//p;
"
"//p;
(* References *)
""//p;
(* Slide *)
bc=Floor[FileByteCount[ToFileName[{dir0,year,roll,"jpeg"},fn<>".jpg"]]/1000];
" "//p;
" "//p;
(* T1 T2 *) ""//p;
" "//p;
" "//p;
(* *)
(*
(* Ruler of images *)
""//p;
(**)
*)
""//p;
blank="";
(* Prev. image *)
prev=If[npic==1,blank,
If[rollpr==roll,"
Previous"//p;
(* Next image *)
next=If[npic==mpic,blank,
If[rollne==roll,"
Next
Next roll of film "//p;
(* /T2 /T1 *) ""//p;
"year<>"/"<>roll<>"/browser.htm\" ONMOUSEOVER=\"window.status='"<>rolltitle<>"' ; return true\" ONMOUSEOUT=\"window.status='' ; return true\">Overview the current roll of film"//p;
" "//p;
(* No-script notice *)
""//p;
(* Title *)
""//p;
" "//p;
(*" year<>"/"<>roll<>"/browser.htm\">This roll of film:"//p;
" "//p;*)
"
"<>rolltitle<>"year<>"/list.htm\">Pictures-"<>year<>" "//p;
"Picture Archives "//p;
"Selected Pictures "//p;
"Random Slide Show "//p;
"Directory of files "//p;
"A. Sergeev "//p;
"