module obl_run_kato
    !< @brief obl scm kato-phillips setup
    ! --------------------------------------------------------------------------------

    ! TO DO:
    !   -- ***

    ! modules used
    ! --------------------------------------------------------------------------------

    ! directives list
    ! --------------------------------------------------------------------------------
    implicit none
    private

    ! public interface
    ! --------------------------------------------------------------------------------
    public :: set_phys
    public :: set_grid
    public :: set_time
    public :: set_forcing
    public :: set_initial_conditions
    ! --------------------------------------------------------------------------------

    ! --------------------------------------------------------------------------------
    ! --------------------------------------------------------------------------------
    
    
    contains

    ! --------------------------------------------------------------------------------
    subroutine set_phys
        !> @brief phys parameters setup
        ! ----------------------------------------------------------------------------
        use obl_scm
        ! ----------------------------------------------------------------------------

        !< coriolis frequency
        f = 0.0

    end subroutine set_phys

    ! --------------------------------------------------------------------------------
    subroutine set_grid(grid)
        !> @brief grid parameters setup
        ! ----------------------------------------------------------------------------
        use obl_grid

        type (gridDataType), intent(inout) :: grid
        ! ----------------------------------------------------------------------------

        !< in: [zpos, height, cz]
        call set_uniform_grid(grid, - 100.0, 100.0, 32)

    end subroutine set_grid

    ! --------------------------------------------------------------------------------
    subroutine set_time(time_begin, time_end, dt)
        !> @brief time parameters setup
        ! ----------------------------------------------------------------------------
        real, intent(out) :: time_begin, time_end, dt
        ! ----------------------------------------------------------------------------

        time_begin = 0.0
        time_end = 300.0 * 3600.0
        dt = 1.0

    end subroutine set_time

    ! --------------------------------------------------------------------------------
    subroutine set_forcing
        !> @brief forcing setup
        ! ----------------------------------------------------------------------------
        use obl_fluxes
        use obl_tforcing
        ! ----------------------------------------------------------------------------

        !< setting atmospheric forcing
        ! ---------------------------------------------------------------------------- 
        !< using 'flux' mode
        is_meteo_setup = 0

        call set_const_tforcing(sensible_hflux_surf, 0.0)
        call set_const_tforcing(latent_hflux_surf, 0.0)

        call set_const_tforcing(salin_flux_surf, 0.0)

        call set_const_tforcing(tau_x_surf, 0.1)
        call set_const_tforcing(tau_y_surf, 0.0)

        call set_const_tforcing(sw_flux_surf, 0.0)

        call set_const_tforcing(lw_net_surf, 0.0)
        ! ---------------------------------------------------------------------------- 

        !< setting bottom forcing
        ! ----------------------------------------------------------------------------
        call set_const_tforcing(hflux_bot, 0.0)

        call set_const_tforcing(salin_flux_bot, 0.0)

        call set_const_tforcing(tau_x_bot, 0.0)
        call set_const_tforcing(tau_y_bot, 0.0)
        ! ----------------------------------------------------------------------------

    end subroutine set_forcing

    ! --------------------------------------------------------------------------------
    subroutine set_initial_conditions(grid)
        !> @brief initial_conditions setup
        ! ----------------------------------------------------------------------------
        use obl_state
        use obl_init
        use obl_grid

        type (gridDataType), intent(in) :: grid
        ! ----------------------------------------------------------------------------

        call set_linear_profile(Theta, 330.0, 0.3, grid)
        call set_const_profile(Salin, 35.0, grid)

        call set_const_profile(U, 0.0, grid)
        call set_const_profile(V, 0.0, grid)

    end subroutine set_initial_conditions

end module