{-# LANGUAGE
TemplateHaskell,
UnicodeSyntax,
CPP
#-}
module Data.Function.Memoize.TH (
deriveMemoizable, deriveMemoizableParams, deriveMemoize,
) where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
#endif
import Control.Monad
import Language.Haskell.TH
import Data.Function.Memoize.Class
deriveMemoizable ∷ Name → Q [Dec]
deriveMemoizable n = deriveMemoizable' n Nothing
deriveMemoizableParams ∷ Name → [Int] → Q [Dec]
deriveMemoizableParams n indices = deriveMemoizable' n (Just indices)
deriveMemoize ∷ Name → ExpQ
deriveMemoize name0 = do
(_, _, cons) ← checkName name0
buildMethodExp cons
deriveMemoizable' ∷ Name → Maybe [Int] → Q [Dec]
deriveMemoizable' name0 mindices = do
(name, tvbs, cons) ← checkName name0
let tvs = freshNames tvbs
inst ← instanceD
(buildContext mindices tvbs tvs)
(buildHead name tvs)
[buildMethodDec cons]
return [inst]
checkName ∷ Name → Q (Name, [TyVarBndr], [(Name, Int)])
checkName name0 = do
info ← reify name0
case info of
#if MIN_VERSION_template_haskell(2,11,0)
TyConI (DataD _ name tvbs _ cons _)
#else
TyConI (DataD _ name tvbs cons _)
#endif
→ return (name, tvbs, stdizeCon <$> cons)
#if MIN_VERSION_template_haskell(2,11,0)
TyConI (NewtypeD _ name tvbs _ con _)
#else
TyConI (NewtypeD _ name tvbs con _)
#endif
→ return (name, tvbs, [stdizeCon con])
_ → fail $
"deriveMemoizable: Can't derive a Memoizable instance for `" ++
show name0 ++ "' because it isn't a type constructor."
where
stdizeCon (NormalC name params) = (name, length params)
stdizeCon (RecC name fields) = (name, length fields)
stdizeCon (InfixC _ name _) = (name, 2)
stdizeCon (ForallC _ _ con) = stdizeCon con
freshNames ∷ [a] → [Name]
freshNames xs = take (length xs) alphabet
where
alphabet = [ mkName (c:s)
| s ← "" : (show <$> [1 ∷ Integer ..])
, c ← ['a' .. 'z'] ]
buildContext ∷ Maybe [Int] → [TyVarBndr] → [Name] → CxtQ
buildContext mindices tvbs tvs =
#if MIN_VERSION_template_haskell(2,10,0)
cxt (appT (conT ''Memoizable) . varT <$> cxttvs)
#else
cxt (classP ''Memoizable . (:[]) . varT <$> cxttvs)
#endif
where
cxttvs = case mindices of
Just ixs → filterBy (`elem` ixs) [1 ..] tvs
Nothing → filterBy isStar tvbs tvs
--
isStar (PlainTV _) = True
#if __GLASGOW_HASKELL__ >= 706
isStar (KindedTV _ StarT) = True
#else
isStar (KindedTV _ StarK) = True
#endif
isStar (KindedTV _ _) = False
--
filterBy ∷ (a → Bool) → [a] → [b] → [b]
filterBy p xs ys = snd <$> filter (p . fst) (zip xs ys)
-- | Build the 'Memoizable' instance head for the given type name
-- and parameter type variables.
buildHead ∷ Name → [Name] → TypeQ
buildHead name tvs =
appT (conT ''Memoizable) (foldl appT (conT name) (varT <$> tvs))
-- | Build the 'memoize' method. The form of 'memoize' is always
--
-- @
-- memoize f = lookup where
-- cache1 = memoize $ \x1 -> ... memoize $ \x(a1) -> f (C1 x1 ...)
-- ...
-- cacheN = memoize $ \x1 -> ... memoize $ \x(aN) -> f (CN x1 ...)
-- lookup (C1 x1 ...) = cache1 x1 ...
-- ...
-- lookup (CN xN ...) = cacheN xN ...
-- @
--
-- where @C1@ ... @CN@ are the constructors of the data type and
-- @aj@ is the arity of constructor @Cj@.
--
-- In this method, we allocate fresh names for the parameter @f@, the
-- lookup function, and the @N@ caches. We then delegate to build
-- the definitions of @look@ and the caches.
buildMethodDec ∷ [(Name, Int)] → DecQ
buildMethodDec cons = do
valD (varP 'memoize)
(normalB (buildMethodExp cons))
[]
-- | Build the body of the 'memoize' method, as described in the comment
-- above 'buildMethodDec'
buildMethodExp ∷ [(Name, Int)] → ExpQ
buildMethodExp cons = do
f ← newName "f"
look ← newName "look"
caches ← mapM (\ _ -> newName "cache") cons
lam1E (varP f)
(letE
(buildLookup look cons caches
: zipWith (buildCache f) cons caches)
(varE look))
-- | Build the look function by building a clause for each constructor
-- of the datatype.
buildLookup ∷ Name → [(Name, Int)] → [Name] → DecQ
buildLookup look cons caches =
funD look (zipWith buildLookupClause cons caches)
-- | Build a lookup clause for one constructor. We lookup a value
-- by matching that constructor and then passing its parameters to
-- the cache for that constructor.
buildLookupClause ∷ (Name, Int) → Name → ClauseQ
buildLookupClause (con, arity) cache = do
params ← replicateM arity (newName "a")
clause [conP con (varP <$> params)]
(normalB (foldl appE (varE cache) (varE <$> params)))
[]
-- | Build the definition of a cache for the given constructor. We do
-- this by binding the cache name to a cascading sequence of
-- memoizations for each component in the constructor's arity.
buildCache ∷ Name → (Name, Int) → Name → DecQ
buildCache f (con, arity) cache =
valD (varP cache) (normalB (composeMemos arity f (conE con))) []
-- | Given the remaining arity to memoize, the name of the function to
-- memoize, and the accumulated parameter so far, build the
-- memoization chain.
composeMemos ∷ Int → Name → ExpQ → ExpQ
composeMemos 0 f arg = [| $(varE f) $arg |]
composeMemos arity f arg = do
[| memoize $ \b -> $(composeMemos (arity - 1) f [| $arg b |]) |]