Created
March 28, 2018 15:16
-
-
Save jchia/6e32401d5afde951f0159c5ecca7fd9b to your computer and use it in GitHub Desktop.
How to fix Lib4.hs:10?
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE DataKinds, FlexibleInstances, TemplateHaskell, TypeFamilies, TypeOperators #-} | |
module Lib3 (partQ) where | |
import ClassyPrelude hiding (IsMap, Map) | |
import Data.Proxy | |
import GHC.TypeLits | |
import Language.Haskell.TH | |
import Labels | |
class KnownSymbol a => IsGridFieldName (a :: Symbol) where | |
type GridFieldType a | |
instance IsGridFieldName "x" where | |
type GridFieldType "x" = Int | |
instance IsGridFieldName "y" where | |
type GridFieldType "y" = Bool | |
partQ :: forall s. (IsGridFieldName s) => Proxy s -> TypeQ | |
partQ proxy = | |
[t|$(litT . strTyLit . symbolVal $ proxy) := GridFieldType s|] |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE DataKinds, OverloadedLabels, TemplateHaskell #-} | |
module Lib4 where | |
import ClassyPrelude | |
import Labels | |
import Lib3 (partQ) | |
-- ERROR: The exact Name 's' is not in scope. Probable cause: you used a unique Template Haskell name ... | |
type Foo = ($(partQ #x), $(partQ #y)) | |
foo :: Foo | |
foo = (#x := 1, #y := False) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment
Lib4.hs:10 uses the splice from Lib3.hs:22, which refers to type variable s, which I expect to be type-level strings "x" and "y" respectively for the two parQ splices, so that GridFieldType s is Int and Bool respectively, but GHC won't let me use s.