aboutsummaryrefslogtreecommitdiff
path: root/pptxml.f90
diff options
context:
space:
mode:
Diffstat (limited to 'pptxml.f90')
-rw-r--r--pptxml.f9054
1 files changed, 45 insertions, 9 deletions
diff --git a/pptxml.f90 b/pptxml.f90
index c785bb8..513703e 100644
--- a/pptxml.f90
+++ b/pptxml.f90
@@ -313,12 +313,14 @@ contains
end subroutine parse_slide_sp
- subroutine slide_load_filename(self, filename)
+ subroutine slide_load_filename(self, filename, title)
use FoX_dom
implicit none
class(slide), intent(out)::self
character(len=*), intent(in)::filename
+ character(len=*), intent(in), optional::title
+
character(len=:), pointer::filename_no_backslashes
! For parsing the title out
@@ -369,11 +371,16 @@ contains
return
end if
- self%title => find_slide_title(self%slide_dom)
- if(.not. associated(self%title) .and. self%number > 0) then
- allocate(character(len=16)::self%title)
- write(self%title, '(I8)') self%number
- self%title = "Slide "//trim(adjustl(self%title))
+ if(present(title)) then
+ allocate(character(len=len_trim(title)) :: self%title)
+ self%title = title
+ else
+ self%title => find_slide_title(self%slide_dom)
+ if(.not. associated(self%title) .and. self%number > 0) then
+ allocate(character(len=16)::self%title)
+ write(self%title, '(I8)') self%number
+ self%title = "Slide "//trim(adjustl(self%title))
+ end if
end if
call parse_slide_sp(self)
@@ -520,10 +527,39 @@ contains
class(text_element), intent(inout)::self
type(Node), pointer::n
- type(NodeList), pointer::rows
+ type(NodeList), pointer::rows, paras
+ character(len=:), pointer::one_para
+ integer::text_length, i
+
+ text_length = 0
+ paras => getElementsByTagNameNS(n, drawing_schema, "p")
+ do i = 1, getLength(paras)
+ rows => getElementsByTagNameNS(item(paras, i-1), drawing_schema, "r")
+ one_para => concatenated_text_in_rows(rows)
+ if(associated(one_para)) then
+ text_length = text_length + len_trim(one_para)
+ if(i /= getLength(paras)) then
+ text_length = text_length + len(new_line(' '))
+ end if
+ end if
+ end do
- rows => getElementsByTagNameNS(n, drawing_schema, "r")
- self%text => concatenated_text_in_rows(rows)
+ allocate(character(len=text_length) :: self%text)
+
+ text_length = 1
+ paras => getElementsByTagNameNS(n, drawing_schema, "p")
+ do i = 1, getLength(paras)
+ rows => getElementsByTagNameNS(item(paras, i-1), drawing_schema, "r")
+ one_para => concatenated_text_in_rows(rows)
+ if(associated(one_para)) then
+ self%text(text_length:len(self%text)) = one_para
+ text_length = text_length + len_trim(one_para)
+ if(i /= getLength(paras)) then
+ self%text(text_length:len(self%text)) = new_line(' ')
+ text_length = text_length + len(new_line(' '))
+ end if
+ end if
+ end do
end subroutine text_element_from_node