Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
Show all changes
30 commits
Select commit Hold shift + click to select a range
d15770f
Save work
mo-rickywong Dec 2, 2025
b91f952
Commit documentation changes before merging on the related code changes.
mo-rickywong Dec 2, 2025
b08fc7a
Update the branch to include the fortran source changes that the docu…
mo-rickywong Dec 3, 2025
bb6d987
Save changes to configuration documentation
mo-rickywong Dec 3, 2025
8dd023b
Save updates to branch
mo-rickywong Dec 5, 2025
3b3e13c
Update the copyright heading on some new files
mo-rickywong Dec 10, 2025
8483a5a
Merge branch 'main' into ConfigTypeAccess
mo-rickywong Dec 11, 2025
65afca1
Added self to contritbutors list file.
mo-rickywong Dec 11, 2025
6dd240d
Merge branch 'main' into ConfigTypeAccess
mo-rickywong Dec 11, 2025
e275eb1
Fix warnings on documnetation code blocks
mo-rickywong Dec 11, 2025
48297c2
Remove some whitespace
mo-rickywong Dec 11, 2025
9f1b3b3
Some tidy and add comment on multiple configurations
mo-rickywong Dec 12, 2025
2f9f624
Update documentation/source/how_it_works/build_system/configurator.rst
mo-rickywong Dec 17, 2025
92c6991
Update documentation/source/how_it_works/build_system/configurator.rst
mo-rickywong Dec 17, 2025
30aa7ee
Update infrastructure/build/tools/configurator/templates/config_type.…
mo-rickywong Dec 17, 2025
8f03526
Update infrastructure/build/tools/configurator/templates/config_type.…
mo-rickywong Dec 17, 2025
4db7e94
Update documentation/source/how_it_works/build_system/configurator.rst
mo-rickywong Dec 17, 2025
cbcbe47
Update to config_loader template to warn of untagged duplicate namelists
mo-rickywong Dec 18, 2025
430347a
Add changes in response to reviewer comments
mo-rickywong Dec 18, 2025
e706297
Merge remote-tracking branch 'origin/main' into ConfigTypeAccess
mo-rickywong Dec 18, 2025
3b82a0c
Empty Commit
mo-rickywong Dec 19, 2025
dbebd0b
Merge remote-tracking branch 'origin/main' into ConfigTypeAccess
mo-rickywong Dec 19, 2025
3d5215c
Fix documentation build
mo-rickywong Dec 19, 2025
f091ca6
Update code in response to reviewer comments
mo-rickywong Jan 8, 2026
b7f6d15
Merge branch 'main' into ConfigTypeAccess
mo-rickywong Jan 8, 2026
6d0b392
Merge branch 'main' into ConfigTypeAccess
mo-rickywong Jan 8, 2026
1c5cc07
Convert last few cases using interim access method
mo-rickywong Jan 8, 2026
867f357
Revert this file as it would require a linked ticket
mo-rickywong Jan 8, 2026
9ba4c1f
Revert this file as it will require a linked ticket
mo-rickywong Jan 8, 2026
c08ffaf
Merge branch 'main' into ConfigTypeAccess
MatthewHambley Jan 9, 2026
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
3 changes: 2 additions & 1 deletion CONTRIBUTORS.md
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,9 @@
| andrewcoughtrie | Andrew Coughtrie | Met Office | 2025.12.12 |
| james-bruten-mo | James Bruten | Met Office | 2025-12-09 |
| jennyhickson | Jenny Hickson | Met Office | 2025-12-10 |
| mo-marqh | Mark Hedley | Met Office | 2025-12-11 |
| mike-hobson | Mike Hobson | Met Office | 2025-12-17 |
| mo-marqh | Mark Hedley | Met Office | 2025-12-11 |
| mo-rickywong | Ricky Wong | Met Office | 2025-12-11 |
| MatthewHambley | Matthew Hambley | Met Office | 2025-12-15 |
| yaswant | Yaswant Pradhan | Met Office | 2025-12-16 |
| harry-shepherd | Harry Shepherd | Met Office | 2026-01-08 |
Expand Down
9 changes: 7 additions & 2 deletions applications/coupled/source/coupled.f90
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,7 @@ program coupled
call modeldb%values%initialise( 'values', 5 )

