-- |
-- SPDX-License-Identifier: BSD-3-Clause
--
-- Creation and utilities for the unit interval
module Swarm.Util.UnitInterval (
  UnitInterval,
  getValue,
  mkInterval,
  safeIndex,
) where

import Data.List.NonEmpty (NonEmpty, (!!))
import Prelude hiding ((!!))

newtype UnitInterval a = UnitInterval
  { forall a. UnitInterval a -> a
getValue :: a
  }

-- | Guarantees that the stored value falls within the closed interval
--   @[0, 1]@. It is up to clients to ensure that the promotion
--   to this type is lossless.
mkInterval :: (Ord a, Num a) => a -> UnitInterval a
mkInterval :: forall a. (Ord a, Num a) => a -> UnitInterval a
mkInterval = forall a. a -> UnitInterval a
UnitInterval forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => a -> a -> a
max a
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => a -> a -> a
min a
1

-- | Since '(!!)' is partial, here is "proof" that it is safe:
-- If "alpha" is its maximum value of @1@, then the maximum value
-- of the computed index shall be one less than the length of the
-- list (i.e., a valid index).
--
-- See also: 'Swarm.Util.indexWrapNonEmpty'.
safeIndex ::
  RealFrac a =>
  -- | alpha
  UnitInterval a ->
  NonEmpty b ->
  b
safeIndex :: forall a b. RealFrac a => UnitInterval a -> NonEmpty b -> b
safeIndex (UnitInterval a
alpha) NonEmpty b
xs =
  NonEmpty b
xs forall a. NonEmpty a -> Int -> a
!! forall a b. (RealFrac a, Integral b) => a -> b
floor (a
alpha forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (t :: * -> *) a. Foldable t => t a -> Int
length NonEmpty b
xs forall a. Num a => a -> a -> a
- Int
1))