2

I'm pretty new to Haskell, and I'm trying to follow along with the Happstack Crash Course. I've done some of the examples, but when I tried the happstack-heist example, I got a strange compilation error. The file that I'm compiling looks like this:

module Main where

import Control.Applicative    ((<$>))
import Control.Monad          (msum)
import qualified Data.Text    as T
import Happstack.Server       ( dir, nullConf, nullDir, simpleHTTP
                              , seeOther, toResponse
                              )
import Happstack.Server.Heist (heistServe, initHeistCompiled)
import Heist                  (Splices, (##), getParamNode, noSplices)
import Heist.Compiled         (Splice, yieldRuntimeText)
import qualified Text.XmlHtml as X

-- | factorial splice
factSplice :: (Monad m) => Splice m
factSplice = do
  intStr <- T.unpack . X.nodeText <$> getParamNode
  let res = yieldRuntimeText $ do
        case reads intStr of
          [(n,[])] ->
            return (T.pack $ show $ product [1..(n :: Integer)])
          _ ->
            return (T.pack $ "Unable to parse " ++
                    intStr ++ " as an Integer.")
  return $ res

main :: IO ()
main = do
  heistState <- do
    r <- initHeistCompiled (T.pack "fact" ## factSplice) noSplices "."
    case r of
      (Left e) -> error $ unlines e
      (Right heistState) -> return $ heistState
  simpleHTTP nullConf $ msum
    [ dir "heist" $ heistServe heistState
    , nullDir >>
      seeOther "/heist/factorial" (toResponse "/heist/factorial")
    ]

The error is:

test.hs:37:36:
    Couldn't match expected type `happstack-server-7.3.9:Happstack.Server.Internal.Types.Response'
                with actual type `Happstack.Server.Internal.Types.Response'
    In the return type of a call of `toResponse'
    In the second argument of `seeOther', namely
      `(toResponse "/heist/factorial")'
    In the second argument of `(>>)', namely
      `seeOther "/heist/factorial" (toResponse "/heist/factorial")'

It seems as though something wants types that are prefixed with the package name and version number, which I don't understand. Both happstack-server and happstack-heist were installed with cabal install.

Rose Kunkel
  • 3,102
  • 2
  • 27
  • 53
  • Are you using a cabal sandbox? – bheklilr Jan 19 '15 at 21:31
  • I don't believe so, but I don't really know much about cabal. – Rose Kunkel Jan 19 '15 at 21:31
  • 1
    It looks like you have conflicting versions of a library installed and the compiler can't figure out which one to use (this is a sore point in the Haskell community and many are actively working on how to implement it better). A few versions ago, the `cabal` package added sandboxes (run `cabal sandbox init` to make one) that sets up a project-specific package database that you can install packages against. This lets you install the version of a library you need for each project and not pollute your global install. It's like virtualenv for Python. – bheklilr Jan 19 '15 at 21:34
  • More info at https://www.haskell.org/cabal/users-guide/installing-packages.html – bheklilr Jan 19 '15 at 21:35
  • Ah, it seems that happstack-heist pulled in happstack-server-7.3.9 when I already had happstack-server-7.4.0 installed. Thank you! – Rose Kunkel Jan 19 '15 at 21:39

1 Answers1

3

Welcome to cabal hell! What has happened is that when you installed the two packages for this example, happstack-server and happstack-heist, one of them pulled in a different version of the other than what was already installed on your system. When you tried to compile the example the compiler couldn't figure out which one to use. The solution to this is sandboxes. Just cd to the directory you have this example, run cabal sandbox init, then cabal install --dependencies-only. This will go grab all the dependencies for a project with a .cabal file and install them in a local .cabal-sandbox/ directory. When you run cabal build or cabal install the dependencies are pulled from this local folder, and any executable will be installed in .cabal-sandbox/bin.

bheklilr
  • 53,530
  • 6
  • 107
  • 163
  • I believe that for this to work you also have to remove the global packages in question. – Dan Jan 19 '15 at 21:56
  • @Dan That very well may be the case. I haven't had to deal with it since I started using sandboxes because I do my absolute best to not install anything globally that isn't in the platform. – bheklilr Jan 19 '15 at 21:57