[Haskell-cafe] TH not compiling when writing the code directly does

Michael Jones mike at proclivis.com
Thu Mar 12 06:07:31 UTC 2015


I’m stuck getting a TH expansion to compile. When I take the generated code and compile it directly, it is fine. But when expanding and compiling, it fails.

The problem seems related to instanceD, where I provide the type as:

 (appT (appT (conT devName') (varT $ mkName "Word8")) (varT $ mkName "BV”))

which expands to:

IDENTIFICATION__MODEL_ID Word8 BV

No matter what I put for the second type (BV), it generates the compile error. For example, Word8 or Word16 gives the same error.

But if I take the resulting expression and just put it into the file and compile, it compiles fine. So something about expansion is causing the problem.

Is there some more correct way to make the expression rather than nesting two appT?

Any ideas?

Note: the generation of the functions with (map (\f -> returnQ f) (concat funs)) is ugly in my opinion. I could not find the right way to express this. So all ideas welcome.

Mike

GEN DEC
--------------

makeInstance :: String -> [String] -> Q [Dec]
makeInstance devName regNames = do
  let devName' = mkName devName
  let regNames' = map mkName regNames
  let ctx = return [] :: Q [Pred]
  funs <- mapM (\regName -> [d| $(varP regName) = $(varE $ mkName "writeReadField") $(stringE $ nameBase regName)(get fi) (set fi)
                                  where
                                    fi = $(conE $ mkName "FieldInfo") 3 1
                                    get info = $(varE $ mkName "getValue") info
                                    set info = $(varE $ mkName "setValue") info
                              |]) regNames'
  instance_ <- instanceD 
    ctx
    (appT (appT (conT devName') (varT $ mkName "Word8")) (varT $ mkName "BV"))
    (map (\f -> returnQ f) (concat funs))
  return [instance_]


COMPILE ERROR
-------------------------

src/TestFields.hs:175:3:
    Illegal type variable name: ‘BV’
    When splicing a TH declaration:
      instance IDENTIFICATION__MODEL_ID Word8 BV
    where id = writeReadField "id" (get_0 fi_1) (set_2 fi_1)
              where fi_1 = FieldInfo 3 1
                    get_0 info_3 = getValue info_3
                    set_2 info_4 = setValue info_4
          ids = writeReadField "ids" (get_5 fi_6) (set_7 fi_6)
              where fi_6 = FieldInfo 3 1
                    get_5 info_8 = getValue info_8
                    set_7 info_9 = setValue info_9




More information about the Haskell-Cafe mailing list