[Haskell-cafe] lhs2tex build failure

Permjacov Evgeniy permeakra at gmail.com
Wed Dec 15 08:14:57 CET 2010


Hello!
I use ghc-7.0.1 and cabal 1.10.0 . When tried to install lhs2tex-1.16 I
got error in Setup.lhs:
===============================
Setup.hs:294:46:
    `programArgs' is not a (visible) field of constructor
`ConfiguredProgram'

Setup.hs:296:46:
    `programArgs' is not a (visible) field of constructor
`ConfiguredProgram'
===============================


s/programArgs/programDefaultArgs/ resolves error (cabal changed
ConfiguredProgram definition)

however, later I had another problem when compiling:
===============================
[16 of 19] Compiling MathPoly         ( MathPoly.lhs,
dist/build/lhs2TeX/lhs2TeX-tmp/MathPoly.o )

MathPoly.lhs:361:39:
    Ambiguous type variable `tok' in the constraint:
      (CToken tok) arising from a use of `mkFromTo'
    Probable fix: add a type signature that fixes these type variable(s)
    In the expression:
      mkFromTo
        fstack
        rn
        n
        rc
        [fromToken $ TeX False (indent (rn, rc) (n, c))]
        p
        ls
    In the expression:
      let
        rstack = dropWhile (\ (rc, _) -> rc >= c) stack
        (rn, rc) = findrel (n, c) rstack
        fstack = (c, l) : rstack
      in
        mkFromTo
          fstack
          rn
          n
          rc
          [fromToken $ TeX False (indent (rn, rc) (n, c))]
          p
          ls
    In a case alternative:
        Poly p@(((n, c), ts, ind) : rs)
          | first
          -> let
               rstack = dropWhile (\ (rc, _) -> ...) stack
               (rn, rc) = findrel ... rstack
               ....
             in
               mkFromTo
                 fstack
                 rn
                 n
                 rc
                 [fromToken $ TeX False (indent (rn, rc) (n, c))]
                 p
                 ls
          | c `elem` z -> mkFromTo stack n (n ++ "E") c ts rs ls
===============================

I cannot fix it on my own. Any suggestions ? Sorry, by I do not want
downgrade, if possible.




More information about the Haskell-Cafe mailing list