! Copyright (c) 2022 Approximatrix, LLC ! ! Permission is hereby granted, free of charge, to any person obtaining a copy ! of this software and associated documentation files (the "Software"), to deal ! in the Software without restriction, including without limitation the rights ! to use, copy, modify, merge, publish, distribute, sublicense, and/or sell ! copies of the Software, and to permit persons to whom the Software is ! furnished to do so, subject to the following conditions: ! ! The above copyright notice and this permission notice shall be included in ! all copies or substantial portions of the Software. ! ! The Software shall be used for Good, not Evil. ! ! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR ! IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, ! FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE ! AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER ! LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, ! OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE ! SOFTWARE. module fpoint_pptxzip use fpoint_pptxml implicit none private public::pptxtracted type :: pptxtracted character(len=2048)::directory character(len=2048), dimension(:), pointer::slide_paths character(len=2048), dimension(:), pointer::note_paths type(slide), dimension(:), pointer::slides type(slide), dimension(:), pointer::notes integer, dimension(:), pointer::slide_note_indices contains procedure :: open => pptx_open procedure :: close => pptx_close procedure :: parse => pptx_parse procedure :: to_text => pptx_to_text procedure :: slide_has_notes procedure :: slide_count procedure :: get_notes => slide_get_notes procedure :: has_notes => pptx_has_notes end type pptxtracted contains function pptx_has_notes(self) implicit none class(pptxtracted), intent(in)::self logical::pptx_has_notes if(.not. associated(self%slide_note_indices)) then pptx_has_notes = .false. else pptx_has_notes = (count(self%slide_note_indices > 0) > 0) end if end function pptx_has_notes function slide_has_notes(self, i) implicit none class(pptxtracted), intent(in)::self integer, intent(in)::i logical::slide_has_notes if(i > size(self%note_paths) .or. i < 1) then slide_has_notes = .false. else slide_has_notes = (len_trim(self%note_paths(i)) > 0) end if end function slide_has_notes function slide_get_notes(self, i, success) implicit none class(pptxtracted), intent(in)::self integer, intent(in)::i logical, intent(out), optional::success type(slide)::slide_get_notes integer::j if(self%slide_has_notes(i)) then j = self%slide_note_indices(i) slide_get_notes = self%notes(j) if(present(success)) then success = .true. end if else if(present(success)) then success = .false. end if end function slide_get_notes function slide_count(self) implicit none class(pptxtracted), intent(in)::self integer::slide_count if(associated(self%slide_paths)) then slide_count = size(self%slide_paths) else slide_count = 0 end if end function slide_count function pptx_open(self, filename) result(res) use fpoint_fsutil use m_unzip, only: unzip implicit none logical::res class(pptxtracted), intent(out)::self character(len=*), intent(in)::filename integer::i, slidecount, j character(len=2048)::slidedir, slidecheck, notesdir character(len=4)::numtext logical::existence call get_temporary_directory(self%directory) i = index(filename, pathsep, back=.true.) + 1 call append_to_path(self%directory, filename(i:len_trim(filename))//".extracted") call make_directory(trim(self%directory)) ! Extract the file into said directory res = unzip(filename, trim(self%directory)) ! Count slides slidedir = self%directory call append_to_path(slidedir, 'ppt') call append_to_path(slidedir, 'slides') do i = 1, 512 slidecheck = slidedir write(numtext, '(I4)') i call append_to_path(slidecheck, "slide"//trim(adjustl(numtext))//".xml") inquire(file=slidecheck, exist=existence) if(.not. existence) then exit end if end do slidecount = i - 1 allocate(self%slide_paths(slidecount)) self%slide_paths = slidedir do i = 1, slidecount write(numtext, '(I4)') i call append_to_path(self%slide_paths(i), "slide"//trim(adjustl(numtext))//".xml") end do ! Now check for notes allocate(self%slide_note_indices(slidecount)) self%slide_note_indices = -1 j = 1 notesdir = self%directory call append_to_path(notesdir, 'ppt') call append_to_path(notesdir, 'notesSlides') allocate(self%note_paths(slidecount)) self%note_paths = notesdir do i = 1, slidecount write(numtext, '(I4)') i call append_to_path(self%note_paths(i), "notesSlide"//trim(adjustl(numtext))//".xml") inquire(file=self%note_paths(i), exist=existence) if(.not. existence) then self%note_paths(i) = " " else self%slide_note_indices(i) = j j = j + 1 end if end do ! These should only be explicitly parsed self%slides => null() self%notes => null() end function pptx_open subroutine pptx_close(self) implicit none class(pptxtracted), intent(inout)::self ! Delete directory tree at self%directory deallocate(self%slide_paths) self%slide_paths => null() deallocate(self%note_paths) self%note_paths => null() self%directory = " " end subroutine pptx_close subroutine pptx_parse(self) use fpoint_pptxml implicit none class(pptxtracted), intent(inout)::self integer::i, j allocate(self%slides(self%slide_count())) allocate(self%notes(count(self%slide_note_indices > 0))) do i = 1, self%slide_count() call self%slides(i)%load(self%slide_paths(i)) if(self%slide_has_notes(i)) then j = self%slide_note_indices(i) call self%notes(j)%load(self%note_paths(i), title=self%slides(i)%title) end if end do end subroutine pptx_parse function pptx_to_text(self, notes_only) result(t) use fpoint_pptxml implicit none class(pptxtracted), intent(in)::self logical, intent(in), optional::notes_only integer::text_length character(len=:), pointer::t, tmp integer::i type(slide)::one_note logical::local_notes t => null() local_notes = .false. if(present(notes_only)) then local_notes = notes_only end if if(self%slide_count() > 0 .and. associated(self%slides)) then text_length = 0 do i = 1, self%slide_count() if(local_notes .and. self%slide_has_notes(i)) then one_note = self%get_notes(i) text_length = text_length + one_note%text_length() else if(.not. local_notes) then text_length = text_length + self%slides(i)%text_length() end if end do allocate(character(len=text_length) :: t) text_length = 1 do i = 1, self%slide_count() tmp => null() if(local_notes .and. self%slide_has_notes(i)) then one_note = self%get_notes(i) tmp => one_note%to_text() else if(.not. local_notes) then tmp => self%slides(i)%to_text() end if if(associated(tmp)) then t(text_length:len(t)) = trim(tmp) text_length = text_length + len_trim(tmp) deallocate(tmp) end if end do end if end function pptx_to_text end module fpoint_pptxzip