aboutsummaryrefslogtreecommitdiff
path: root/captain/template.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-03-29 16:38:00 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-03-29 16:38:00 -0400
commitbe976a38f1d95258f19d94f4cf5dc4c677041ed9 (patch)
treedf8557c3d44c6dc41a29f34646d5d231d6075270 /captain/template.f90
parent7614a6244d080b8c0f82da8c34ccf7a4a88fe72a (diff)
downloadlevitating-be976a38f1d95258f19d94f4cf5dc4c677041ed9.tar.gz
levitating-be976a38f1d95258f19d94f4cf5dc4c677041ed9.zip
Changed how temp files work on UNIX-y stuff. Fixed templates, which were quite broken.
Diffstat (limited to 'captain/template.f90')
-rw-r--r--captain/template.f9091
1 files changed, 51 insertions, 40 deletions
diff --git a/captain/template.f90 b/captain/template.f90
index 6b5429d..f8a6625 100644
--- a/captain/template.f90
+++ b/captain/template.f90
@@ -31,6 +31,7 @@ implicit none
character(len=:), pointer::base_filename
type(variable), dimension(:), pointer::variables
+ character(len=:), pointer::output_filename
contains
@@ -39,11 +40,10 @@ implicit none
procedure :: assign_integer => template_assign_integer
procedure :: assign_string => template_assign_string
procedure :: assign_logical => template_assign_logical
- procedure :: render_unit => template_render_unit
- procedure :: render_filename => template_render_filename
+ procedure :: render => template_render
procedure :: evaluate => template_evaluate
+ procedure :: generate_output_filename => template_generate_output_filename
- generic :: render => render_unit, render_filename
generic :: assign => assign_integer, assign_string, assign_logical
end type
@@ -84,15 +84,12 @@ contains
end subroutine variable_shallow_copy
subroutine variable_set_name(self, name)
+ use logging
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 = " "
@@ -140,15 +137,16 @@ contains
end subroutine variable_assign_integer
subroutine variable_assign_string(self, name, str)
+ use logging
implicit none
class(variable)::self
character(*), intent(in)::name, str
- call self%set_name(name)
+ call self%set_name(name)
self%vtype = VTYPE_STRING
call self%set_string_value(str)
-
+
end subroutine variable_assign_string
subroutine variable_assign_logical(self, name, lg)
@@ -182,6 +180,8 @@ contains
allocate(self%variables(32))
self%variables%vtype = VTYPE_NONE
+ self%output_filename => null()
+
end subroutine template_init
subroutine template_destroy(self)
@@ -196,6 +196,17 @@ contains
end subroutine template_destroy
+ subroutine template_generate_output_filename(self)
+ use utilities, only: generate_temporary_filename
+ use logging
+ implicit none
+
+ class(template)::self
+
+ self%output_filename => generate_temporary_filename()
+
+ end subroutine template_generate_output_filename
+
function template_available_variable_index(self) result(i)
implicit none
@@ -212,6 +223,9 @@ contains
! Need to expand
if(i > size(self%variables)) then
allocate(tmp(size(self%variables)+32))
+
+ tmp%vtype = VTYPE_NONE
+
do j=1, i-1
call tmp(j)%shallow_copy(self%variables(j))
end do
@@ -239,6 +253,7 @@ contains
end subroutine template_assign_integer
subroutine template_assign_string(self, name, value)
+ use logging
implicit none
class(template)::self
@@ -246,6 +261,7 @@ contains
integer::i
i = template_available_variable_index(self)
+
call self%variables(i)%assign(name, value)
end subroutine template_assign_string
@@ -259,30 +275,17 @@ contains
integer::i
i = template_available_variable_index(self)
+
call self%variables(i)%assign(name, value)
end subroutine template_assign_logical
-
- 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)
+ subroutine template_render(self, filename)
+ use logging
implicit none
class(template)::self
- integer, intent(in)::unum
+ character(*), intent(in), optional::filename
character::this_char, last_char
character(len=2)::running_pair, closing_pair
@@ -293,14 +296,22 @@ contains
logical::writing_now
- integer::input, istat, i
-
- open(newunit=input, file=self%base_filename, status="old", form="formatted", action="read")
+ integer::input, istat, i, unum
+
+ if(present(filename)) then
+ allocate(character(len=len_trim(filename)) :: self%output_filename)
+ self%output_filename = trim(filename)
+ else
+ call self%generate_output_filename()
+ end if
+
+ open(newunit=unum, file=trim(self%output_filename), status="new", form="formatted", access="stream", action="write")
+ open(newunit=input, file=trim(self%base_filename), status="old", form="unformatted", access="stream")
writing_now = .true.
last_char = ' '
- read(input, '(A1)', iostat=istat) this_char
+ read(input, iostat=istat) this_char
do while(istat == 0)
running_pair = last_char//this_char
@@ -314,17 +325,17 @@ contains
brace_internals = ' '
- read(input, '(A1)', iostat=istat) this_char
+ read(input, iostat=istat) this_char
i = 1
- do while(istat == 0 .and. .not. (running_pair /= closing_pair))
+ do while(istat == 0 .and. (running_pair /= closing_pair))
brace_internals(i:i) = this_char
i = i + 1
last_char = this_char
- read(input, '(A1)', iostat=istat) this_char
+ read(input, iostat=istat) this_char
running_pair = last_char//this_char
end do
- brace_internals(i:i) = ' ' ! Remove trailing bracket
+ brace_internals(i-1:i-1) = ' ' ! Remove trailing bracket
brace_internals = adjustl(brace_internals)
! Simple variable
@@ -333,7 +344,7 @@ contains
if(associated(replacement)) then
do i=1, len_trim(replacement)
- write(unum, '(A1)', advance='no') replacement(i:i)
+ write(unum, '(A1)', advance='no') replacement(i:i)
end do
replacement => null() ! do not free - internal strings
end if
@@ -348,18 +359,18 @@ contains
write(unum, '(A1)', advance='no') last_char
write(unum, '(A1)', advance='no') this_char
- else
+ else if(this_char /= '{') then
write(unum, '(A1)', advance='no') this_char
-
end if
last_char = this_char
- read(input, '(A1)', iostat=istat) this_char
+ read(input, iostat=istat) this_char
end do
+ close(unum)
close(input)
- end subroutine template_render_unit
+ end subroutine template_render
function template_evaluate(self, txt) result(res)
implicit none