module Language.Haskell.Holes
(
(-->)
, hole
, holeWith
, internals
, Term (Internal)
)
where
import Language.Haskell.TH
import Prelude hiding (lookup)
import Data.List (inits, tails)
import Data.Either (rights)
import Control.Arrow (second)
data TypeDef =
TVar Name
| Imp TypeDef TypeDef
deriving (Eq)
instance Show TypeDef where
show (TVar name) = show name
show (Imp a b) = "(" ++ show a ++ " -> " ++ show b ++ ")"
data Term =
Var Name
| Internal (Q Exp)
| App Term Term
| Lam Name Term
type ErrorMsg = String
type Context = [(Term, TypeDef)]
class TypeDefClass a where
asTypeDef :: a -> TypeDef
instance TypeDefClass TypeDef where
asTypeDef = id
instance TypeDefClass Char where
asTypeDef = asTypeDef . (:[])
instance TypeDefClass String where
asTypeDef = asTypeDef . mkName
instance TypeDefClass Name where
asTypeDef = TVar
(-->) :: (TypeDefClass a, TypeDefClass b) => a -> b -> TypeDef
a --> b = Imp (asTypeDef a) (asTypeDef b)
infixr 6 -->
vars :: [String]
vars =
map (\n -> n) $
map return letters ++
(zipWith (\c n -> c : show n) (concat $ repeat letters) $
concatMap (\n -> take (length letters) $ repeat n) [1..])
where letters = "abcdefghijklmnopqrstuvwxyz"
tip ::
[String]
-> Context
-> TypeDef
-> Either ErrorMsg Term
tip vars ctx (Imp a b) =
let name = mkName (head vars) in
case tip (tail vars) ((Var name, a) : ctx) b of
Right exp -> Right $ Lam name exp
x -> x
tip vars ctx goal =
if null branches
then Left $ "Can't prove " ++ show goal
else Right $ head branches
where
branches = rights . map try $ pulls ctx
try :: ((Term, TypeDef), Context) -> Either ErrorMsg Term
try ((exp, TVar v), newCtx)
| TVar v == goal = Right exp
try ((exp, Imp a b), newCtx) =
case tip vars newCtx a of
Right expA -> tip vars ((App exp expA, b) : newCtx) goal
x -> x
try _ = Left mempty
pulls :: [a] -> [(a, [a])]
pulls xs = take (length xs) $ zipWith (second . (++)) (inits xs) breakdown
where pull (x : xs) = (x, xs)
breakdown = map pull (tails xs)
hole :: TypeDefClass a => a -> Q Exp
hole = holeWith internals
holeWith :: TypeDefClass a => [(Term, TypeDef)] -> a -> Q Exp
holeWith internals exp =
let typeDef = asTypeDef exp in
case tip vars internals typeDef of
Right r -> do
r <- toExp r
runIO . putStrLn $ "hole: " ++ pprint r ++ " :: " ++ show typeDef
return r
Left e -> fail e
toExp :: Term -> Q Exp
toExp (Var n) = return $ VarE n
toExp (App a b) = do
a <- toExp a
b <- toExp b
return (AppE a b)
toExp (Lam a b) =
toExp b >>= return . LamE [VarP a]
toExp (Internal qexp) = qexp
internals =
map (\(a, b) -> (Internal a, b))
[
([| 0 :: Int |], TVar ''Int),
([| 0 :: Integer |], TVar ''Integer),
([| 0 :: Double |], TVar ''Double),
([| 0 :: Float |], TVar ''Float),
([| "" :: String |], TVar ''String),
([| ' ' :: Char |], TVar ''Char)
]