call modeldb%configuration%initialise( program_name, table_len=10 )
call modeldb%config%initialise( program_name )

write(log_scratch_space,'(A)') &
'Application built with '// trim(precision_real) // &
Expand All @@ -53,8 +54,12 @@ program coupled

call modeldb%values%add_key_value('cpl_name', cpl_component_name)
call init_comm( "coupled", modeldb )
call init_config( filename, coupled_required_namelists, &
modeldb%configuration )

call init_config( filename, &
coupled_required_namelists, &
configuration=modeldb%configuration, &
config=modeldb%config )

call init_logger( modeldb%mpi%get_comm(), &
program_name//"_"//cpl_component_name )
call init_collections()
Expand Down
26 changes: 8 additions & 18 deletions applications/coupled/source/driver/coupled_driver_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ module coupled_driver_mod
LOG_LEVEL_INFO
use mesh_mod, only : mesh_type
use mesh_collection_mod, only : mesh_collection
use namelist_mod, only : namelist_type

use sci_checksum_alg_mod, only : checksum_alg

implicit none
Expand Down Expand Up @@ -69,10 +69,6 @@ subroutine initialise( program_name, modeldb, calendar )
class(extrusion_type), allocatable :: extrusion
type(uniform_extrusion_type), allocatable :: extrusion_2d

type(namelist_type), pointer :: base_mesh_nml
type(namelist_type), pointer :: planet_nml
type(namelist_type), pointer :: extrusion_nml

character(str_def) :: prime_mesh_name

integer(i_def) :: stencil_depth
Expand All @@ -89,18 +85,12 @@ subroutine initialise( program_name, modeldb, calendar )


! Extract namelist variables
base_mesh_nml => modeldb%configuration%get_namelist('base_mesh')
planet_nml => modeldb%configuration%get_namelist('planet')
extrusion_nml => modeldb%configuration%get_namelist('extrusion')
call base_mesh_nml%get_value( 'prime_mesh_name', prime_mesh_name )
call base_mesh_nml%get_value( 'geometry', geometry )
call extrusion_nml%get_value( 'method', method )
call extrusion_nml%get_value( 'domain_height', domain_height )
call extrusion_nml%get_value( 'number_of_layers', number_of_layers )
call planet_nml%get_value( 'scaled_radius', scaled_radius )
base_mesh_nml => null()
planet_nml => null()
extrusion_nml => null()
prime_mesh_name = modeldb%config%base_mesh%prime_mesh_name()
geometry = modeldb%config%base_mesh%geometry()
method = modeldb%config%extrusion%method()
domain_height = modeldb%config%extrusion%domain_height()
number_of_layers = modeldb%config%extrusion%number_of_layers()
scaled_radius = modeldb%config%planet%scaled_radius()

! Initialise mesh
! Determine the required meshes
Expand All @@ -118,7 +108,7 @@ subroutine initialise( program_name, modeldb, calendar )
LOG_LEVEL_ERROR)
end select
allocate( extrusion, source=create_extrusion( method, &
domain_height, &
domain_height, &
domain_bottom, &
number_of_layers, &
PRIME_EXTRUSION ) )
Expand Down
21 changes: 13 additions & 8 deletions applications/coupled/source/driver/init_coupled_mod.X90
Original file line number Diff line number Diff line change
Expand Up @@ -21,8 +21,8 @@ module init_coupled_mod
use field_collection_mod, only : field_collection_type
use field_mod, only : field_type
use field_parent_mod, only : write_interface
use finite_element_config_mod, only : element_order_h, element_order_v
use function_space_collection_mod, only : function_space_collection
use function_space_mod, only : function_space_type
use fs_continuity_mod, only : W3
use log_mod, only : log_event, &
LOG_LEVEL_INFO, &
Expand All @@ -40,11 +40,12 @@ module init_coupled_mod
!> @param[in,out] chi The co-ordinate field
!> @param[in,out] panel_id 2d field giving the id for cubed sphere panels
!> @param[in,out] modeldb The structure that holds model state
subroutine init_coupled( mesh, chi, panel_id, modeldb)
subroutine init_coupled(mesh, chi, panel_id, modeldb)

