[Haskell-cafe] How can I find out which functions can be run on an expression?
Julian Leviston
julian at getcontented.com.au
Sun Apr 30 12:35:05 UTC 2017
I'd like to programmatically find out which functions in a module could possibly apply to a particular expression.
I also posted this to stack overflow.
To make this concrete:
{-# LANGUAGE TemplateHaskell #-}
module Test where
-- we'll import template-haskell from Lens
-- so we can create prisms automatically for our 'AST'
import qualified Control.Lens.TH as LTH
--- some 'AST' in a toy language
data CExp
= CLit Int -- a literal integer
| CAdd CExp CExp -- addition
| CMul CExp CExp -- multiplication
| CSub CExp CExp -- subtraction
deriving Show
-- an eval for our AST
eval :: CExp -> Int
eval exp =
case exp of
CLit i -> i
CAdd e1 e2 ->
eval e1 + eval e2
CMul e1 e2 ->
eval e1 * eval e2
CSub e1 e2 ->
eval e1 - eval e2
-- a function to build a sum using add with our AST, from a list of Int values
listToSums :: [Int] -> CExp
listToSums =
foldr CAdd (CLit 0) . fmap CLit
-- here we make prisms for looking at particular values
-- in the CExp AST
LTH.makePrisms ''CExp
-- let's have an expression:
theList1 :: CExp
theList1 = listToSums [1..38]
Now, at this point, I'd like a function that can give me a list of all the top level functions of a particular module (including this one) that are able to be applied to the expression theList1. This will include the prisms that were created with makePrisms.
It would be fine if it uses the hint library's Interpreter monad. I've been experimenting with it a bit, and while I can get a list of all of the definitions at the top level of any module, and I can find the types of them, too (more or less), I'm a bit lost about how to pass an expression in as an argument to these functions then check if that exprssions will typecheck.
If I can do that, I can run filter across all of the functions in a module, which lets me find out which ones are applicable.
Many thanks in advance.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170430/8172b798/attachment.html>
More information about the Haskell-Cafe
mailing list