aboutsummaryrefslogtreecommitdiff
path: root/pptxzip.f90
diff options
context:
space:
mode:
Diffstat (limited to 'pptxzip.f90')
-rw-r--r--pptxzip.f9092
1 files changed, 85 insertions, 7 deletions
diff --git a/pptxzip.f90 b/pptxzip.f90
index d526125..1a11b1e 100644
--- a/pptxzip.f90
+++ b/pptxzip.f90
@@ -34,6 +34,9 @@ implicit none
character(len=2048), dimension(:), pointer::note_paths
type(slide), dimension(:), pointer::slides
+
+ type(slide), dimension(:), pointer::notes
+ integer, dimension(:), pointer::slide_note_indices
contains
@@ -43,11 +46,27 @@ implicit none
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
@@ -63,6 +82,28 @@ contains
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
@@ -85,7 +126,7 @@ contains
logical::res
class(pptxtracted), intent(out)::self
character(len=*), intent(in)::filename
- integer::i, slidecount
+ integer::i, slidecount, j
character(len=2048)::slidedir, slidecheck, notesdir
character(len=4)::numtext
logical::existence
@@ -121,6 +162,10 @@ contains
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')
@@ -132,11 +177,15 @@ contains
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
@@ -162,39 +211,68 @@ contains
implicit none
class(pptxtracted), intent(inout)::self
- integer::i
+ 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) result(t)
+ 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()
- text_length = text_length + self%slides(i)%text_length()
+ 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 => self%slides(i)%to_text()
- t(text_length:len(t)) = trim(tmp)
- text_length = text_length + len_trim(tmp)
+ 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