implicit none

type(mesh_type), intent(in), pointer :: mesh

! Coordinate field
type( field_type ), intent(inout) :: chi(:)
type( field_type ), intent(inout) :: panel_id
Expand Down Expand Up @@ -74,19 +75,23 @@ module init_coupled_mod

procedure(write_interface), pointer :: tmp_ptr

integer(i_def) :: order_h, order_v
type(function_space_type), pointer :: fs

call log_event( 'coupled: Initialising app ...', LOG_LEVEL_INFO )

! Get the name of the coupling component
call modeldb%values%get_value("cpl_name", cpl_component_name)

order_h = modeldb%config%finite_element%element_order_h()
order_v = modeldb%config%finite_element%element_order_v()

fs => function_space_collection%get_fs(mesh, order_h, order_v, W3)

! Create prognostic fields
! Creates a field in the W3 function space (fully discontinuous field)
call field_1%initialise( vector_space = &
function_space_collection%get_fs(mesh, element_order_h, element_order_v, W3), &
name="field_1")
call field_2%initialise( vector_space = &
function_space_collection%get_fs(mesh, element_order_h, element_order_v, W3), &
name="field_2")
call field_1%initialise(fs, name="field_1")
call field_2%initialise(fs, name="field_2")

! Add field to modeldb
depository => modeldb%fields%get_field_collection("depository")
Expand Down
38 changes: 25 additions & 13 deletions applications/io_demo/source/algorithm/io_demo_alg_mod.x90
Original file line number Diff line number Diff line change
Expand Up @@ -6,16 +6,18 @@

!>@brief Module containing io_demo_alg
module io_demo_alg_mod

use constants_mod, only: i_def,r_def
use driver_modeldb_mod, only: modeldb_type
use log_mod, only: log_event, &
LOG_LEVEL_INFO, &
LOG_LEVEL_TRACE
use mesh_mod, only: mesh_type

use field_mod, only: field_type
use finite_element_config_mod, only: element_order_h, &
element_order_v
use fs_continuity_mod, only: Wtheta, W2
use fs_continuity_mod, only: Wtheta
use function_space_collection_mod, only: function_space_collection
use function_space_mod, only: function_space_type
use operator_mod, only: operator_type
use matrix_vector_kernel_mod, only: matrix_vector_kernel_type
use io_demo_constants_mod, only: get_dx_at_w2
Expand All @@ -31,11 +33,14 @@ module io_demo_alg_mod
contains

!> @details Calculates the diffusion increment for a field, and adds it to said field.
!> @param[in] modeldb Application state object
!> @param[inout] field_in Input Wtheta field
subroutine io_demo_alg( field_in )
subroutine io_demo_alg( modeldb, field_in )

implicit none

type(modeldb_type), intent(in) :: modeldb

! Prognostic fields
type( field_type ), intent( inout ) :: field_in

Expand All @@ -44,20 +49,27 @@ contains
type( field_type ) :: visc

real(r_def), parameter :: visc_val = 100000.0_r_def
type(mesh_type), pointer :: mesh => null()
integer(kind=i_def), parameter :: stencil_depth = 1_i_def
type( field_type ), pointer :: dx_at_w2 => null()

type(mesh_type), pointer :: mesh
type(field_type), pointer :: dx_at_w2
type(function_space_type), pointer :: fs

integer(i_def) :: order_h, order_v

call log_event( "io_demo: Running algorithm", LOG_LEVEL_TRACE )
mesh => field_in%get_mesh()

