module Interpreter.Lib.Math where import Control.Monad.IO.Class import Data.Coerce import Data.Vector as V import Common import Interpreter.Common import System.Random builtInSum :: BuiltInFnWithDoc '[ '("numbers", Vector Number)] builtInSum ((coerce -> numbers) :> _) = let addFn = numberBinaryFn (+) in pure $ Just $ NumberValue $ V.foldl' addFn (NumberInt 0) numbers builtInMod :: BuiltInFnWithDoc '[ '("divident", IntType), '("divisor", IntType)] builtInMod ((coerce -> divid) :> (coerce -> divis) :> _) = pure $ Just $ NumberValue $ NumberInt $ mod divid divis builtInRound :: BuiltInFnWithDoc '[ '("value", FloatType)] builtInRound ((coerce -> (number :: FloatType)) :> _) = pure $ Just $ NumberValue $ NumberInt $ round $ number builtInRandom :: BuiltInFnWithDoc '[ '("start_rage", IntType), '("end_range", IntType)] builtInRandom ((coerce -> start) :> (coerce -> end) :> _) = do r <- liftIO $ randomRIO @IntType (start, end) pure $ Just $ NumberValue $ NumberInt r builtInSin :: BuiltInFnWithDoc '[ '("angle", FloatType)] builtInSin ((coerce -> angle) :> _) = do pure $ Just $ NumberValue $ NumberFractional (sin (degreeToRadian angle)) builtInCos :: BuiltInFnWithDoc '[ '("angle", FloatType)] builtInCos ((coerce -> angle) :> _) = do pure $ Just $ NumberValue $ NumberFractional (cos (degreeToRadian angle)) builtInTan :: BuiltInFnWithDoc '[ '("angle", FloatType)] builtInTan ((coerce -> angle) :> _) = do pure $ Just $ NumberValue $ NumberFractional (tan (degreeToRadian angle)) builtInASin :: BuiltInFnWithDoc '[ '("arg", FloatType)] builtInASin ((coerce -> v) :> _) = do pure $ Just $ NumberValue $ NumberFractional (radianToDegree $ asin v) builtInACos :: BuiltInFnWithDoc '[ '("arg", FloatType)] builtInACos ((coerce -> v) :> _) = do pure $ Just $ NumberValue $ NumberFractional (radianToDegree $ acos v) builtInATan :: BuiltInFnWithDoc '[ '("arg", FloatType)] builtInATan ((coerce -> v) :> _) = do pure $ Just $ NumberValue $ NumberFractional (radianToDegree $ atan v) builtInPow :: BuiltInFnWithDoc '[ '("number", Double), '("pow", IntType)] builtInPow ((coerce -> (v :: FloatType)) :> (coerce -> (pw :: IntType)) :> EmptyArgs) = pure $ Just $ NumberValue $ NumberFractional $ v ^ pw radianToDegree :: FloatType -> FloatType radianToDegree x = (x/pi*180) degreeToRadian :: FloatType -> FloatType degreeToRadian x = (x/180*pi)