{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
module Dovetail.Core.Data.EuclideanRing where
import Data.Foldable (fold)
import Dovetail
import Dovetail.Evaluate (builtIn)
env :: forall ctx. Env ctx
env :: Env ctx
env = do
let _ModuleName :: ModuleName
_ModuleName = Text -> ModuleName
ModuleName Text
"Data.EuclideanRing"
[Env ctx] -> Env ctx
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold
[
ModuleName -> Text -> (Integer -> Eval ctx Integer) -> Env ctx
forall ctx a. ToValue ctx a => ModuleName -> Text -> a -> Env ctx
builtIn @ctx @(Integer -> Eval ctx Integer)
ModuleName
_ModuleName Text
"intDegree"
\Integer
n ->
Integer -> Eval ctx Integer
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Integer -> Integer
forall a. Num a => a -> a
abs Integer
n)
, ModuleName
-> Text -> (Integer -> Integer -> Eval ctx Integer) -> Env ctx
forall ctx a. ToValue ctx a => ModuleName -> Text -> a -> Env ctx
builtIn @ctx @(Integer -> Integer -> Eval ctx Integer)
ModuleName
_ModuleName Text
"intDiv"
\Integer
x Integer
y ->
Integer -> Eval ctx Integer
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Integer
x Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
y)
, ModuleName
-> Text -> (Integer -> Integer -> Eval ctx Integer) -> Env ctx
forall ctx a. ToValue ctx a => ModuleName -> Text -> a -> Env ctx
builtIn @ctx @(Integer -> Integer -> Eval ctx Integer)
ModuleName
_ModuleName Text
"intMod"
\Integer
x Integer
y ->
Integer -> Eval ctx Integer
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Integer
x Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
y)
, ModuleName
-> Text -> (Double -> Double -> Eval ctx Double) -> Env ctx
forall ctx a. ToValue ctx a => ModuleName -> Text -> a -> Env ctx
builtIn @ctx @(Double -> Double -> Eval ctx Double)
ModuleName
_ModuleName Text
"numDiv"
\Double
x Double
y ->
Double -> Eval ctx Double
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Double
x Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
y)
]