aboutsummaryrefslogtreecommitdiff
path: root/captain/template.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-03-26 11:19:59 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-03-26 11:19:59 -0400
commit13f8f7e0e5b2361a5d3aa3f3a21519b03cd4c9c2 (patch)
tree62914777fe9fef2ade01be0361d65900bf73aacf /captain/template.f90
parent2a79043e4b33118437b3ade35a792b9e0d1323be (diff)
downloadlevitating-13f8f7e0e5b2361a5d3aa3f3a21519b03cd4c9c2.tar.gz
levitating-13f8f7e0e5b2361a5d3aa3f3a21519b03cd4c9c2.zip
Started work on a template engine complete with variables. Added a few database routines and some hopeful, untested changes to the sql creation script.
Diffstat (limited to 'captain/template.f90')
-rw-r--r--captain/template.f90262
1 files changed, 262 insertions, 0 deletions
diff --git a/captain/template.f90 b/captain/template.f90
new file mode 100644
index 0000000..3e1f2bc
--- /dev/null
+++ b/captain/template.f90
@@ -0,0 +1,262 @@
+module page_template
+implicit none
+
+ integer, parameter::VTYPE_NONE = 0, &
+ VTYPE_STRING = 1, &
+ VTYPE_INTEGER = 2
+
+ type :: variable
+
+ character(len=:), pointer::vname
+
+ integer::vtype
+ character(len=:), pointer::vstr
+ integer::vint
+
+ contains
+
+ procedure :: destroy => variable_destroy
+ procedure :: shallow_copy => variable_shallow_copy
+ procedure :: set_name => variable_set_name
+ procedure :: set_string_value => variable_set_string_value
+ procedure :: assign_integer => variable_assign_integer
+ procedure :: assign_string => variable_assign_string
+
+ generic :: assign => assign_integer, assign_string
+ end type
+
+ type :: template
+
+ character(len=:), pointer::base_filename
+ type(variable), dimension(:), pointer::variables
+
+ contains
+
+ procedure :: init => template_init
+ procedure :: destroy => template_destroy
+ procedure :: assign_integer => template_assign_integer
+ procedure :: assign_string => template_assign_string
+ procedure :: render_unit => template_render_unit
+ procedure :: render_filename => template_render_filename
+
+ generic :: render => render_unit, render_filename
+ generic :: assign => assign_integer, assign_string
+ end type
+
+contains
+
+ elemental subroutine variable_destroy(self)
+ implicit none
+
+ class(variable), intent(inout)::self
+
+ if(associated(self%vname)) then
+ deallocate(self%vname)
+ end if
+
+ if(associated(self%vstr)) then
+ deallocate(self%vstr)
+ end if
+
+ end subroutine variable_destroy
+
+ subroutine variable_shallow_copy(self, v)
+ implicit none
+
+ class(variable), intent(inout)::self
+ class(variable), intent(in)::v
+
+ if(associated(v%vname)) then
+ self%vname => v%vname
+ end if
+
+ if(associated(v%vstr)) then
+ self%vstr => v%vstr
+ end if
+
+ self%vtype = v%vtype
+ self%vint = v%vint
+
+ end subroutine variable_shallow_copy
+
+ subroutine variable_set_name(self, name)
+ implicit none
+
+ class(variable)::self
+ character(*), intent(in)::name
+
+ if(associated(self%vname)) then
+ deallocate(self%vname)
+ end if
+
+ allocate(character(len=max(len_trim(name), 1)) :: self%vname)
+ if(len_trim(name) == 0) then
+ self%vname = " "
+ else
+ self%vname = trim(name)
+ end if
+
+ end subroutine variable_set_name
+
+ subroutine variable_set_string_value(self, v)
+ implicit none
+
+ class(variable)::self
+ character(*), intent(in)::v
+
+ if(associated(self%vstr)) then
+ deallocate(self%vstr)
+ end if
+
+ allocate(character(len=max(len_trim(v), 1)) :: self%vstr)
+ if(len_trim(v) == 0) then
+ self%vstr = " "
+ else
+ self%vstr = trim(v)
+ end if
+
+ end subroutine variable_set_string_value
+
+ subroutine variable_assign_integer(self, name, i)
+ implicit none
+
+ class(variable)::self
+ character(*), intent(in)::name
+ integer, intent(in)::i
+ character(16)::int_string
+
+ call self%set_name(name)
+ self%vint = i
+ self%vtype = VTYPE_INTEGER
+
+ write(int_string, *) i
+
+ call self%set_string_value(trim(adjustl(int_string)))
+
+ end subroutine variable_assign_integer
+
+ subroutine variable_assign_string(self, name, str)
+ implicit none
+
+ class(variable)::self
+ character(*), intent(in)::name, str
+
+ call self%set_name(name)
+ self%vtype = VTYPE_STRING
+ call self%set_string_value(str)
+
+ end subroutine variable_assign_string
+
+ subroutine template_init(self, filename)
+ implicit none
+
+ class(template)::self
+ character(*), intent(in)::filename
+
+ allocate(character(len=len_trim(filename)) :: self%base_filename)
+ self%base_filename = filename
+
+ allocate(self%variables(32))
+ self%variables%vtype = VTYPE_NONE
+
+ end subroutine template_init
+
+ subroutine template_destroy(self)
+ implicit none
+
+ class(template)::self
+
+ deallocate(self%base_filename)
+
+ call self%variables%destroy()
+ deallocate(self%variables)
+
+ end subroutine template_destroy
+
+ function template_available_variable_index(self) result(i)
+ implicit none
+
+ class(template)::self
+ type(variable), dimension(:), pointer::tmp
+ integer::i, j
+
+ do i = 1, size(self%variables)
+ if(self%variables(i)%vtype == VTYPE_NONE) then
+ exit
+ end if
+ end do
+
+ ! Need to expand
+ if(i > size(self%variables)) then
+ allocate(tmp(size(self%variables)+32))
+ do j=1, i-1
+ call tmp(j)%shallow_copy(self%variables(j))
+ end do
+
+ ! We performed a shallow copy above, so don't destroy
+ ! the old variables
+ deallocate(self%variables)
+ self%variables => tmp
+ tmp => null()
+ end if
+
+ end function template_available_variable_index
+
+ subroutine template_assign_integer(self, name, value)
+ implicit none
+
+ class(template)::self
+ character(*), intent(in)::name
+ integer, intent(in)::value
+ integer::i
+
+ i = template_available_variable_index(self)
+ call self%variables(i)%assign(name, value)
+
+ end subroutine template_assign_integer
+
+ subroutine template_assign_string(self, name, value)
+ implicit none
+
+ class(template)::self
+ character(*), intent(in)::name, value
+ integer::i
+
+ i = template_available_variable_index(self)
+ call self%variables(i)%assign(name, value)
+
+ end subroutine template_assign_string
+
+ subroutine template_render_filename(self, filename)
+ implicit none
+
+ class(template)::self
+ character(*), intent(in)::filename
+ integer::unit_number
+
+ open(file=filename, newunit=unit_number, status="unknown", form="formatted", action="write")
+
+ call self%render_unit(unit_number)
+
+ close(unit_number)
+
+ end subroutine template_render_filename
+
+ subroutine template_render_unit(self, unum)
+ implicit none
+
+ class(template)::self
+ integer, intent(in)::unum
+
+ integer::input
+
+ open(newunit=input, file=self%base_filename, status="old", form="formatted", action="read")
+
+
+
+
+ close(input)
+
+ end subroutine template_render_unit
+
+end module page_template \ No newline at end of file