program staticgen ! Spheniscus Static Generator ! Version : 6, 12-09-2013 ! BenoƮt Leveugle ! to compile : gfortran -ffree-line-length-400 implicit none integer :: nbfiles,error,n,g,m,last1,last2,report,compt,gg character(len=50), dimension(:), allocatable :: Arbo, Names integer, dimension(:,:), allocatable :: Levels integer, dimension(:), allocatable :: active character(len=50), dimension(1:3) :: pos integer, dimension(:,:), allocatable :: levelandparity character(len=200), dimension(:), allocatable :: fArbo,fRevArbo,fFileArbo integer(4) :: today(3) character(len=4) :: year character(len=2) :: month, day character(len=200) :: sbuf logical, dimension(:), allocatable :: fHaveSons character(len=400) :: buffcharlen character, dimension(1:400) :: buffchar ! Get the date, for sitemap xml call idate(today) ! today(1)=day, (2)=month, (3)=year write(year,'(I4.4)') today(3) write(month,'(I2.2)') today(2) write(day,'(I2.2)') today(1) ! trunk contains the website hierarchy, pre-read to define number of files, and then read. open(10,file='Trunk') !############## Pre-read nbfiles = 0 do n=1,300 read(10,*,iostat=error) if(error /=0) exit nbfiles=nbfiles+1 end do nbfiles=nbfiles print *,'nbfiles',nbfiles close(10) !############## Reading Arbo allocate(Arbo(1:nbfiles),fArbo(1:nbfiles),fRevArbo(1:nbfiles),fFileArbo(1:nbfiles),& &Names(1:nbfiles),Levels(1:3,1:nbfiles),active(1:nbfiles), & & levelandparity(1:4,1:nbfiles), fHaveSons(1:nbfiles)) open(10,file='Trunk') do n=1,nbfiles read(10,*) Levels(1:3,n),Arbo(n),Names(n) end do close(10) ! At this stage, Levels contain the level of each file. If the file is at level 1, then its second and third value are 0, same for level 2, the third value is 0. ! Arbo contains the name with file system compliance (no espaces, etc). Names contains the real name displayed on the web page. !############## Organise Arbo ! Level and parity : 1:3 the hierarchy (father and sons), 4 the current level ! Aim : define for each file it's father(s) in the hierarchy, and set it's current level (1, 2 or 3) ! Special case for index.html because it has to be at root /, not in a folder named /index/ ! last1 keeps in memory the last level 1 file detected, so all next no level 1 files will have this father for level 1. ! last2 keeps in memory the last level 2 file, same. ! fArbo contains the directory where the file is. ! fFileArbo contains the direct link to the file ! fRevArbo contains the way to go root, in order to be relative to other files. ! fHaveSons : true if the file have sons (to generate submenus), false if not ! Organise parity last1 = 0 last2 = 0 do g=1,nbfiles if(g==1) then ! Special case for index.html levelandparity(4,g) = 1 levelandparity(1,g) = 1 levelandparity(2,g) = 0 levelandparity(3,g) = 0 fArbo(g) = './' fFileArbo(g) = trim(adjustl(Arbo(levelandparity(1,g))))//'.html' fRevArbo(g) = './' last1 = g else if( Levels(2,g) == 0 ) then ! Level 1 levelandparity(4,g) = 1 levelandparity(1,g) = g levelandparity(2,g) = 0 levelandparity(3,g) = 0 fArbo(g) = trim(adjustl(Arbo(levelandparity(1,g)))) fFileArbo(g) = trim(adjustl(Arbo(levelandparity(1,g))))//'/'//trim(adjustl(Arbo(levelandparity(1,g))))//'.html' fRevArbo(g) = '../' last1 = g elseif( Levels(3,g)==0 ) then ! Level 2 levelandparity(4,g) = 2 levelandparity(1,g) = last1 levelandparity(2,g) = g levelandparity(3,g) = 0 fArbo(g) = trim(adjustl(Arbo(levelandparity(1,g))))//'/'//trim(adjustl(Arbo(levelandparity(2,g)))) fFileArbo(g) = trim(adjustl(Arbo(levelandparity(1,g))))//'/'//trim(adjustl(Arbo(levelandparity(2,g))))//'/'//trim(adjustl(Arbo(levelandparity(2,g))))//'.html' fRevArbo(g) = '../../' last2 = g else ! Level 3 levelandparity(4,g) = 3 levelandparity(1,g) = last1 levelandparity(2,g) = last2 levelandparity(3,g) = g fArbo(g) = trim(adjustl(Arbo(levelandparity(1,g))))//'/'//trim(adjustl(Arbo(levelandparity(2,g))))//'/'//trim(adjustl(Arbo(levelandparity(3,g)))) fFileArbo(g) = trim(adjustl(Arbo(levelandparity(1,g))))//'/'//trim(adjustl(Arbo(levelandparity(2,g))))//'/'//trim(adjustl(Arbo(levelandparity(3,g))))//'/'//trim(adjustl(Arbo(levelandparity(3,g))))//'.html' fRevArbo(g) = '../../../' end if end if print *,g,levelandparity(:,g),trim(adjustl(Arbo(g))),' ',trim(adjustl(Names(g))) print *,trim(adjustl(fArbo(g))),' ',trim(adjustl(fFileArbo(g))),' ',trim(adjustl(fRevArbo(g))) end do ! Detect if files have sons do g=1,nbfiles fHaveSons(g) = .false. ! Detect Level 1 sons presence if(levelandparity(4,g) == 1) then do n=1,nbfiles if(levelandparity(2,n) /= 0 .AND. levelandparity(1,n) == levelandparity(1,g)) then fHaveSons(g) = .true. exit end if end do end if ! Detect Level 2 sons presence if(levelandparity(4,g) == 2) then do n=1,nbfiles if(levelandparity(3,n) /= 0 .AND. levelandparity(2,n) == levelandparity(2,g)) then fHaveSons(g) = .true. exit end if end do end if ! Of course, Level 3 have no sons print *,g,"has sons ?",fHaveSons(g) end do do g=1,nbfiles ! -> Loop on files ! Destroy previous files open(11,file=trim(adjustl(fFileArbo(g)))) write(11,*) close(11) open(11,file=trim(adjustl(fFileArbo(g)))) write(11,*) '' write(11,*) '' write(11,*) '' write(11,*) ' ' write(11,*) ' ' write(11,*) ' ' write(11,*) ' '//trim(adjustl(Names(g)))//' ' write(11,*) ' ' write(11,*) ' ' write(11,*) ' ' write(11,*) ' ' write(11,*) ' ' write(11,*) '' write(11,*) '' write(11,*) write(11,*) '
' write(11,*) write(11,*) '' write(11,*) ! Level 1 menu, for all files if(levelandparity(4,g) == 1 .AND. (fHaveSons(g) .EQV. .false.)) then ! no decoration because no Level 2 and 3 menus write(11,*) '