Create a function from a string

I have this type that I made an instance of Num:

data MyNumType = MyNumType [String] String deriving Show
myNumType n = MyNumType [n] n --constructor

instance Num MyNumType where
  (+) (MyNumType a b) (MyNumType c d) = MyNumType (a ++ c) ("(" ++ b ++ "+" ++ d ++ ")")
  (-) (MyNumType a b) (MyNumType c d) = MyNumType (a ++ c) ("(" ++ b ++ "-" ++ d ++ ")")
  (*) (MyNumType a b) (MyNumType c d) = MyNumType (a ++ c) ("(" ++ b ++ "*" ++ d ++ ")")
  fromInteger n = MyNumType [show n] (show n)
  abs (MyNumType a b) = MyNumType a ("abs(" ++ b ++ ")")
  signum (MyNumType a b) = MyNumType a ("signum(" ++ b ++ ")") 

The purpose of this MyNumType is to keep track of the calculations that variables undergo, here is an example:

a = myNumType "a"
b = myNumType "b"
myComputation = a + b
-- myComputation --> MyNumType ["a","b"] "(a+b)"

myComputation keeps track of independent variables and functions that have been computed from them. I would like to create a haskell function from “(a+b)”: \a b -> a+b


I understand that using strings is not the most efficient way to do this. In julia I would have used some symbolic computation library or built functions from the strings with metaprogramming.
So if you have better ways to do it every answer is welcome.

Do you maybe want to use Template Haskell to generate the function at compile time?

2 Likes

You’d be better keep the all expression tree and (pretty) print it when need than just keeping a string.

4 Likes

Maybe something like this?

data NumExpr v
  = Plus (NumExpr v) (NumExpr v)
  | Minus (NumExpr v) (NumExpr v)
  | Times (NumExpr v) (NumExpr v)
  | Negate (NumExpr v)
  | Abs (NumExpr v)
  | Signum (NumExpr v)
  | FromInteger Integer
  | Var v
  | Lambda (NumExpr (Maybe v))
  | Apply (NumExpr v) (NumExpr v)
  deriving (Eq, Show, Read)

eval :: Num x => (v -> x) -> NumExpr v -> x
eval args = eval'
 where
  eval' (Plus n m) = eval' n + eval' m
  eval' (Minus n m) = eval' n - eval' m
  eval' (Times n m) = eval' n * eval' m
  eval' (Negate n) = negate (eval' n)
  eval' (Abs n) = abs (eval' n)
  eval' (Signum n) = signum (eval' n)
  eval' (FromInteger i) = fromInteger i
  eval' (Var x) = args x
  eval' (Lambda b) = eval args' b
   where
    args' Nothing = error "Unapplied function"
    args' (Just x) = args x
  eval' (Apply (Lambda f) x) = eval args' f
   where
    args' Nothing = eval' x
    args' (Just y) = args y
  eval' (Apply _ _) = error "Appliying non-function"

main :: IO ()
main = print $ eval (\() -> 0 :: Integer) (Plus (FromInteger 2) (FromInteger 3))

Also consider the “bound” library, and actual parsing and pretty-printing functions.

2 Likes