独自の数学関数と数値のセットを使用する場合は、理論的には可能です。あなたがする必要があるのは、各関数がどのように計算されるかを追跡するタイプのシステムを作成することです。これは、式のタイプに反映されます。テンプレートhaskellとreify関数のいずれかを使用するか、型クラスコードを使用すると、コンパイル時に正しいコードを生成できます。
これは、型クラスを使用したハッキーなサンプル実装です。これは、sin、cos、定数、および加算で機能します。すべての操作を実装するのは大変な作業です。また、コードにはかなりの重複があります。そのようなアプローチの使用を計画している場合は、その問題の修正を試みる必要があります。
{-# LANGUAGE ScopedTypeVariables, UndecidableInstances, FlexibleInstances, MultiParamTypeClasses, FunctionalDependencies #-}
module TrackedComputation where
import Prelude hiding (sin, cos, Num(..))
import Data.Function (on)
import qualified Prelude as P
-- A tracked computation (TC for short).
-- It stores how a value is computed in the computation phantom variable
newtype TC newComp val = TC { getVal :: val }
deriving (Eq)
instance (Show val) => Show (TC comp val) where
show = show . getVal
data SinT comp = SinT
data CosT comp = CosT
data AddT comp1 comp2 = AddT
data ConstantT = ConstantT
data VariableT = VariableT
sin :: (P.Floating a) => TC comp1 a -> TC (SinT comp1) a
sin = TC . P.sin . getVal
cos :: (P.Floating a) => TC comp1 a -> TC (CosT comp1) a
cos = TC . P.cos . getVal
(+) :: (P.Num a) => TC comp1 a -> TC comp2 a -> TC (AddT comp1 comp2) a
(TC a) + (TC b) = TC $ (P.+) a b
toNum :: a -> TC ConstantT a
toNum = TC
class Differentiate comp compRIn compROut | comp compRIn -> compROut where
differentiate :: P.Floating a => (TC VariableT a -> TC comp a) -> (TC compRIn a -> TC compROut a)
instance Differentiate ConstantT compIn ConstantT where
differentiate _ = const $ toNum 0
instance Differentiate (SinT VariableT) compIn (CosT compIn) where
differentiate _ = cos
instance Differentiate VariableT compIn (ConstantT) where
differentiate _ = const $ toNum 1
instance (Differentiate add1 compIn add1Out, Differentiate add2 compIn add2Out) =>
Differentiate (AddT add1 add2) compIn (AddT add1Out add2Out) where
differentiate _ (val :: TC compROut a) = result where
first = differentiate (undefined :: TC VariableT a -> TC add1 a) val :: TC add1Out a
second = differentiate (undefined :: TC VariableT a -> TC add2 a) val :: TC add2Out a
result = first + second
instance P.Num val => P.Num (TC ConstantT val) where
(+) = (TC .) . ((P.+) `on` getVal)
(*) = (TC .) . ((P.*) `on` getVal)
abs = (TC) . ((P.abs) . getVal)
signum = (TC) . ((P.signum) . getVal)
fromInteger = TC . P.fromInteger
f x = sin x
g = differentiate f
h x = sin x + x + toNum 42 + x
test1 = f . toNum
test2 = g . toNum
test3 = differentiate h . toNum