order_h = modeldb%config%finite_element%element_order_h()
order_v = modeldb%config%finite_element%element_order_v()

mesh => field_in%get_mesh()
dx_at_w2 => get_dx_at_w2(mesh)
call dfield_in%initialise( &
function_space_collection%get_fs( mesh, element_order_h, &
element_order_v, Wtheta))
call visc%initialise( &
function_space_collection%get_fs( mesh, element_order_h, &
element_order_v, Wtheta))

fs => function_space_collection%get_fs(mesh, order_h, order_v, Wtheta)

call dfield_in%initialise(fs)
call visc%initialise(fs)

call invoke( name = "compute_diffusion", &
setval_c(visc, visc_val), &
setval_c(dfield_in, 0.0_r_def), &
Expand Down
29 changes: 17 additions & 12 deletions applications/io_demo/source/algorithm/io_demo_constants_mod.x90
Original file line number Diff line number Diff line change
Expand Up @@ -15,30 +15,30 @@
module io_demo_constants_mod

! Infrastructure
use constants_mod, only: i_def, r_def, &
use constants_mod, only: i_def, r_def, l_def, &
str_def, str_short
use driver_modeldb_mod, only: modeldb_type
use field_collection_mod, only: field_collection_type
use field_mod, only: field_type
use fs_continuity_mod, only: W2
use function_space_collection_mod, only: function_space_collection
use function_space_mod, only: function_space_type
use io_config_mod, only: subroutine_timers
use log_mod, only: log_event, LOG_LEVEL_TRACE, &
LOG_LEVEL_ERROR
use mesh_mod, only: mesh_type
use timer_mod, only: timer

! Kernels
use sci_calc_dA_at_w2_kernel_mod, only: calc_dA_at_w2_kernel_type
use sci_calc_detj_at_w2_kernel_mod, only: calc_detj_at_w2_kernel_type
use sci_multiplicity_kernel_mod, only: multiplicity_kernel_type
use sci_calc_dA_at_w2_kernel_mod, only: calc_dA_at_w2_kernel_type
use sci_calc_detj_at_w2_kernel_mod, only: calc_detj_at_w2_kernel_type
use sci_multiplicity_kernel_mod, only: multiplicity_kernel_type

implicit none

private

! Objects for dx_at_w2 functionality
type(field_collection_type) :: dx_at_w2_collection
type(field_collection_type) :: dx_at_w2_collection

private :: add_dx_at_w2

Expand All @@ -48,19 +48,24 @@ module io_demo_constants_mod
contains

!> @brief Subroutine to create the finite element constants
!> @param[in] modeldb Application state object
!> @param[in] mesh The prime model mesh
!> @param[in] chi Coordinate fields
!> @param[in] panel_id Panel_id field
subroutine create_io_demo_constants(mesh, &
chi, &
panel_id )
subroutine create_io_demo_constants(modeldb, mesh, chi, panel_id)

implicit none

! Arguments
type(mesh_type), pointer, intent(in) :: mesh
type(field_type), target, intent(in) :: chi(:)
type(field_type), target, intent(in) :: panel_id
type(modeldb_type), intent(in) :: modeldb

type(mesh_type), pointer, intent(in) :: mesh
type(field_type), target, intent(in) :: chi(:)
type(field_type), target, intent(in) :: panel_id

logical(l_def) :: subroutine_timers

subroutine_timers = modeldb%config%io%subroutine_timers()

if ( subroutine_timers ) call timer('io_demo_constants_alg')
call log_event( "io_demo: creating runtime constants", LOG_LEVEL_TRACE )
Expand Down
40 changes: 24 additions & 16 deletions applications/io_demo/source/driver/init_io_demo_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -12,22 +12,19 @@
module init_io_demo_mod

use sci_assign_field_random_range_alg_mod, only: assign_field_random_range
use constants_mod, only : i_def, r_def
use constants_mod, only : i_def, r_def, l_def
use driver_modeldb_mod, only : modeldb_type
use field_collection_mod, only : field_collection_type
use field_mod, only : field_type
use field_parent_mod, only : write_interface
use finite_element_config_mod, only : element_order_h, &
element_order_v
use function_space_collection_mod, only : function_space_collection
use function_space_mod, only : function_space_type
use fs_continuity_mod, only : Wtheta
use key_value_mod, only : abstract_value_type
use log_mod, only : log_event, &
LOG_LEVEL_TRACE, &
LOG_LEVEL_ERROR
use mesh_mod, only : mesh_type
use io_config_mod, only : write_diag, &
use_xios_io
use lfric_xios_write_mod, only : write_field_generic
use io_demo_constants_mod, only : create_io_demo_constants
use random_number_generator_mod, only : random_number_generator_type
Expand All @@ -37,20 +34,21 @@ module init_io_demo_mod
contains

!> @details Initialises everything needed to run the io_demo miniapp
!> @param[in,out] modeldb The structure that holds model state
!> @param[in] mesh Representation of the mesh the code will run on
!> @param[in,out] chi The co-ordinate field
!> @param[in,out] panel_id 2d field giving the id for cubed sphere panels
!> @param[in,out] modeldb The structure that holds model state
subroutine init_io_demo( mesh, chi, panel_id, modeldb)
subroutine init_io_demo(modeldb, mesh, chi, panel_id)

implicit none

type(mesh_type), intent(in), pointer :: mesh
type(modeldb_type), intent(inout) :: modeldb
type(mesh_type), intent(in), pointer :: mesh

! Coordinate field
type(field_type), intent(inout) :: chi(:)
type(field_type), intent(inout) :: panel_id
type(modeldb_type), intent(inout) :: modeldb
type(field_type), intent(inout) :: chi(:)
type(field_type), intent(inout) :: panel_id

class(abstract_value_type), pointer :: abstract_value
type(random_number_generator_type), pointer :: rng
type(field_type) :: diffusion_field
Expand All @@ -59,8 +57,20 @@ subroutine init_io_demo( mesh, chi, panel_id, modeldb)
real(kind=r_def), parameter :: min_val = 280.0_r_def
real(kind=r_def), parameter :: max_val = 330.0_r_def

type(function_space_type), pointer :: fs

integer(i_def) :: order_h, order_v
logical(l_def) :: write_diag
logical(l_def) :: use_xios_io

call log_event( 'io_demo: Initialising miniapp ...', LOG_LEVEL_TRACE )

order_h = modeldb%config%finite_element%element_order_h()
order_v = modeldb%config%finite_element%element_order_v()

write_diag = modeldb%config%io%write_diag()
use_xios_io = modeldb%config%io%use_xios_io()

! seed the random number generator
call modeldb%values%get_value("rng", abstract_value)
select type(abstract_value)
Expand All @@ -76,10 +86,8 @@ subroutine init_io_demo( mesh, chi, panel_id, modeldb)

! Create prognostic fields
! Creates a field in the Wtheta function space
call diffusion_field%initialise( vector_space = &
function_space_collection%get_fs(mesh, element_order_h, &
element_order_v, Wtheta), &
name="diffusion_field")
fs => function_space_collection%get_fs(mesh, order_h, order_v, Wtheta)
call diffusion_field%initialise(fs, name="diffusion_field")

! Set up field with an IO behaviour (XIOS only at present)
if (write_diag .and. use_xios_io) then
Expand All @@ -98,7 +106,7 @@ subroutine init_io_demo( mesh, chi, panel_id, modeldb)
! Create io_demo runtime constants. This creates various things
! needed by the fem algorithms such as mass matrix operators, mass
! matrix diagonal fields and the geopotential field
call create_io_demo_constants(mesh, chi, panel_id)
call create_io_demo_constants(modeldb, mesh, chi, panel_id)

call log_event( 'io_demo: Miniapp initialised', LOG_LEVEL_TRACE )

Expand Down
Loading