{-# LANGUAGE GADTs #-}
module Duckling.Distance.Helpers
( distance
, distanceSum
, isDistanceOfUnit
, isSimpleDistance
, unitOnly
, withInterval
, withMax
, withMin
, withUnit
, withValue
) where
import Prelude
import Data.Semigroup ((<>))
import Duckling.Dimensions.Types
import Duckling.Distance.Types (DistanceData(..))
import Duckling.Types
import qualified Duckling.Distance.Types as TDistance
import qualified Duckling.DistanceUnits.Types as DGTypes
isSimpleDistance :: Predicate
isSimpleDistance :: Predicate
isSimpleDistance (Token Dimension a
Distance DistanceData {TDistance.value = Just _
, TDistance.unit = Just _}) = Bool
True
isSimpleDistance Token
_ = Bool
False
isDistanceOfUnit :: TDistance.Unit -> Predicate
isDistanceOfUnit :: Unit -> Predicate
isDistanceOfUnit Unit
unit (Token Dimension a
Distance DistanceData {TDistance.unit = Just u}) =
Unit
unit Unit -> Unit -> Bool
forall a. Eq a => a -> a -> Bool
== Unit
u
isDistanceOfUnit Unit
_ Token
_ = Bool
False
distance :: Double -> DistanceData
distance :: Double -> DistanceData
distance Double
x = DistanceData :: Maybe Unit
-> Maybe Double -> Maybe Double -> Maybe Double -> DistanceData
DistanceData {value :: Maybe Double
TDistance.value = Double -> Maybe Double
forall a. a -> Maybe a
Just Double
x
, unit :: Maybe Unit
TDistance.unit = Maybe Unit
forall a. Maybe a
Nothing
, minValue :: Maybe Double
TDistance.minValue = Maybe Double
forall a. Maybe a
Nothing
, maxValue :: Maybe Double
TDistance.maxValue = Maybe Double
forall a. Maybe a
Nothing}
distanceSum ::
Double
-> TDistance.Unit
-> Double
-> TDistance.Unit
-> Maybe DistanceData
distanceSum :: Double -> Unit -> Double -> Unit -> Maybe DistanceData
distanceSum Double
v1 Unit
u1 Double
v2 Unit
u2 = ContextualDistance -> Maybe DistanceData
unwrapContext (ContextualDistance -> Maybe DistanceData)
-> ContextualDistance -> Maybe DistanceData
forall a b. (a -> b) -> a -> b
$ ContextualDistance
cd1 ContextualDistance -> ContextualDistance -> ContextualDistance
forall a. Semigroup a => a -> a -> a
<> ContextualDistance
cd2
where
wrapContext :: Double -> Unit -> ContextualDistance
wrapContext Double
v Unit
u = Double -> DeferrableUnit -> ContextualDistance
DGTypes.ContextualDistance Double
v (DeferrableUnit -> ContextualDistance)
-> DeferrableUnit -> ContextualDistance
forall a b. (a -> b) -> a -> b
$ Unit -> DeferrableUnit
DGTypes.toSystemUnit Unit
u
cd1 :: ContextualDistance
cd1 = Double -> Unit -> ContextualDistance
wrapContext Double
v1 Unit
u1
cd2 :: ContextualDistance
cd2 = Double -> Unit -> ContextualDistance
wrapContext Double
v2 Unit
u2
unwrapContext :: ContextualDistance -> Maybe DistanceData
unwrapContext ContextualDistance
DGTypes.Nonrelatable = Maybe DistanceData
forall a. Maybe a
Nothing
unwrapContext (DGTypes.ContextualDistance Double
v DeferrableUnit
u) =
DistanceData -> Maybe DistanceData
forall a. a -> Maybe a
Just (DistanceData -> Maybe DistanceData)
-> DistanceData -> Maybe DistanceData
forall a b. (a -> b) -> a -> b
$ Unit -> DistanceData -> DistanceData
withUnit (DeferrableUnit -> Unit
DGTypes.toRawUnit DeferrableUnit
u) (DistanceData -> DistanceData) -> DistanceData -> DistanceData
forall a b. (a -> b) -> a -> b
$ Double -> DistanceData
distance Double
v
unitOnly :: TDistance.Unit -> DistanceData
unitOnly :: Unit -> DistanceData
unitOnly Unit
u = DistanceData :: Maybe Unit
-> Maybe Double -> Maybe Double -> Maybe Double -> DistanceData
DistanceData {unit :: Maybe Unit
TDistance.unit = Unit -> Maybe Unit
forall a. a -> Maybe a
Just Unit
u
, value :: Maybe Double
TDistance.value = Maybe Double
forall a. Maybe a
Nothing
, minValue :: Maybe Double
TDistance.minValue = Maybe Double
forall a. Maybe a
Nothing
, maxValue :: Maybe Double
TDistance.maxValue = Maybe Double
forall a. Maybe a
Nothing}
withUnit :: TDistance.Unit -> DistanceData -> DistanceData
withUnit :: Unit -> DistanceData -> DistanceData
withUnit Unit
u DistanceData
dd = DistanceData
dd {unit :: Maybe Unit
TDistance.unit = Unit -> Maybe Unit
forall a. a -> Maybe a
Just Unit
u}
withValue :: Double -> DistanceData -> DistanceData
withValue :: Double -> DistanceData -> DistanceData
withValue Double
value DistanceData
dd = DistanceData
dd {value :: Maybe Double
TDistance.value = Double -> Maybe Double
forall a. a -> Maybe a
Just Double
value}
withInterval :: (Double, Double) -> DistanceData -> DistanceData
withInterval :: (Double, Double) -> DistanceData -> DistanceData
withInterval (Double
from, Double
to) DistanceData
dd = DistanceData
dd {minValue :: Maybe Double
TDistance.minValue = Double -> Maybe Double
forall a. a -> Maybe a
Just Double
from
, maxValue :: Maybe Double
TDistance.maxValue = Double -> Maybe Double
forall a. a -> Maybe a
Just Double
to}
withMin :: Double -> DistanceData -> DistanceData
withMin :: Double -> DistanceData -> DistanceData
withMin Double
from DistanceData
dd = DistanceData
dd {minValue :: Maybe Double
TDistance.minValue = Double -> Maybe Double
forall a. a -> Maybe a
Just Double
from}
withMax :: Double -> DistanceData -> DistanceData
withMax :: Double -> DistanceData -> DistanceData
withMax Double
to DistanceData
dd = DistanceData
dd {maxValue :: Maybe Double
TDistance.maxValue = Double -> Maybe Double
forall a. a -> Maybe a
Just Double
to}