Restricted Template Haskell

adam vogt vogt.adam at gmail.com
Sat Jan 31 03:05:13 UTC 2015


Hi Greg,

Perhaps a less-invasive way to implement the -XSafe part of your
proposal would be to provide a module like:

module Language.Haskell.TH.Safe (
  module Language.Haskell.TH,
  reifyWithoutNameG,
 )  where
import Language.Haskell.TH hiding (runIO, reify*)

where reifyWithoutNameG is the same as reify, except definitions that
are out of scope are either missing or modified such that they use
NameQ instead of NameG for out-of-scope names.

That way there is no new syntax needed, and safe TH can be called by
unsafe TH without any conversions.

I think defining another monad like Q that can do less is too
inconvenient because you have to disambiguate between Safe.listE and
Unsafe.listE, or make those functions more polymorphic (which makes
type errors worse). Another option would be if there were

newtype QThat (canIO :: Bool) (canReify :: Bool) (canNewName :: Bool)
   = QThat (TheRealQImplementation)

type Q = QThat True True True

listE :: Monad m => [m Exp] -> m Exp
listE = liftM ListE . sequence

reify :: Name -> QThat a True b Info
runIO :: IO a -> QThat True b c a

runQFFF :: QThat False False False a -> a
runQTFF :: QThat True False False a -> IO a


But I think that design would be a step in the direction of "harder to
reason about"

Regards,
Adam


On Fri, Jan 30, 2015 at 6:39 PM, Greg Weber <greg at gregweber.info> wrote:
> Hello GHC friends!
>
> I am starting up a proposal for variants of Template Haskell that restrict
> what operations are available. The goal is to make TH easier for users to
> reason about and to allow for an easier compilation story.
>
> Here is the proposal page:
> https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Restricted
>
> Right now the proposal does not have any details and the goal is to write
> out a clear specification.
> If this sounds interesting to you, let me know or leave some feedback on the
> wiki.
>
>
> Thanks,
> Greg Weber
>
>
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>


More information about the Glasgow-haskell-users mailing list