@@ -5,14 +5,16 @@ module foodie_test_integrand_lcce
55! < Define [[integrand_lcce]], the linear constant coefficients equation test field that is a concrete extension of the
66! < abstract integrand type.
77
8+ use flap, only : command_line_interface
89use foodie, only : integrand_object
9- use penf, only : I_P, R_P
10+ use foodie_test_integrand_tester_object, only : integrand_tester_object
11+ use penf, only : FR_P, R_P, I_P, str
1012
1113implicit none
1214private
1315public :: integrand_lcce
1416
15- type, extends(integrand_object ) :: integrand_lcce
17+ type, extends(integrand_tester_object ) :: integrand_lcce
1618 ! < The linear constant coefficient equation field.
1719 ! <
1820 ! < It is a FOODIE integrand class concrete extension.
@@ -47,10 +49,16 @@ module foodie_test_integrand_lcce
4749 real (R_P) :: U0= 0._R_P ! < Integrand initial state.
4850 contains
4951 ! auxiliary methods
50- procedure , pass(self), public :: exact_solution ! < Return exact solution.
51- procedure , pass(self), public :: initialize ! < Initialize integrand.
5252 procedure , pass(self), public :: output ! < Extract integrand state field.
53- ! public deferred methods
53+ ! integrand_tester_object deferred methods
54+ procedure , pass(self), public :: description ! < Return an informative description of the test.
55+ procedure , pass(self), public :: error ! < Return error.
56+ procedure , pass(self), public :: exact_solution ! < Return exact solution.
57+ procedure , pass(self), public :: export_tecplot ! < Export integrand to Tecplot file.
58+ procedure , pass(self), public :: initialize ! < Initialize field.
59+ procedure , pass(self), public :: parse_cli ! < Initialize from command line interface.
60+ procedure , nopass, public :: set_cli ! < Set command line interface.
61+ ! integrand_object deferred methods
5462 procedure , pass(self), public :: integrand_dimension ! < Return integrand dimension.
5563 procedure , pass(self), public :: t = > dU_dt ! < Time derivative, residuals.
5664 ! operators
@@ -82,39 +90,113 @@ module foodie_test_integrand_lcce
8290
8391contains
8492 ! auxiliary methods
85- pure function exact_solution (self , t , t0 ) result(exact)
86- ! < Return exact solution.
87- class(integrand_lcce), intent (in ) :: self ! < Integrand.
88- real (R_P), intent (in ) :: t ! < Time.
89- real (R_P), intent (in ), optional :: t0 ! < Initial time.
90- real (R_P) :: exact ! < Exact solution.
91- real (R_P) :: t0_ ! < Initial time, local variable.
93+ pure function output (self ) result(state)
94+ ! < Extract integrand state field.
95+ class(integrand_lcce), intent (in ) :: self ! < Integrand.
96+ real (R_P) :: state ! < State.
9297
98+ state = self% U
99+ end function output
100+
101+ ! integrand_tester_object deferred methods
102+ pure function description (self , prefix ) result(desc)
103+ ! < Return informative integrator description.
104+ class(integrand_lcce), intent (in ) :: self ! < Integrand.
105+ character (* ), intent (in ), optional :: prefix ! < Prefixing string.
106+ character (len= :), allocatable :: desc ! < Description.
107+ character (len= :), allocatable :: prefix_ ! < Prefixing string, local variable.
108+
109+ prefix_ = ' ' ; if (present (prefix)) prefix_ = prefix
110+ desc = prefix// ' linear_constant_coefficients_eq'
111+ end function description
112+
113+ pure function error (self , t , t0 , U0 )
114+ ! < Return error.
115+ class(integrand_lcce), intent (in ) :: self ! < Integrand.
116+ real (R_P), intent (in ) :: t ! < Time.
117+ real (R_P), intent (in ), optional :: t0 ! < Initial time.
118+ class(integrand_object), intent (in ), optional :: U0 ! < Initial conditions.
119+ real (R_P), allocatable :: error(:) ! < Error.
120+
121+ allocate (error(1 :1 ))
122+ error = abs ([self% U] - self% exact_solution(t= t, t0= t0))
123+ end function error
124+
125+ pure function exact_solution (self , t , t0 , U0 ) result(exact)
126+ ! < Return exact solution.
127+ class(integrand_lcce), intent (in ) :: self ! < Integrand.
128+ real (R_P), intent (in ) :: t ! < Time.
129+ real (R_P), intent (in ), optional :: t0 ! < Initial time.
130+ class(integrand_object), intent (in ), optional :: U0 ! < Initial conditions.
131+ real (R_P), allocatable :: exact(:) ! < Exact solution.
132+ real (R_P) :: t0_ ! < Initial time, local variable.
133+
134+ allocate (exact(1 :1 ))
93135 t0_ = 0._R_P ; if (present (t0)) t0_ = t0
94- exact = (self% U0 + self% b / self% a) * exp (self% a * (t - t0_)) - self% b / self% a
136+ exact( 1 ) = (self% U0 + self% b / self% a) * exp (self% a * (t - t0_)) - self% b / self% a
95137 end function exact_solution
96138
97- pure subroutine initialize (self , a , b , U0 )
139+ subroutine export_tecplot (self , file_name , t , scheme , close_file )
140+ ! < Export integrand to Tecplot file.
141+ class(integrand_lcce), intent (in ) :: self ! < Advection field.
142+ character (* ), intent (in ), optional :: file_name ! < File name.
143+ real (R_P), intent (in ), optional :: t ! < Time.
144+ character (* ), intent (in ), optional :: scheme ! < Scheme used to integrate integrand.
145+ logical , intent (in ), optional :: close_file ! < Flag for closing file.
146+ logical , save :: is_open= .false. ! < Flag for checking if file is open.
147+ integer (I_P), save :: file_unit ! < File unit.
148+
149+ if (present (close_file)) then
150+ if (close_file .and. is_open) then
151+ close (unit= file_unit)
152+ is_open = .false.
153+ endif
154+ else
155+ if (present (file_name)) then
156+ if (is_open) close (unit= file_unit)
157+ open (newunit= file_unit, file= trim (adjustl (file_name)))
158+ is_open = .true.
159+ write (unit= file_unit, fmt= ' (A)' ) ' VARIABLES="t" "x"'
160+ endif
161+ if (present (t) .and. present (scheme) .and. is_open) then
162+ write (unit= file_unit, fmt= ' (A)' ) ' ZONE T="' // trim (adjustl (scheme))// ' "'
163+ write (unit= file_unit, fmt= ' (2(' // FR_P// ' ,1X))' ) t, self% U
164+ elseif (present (t) .and. is_open) then
165+ write (unit= file_unit, fmt= ' (2(' // FR_P// ' ,1X))' ) t, self% U
166+ endif
167+ endif
168+ end subroutine export_tecplot
169+
170+ pure subroutine initialize (self , Dt )
98171 ! < Initialize integrand.
172+ ! <
173+ ! < Intentionally empty, all is done in `parse_cli` method.
99174 class(integrand_lcce), intent (inout ) :: self ! < Integrand.
100- real (R_P), intent (in ) :: a, b ! < Equation coefficients.
101- real (R_P), intent (in ) :: U0 ! < Initial state of the integrand.
102-
103- self% a = a
104- self% b = b
105- self% U = U0
106- self% U0 = U0
175+ real (R_P), intent (in ) :: Dt ! < Time step.
107176 end subroutine initialize
108177
109- pure function output (self ) result(state )
110- ! < Extract integrand state field .
111- class(integrand_lcce), intent (in ) :: self ! < Integrand .
112- real (R_P) :: state ! < State .
178+ subroutine parse_cli (self , cli )
179+ ! < Initialize from command line interface .
180+ class(integrand_lcce), intent (inout ) :: self ! < Advection field .
181+ type (command_line_interface), intent ( inout ) :: cli ! < Command line interface handler .
113182
114- state = self% U
115- end function output
183+ call cli% get(group= ' lcce' , switch= ' -a' , val= self% a, error= cli% error) ; if (cli% error/= 0 ) stop
184+ call cli% get(group= ' lcce' , switch= ' -b' , val= self% b, error= cli% error) ; if (cli% error/= 0 ) stop
185+ call cli% get(group= ' lcce' , switch= ' -U0' , val= self% U0, error= cli% error) ; if (cli% error/= 0 ) stop
186+ self% U = self% U0
187+ end subroutine parse_cli
188+
189+ subroutine set_cli (cli )
190+ ! < Set command line interface.
191+ type (command_line_interface), intent (inout ) :: cli ! < Command line interface handler.
192+
193+ call cli% add_group(description= ' linear constant coefficient equation test settings' , group= ' lcce' )
194+ call cli% add(group= ' lcce' , switch= ' -a' , help= ' "a" coeff of "a * x + b" equation' , required= .false. , def= ' -1.0' , act= ' store' )
195+ call cli% add(group= ' lcce' , switch= ' -b' , help= ' "b" coeff of "a * x + b" equation' , required= .false. , def= ' 0.0' , act= ' store' )
196+ call cli% add(group= ' lcce' , switch= ' -U0' , help= ' initial state' , required= .false. , def= ' 1.0' , act= ' store' )
197+ end subroutine set_cli
116198
117- ! deferred methods
199+ ! integrand_object deferred methods
118200 pure function integrand_dimension (self )
119201 ! < return integrand dimension.
120202 class(integrand_lcce), intent (in ) :: self ! < integrand.
0 commit comments