[Haskell-cafe] Mystified by Cabal

Colin Paul Adams colin at colina.demon.co.uk
Sat Mar 7 12:18:24 EST 2009


I have just attempted Cabal-izing my program (splitting it into a
library and main program as well), and I'm mystified by some problems
I am having.

First, when I try to build the library I get:

[colin at susannah game-tree]$ runhaskell Setup build
Preprocessing library game-tree-1.0.0.0...
Building game-tree-1.0.0.0...

Data/Tree/Game/Negascout.hs:31:0: Unrecognised pragma
[1 of 2] Compiling Data.Tree.Game.Tree ( Data/Tree/Game/Tree.hs, dist/build/Data/Tree/Game/Tree.o )

Data/Tree/Game/Tree.hs:1:0:
    Failed to load interface for `Prelude':
      it is a member of package base-3.0.3.0, which is hidden

That mystifies me. Googling, it appears to be a common error in the
past, but none of the reasons apparently apply to my
case. Incidentally, Tree.hs imports nothing. It just looks like:

-- | Nodes in game trees
-- Copyright 2009 Colin Adams
--
-- This file is part of game-tree.
--
--  Game-tree is free software: you can redistribute it and/or modify
--  it under the terms of the GNU General Public License as published by
--  the Free Software Foundation, either version 3 of the License, or
--  (at your option) any later version.

--  Game-tree is distributed in the hope that it will be useful,
--  but WITHOUT ANY WARRANTY; without even the implied warranty of
--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
--  GNU General Public License for more details.

--  You should have received a copy of the GNU General Public License
--  along with game-tree.  If not, see <http://www.gnu.org/licenses/>.

module Data.Tree.Game.Tree where

-- | Nodes in a game search tree
class Tree a where
    -- | Is this a game-terminating node (e.g. checkmate)?
    is_terminal ::  a -> Bool
    -- | Heuristic value of node
    node_value :: a -> Int
    -- | Child nodes in the game tree (positions more deeply searched)
    children :: a -> [a]

So I couldn't build my program using runhaskell, as I couldn't install
the library. Instead, i tried ghc --make instead with the -idir
option. It looks in the right place, but still doesn't recognise the
module:

Chasing modules from: *Chu-shogi.hs

Generator.hs:27:7:
    Could not find module `Data.Tree.Game.Tree':
      locations searched:
        Data/Tree/Game/Tree.hs
        Data/Tree/Game/Tree.lhs
        dirs=../game-tree/Data/Tree/Game/Tree.hs
        dirs=../game-tree/Data/Tree/Game/Tree.lhs

What am I doing wrong?

Perhaps Cabal should be named Caballa instead.
-- 
Colin Adams
Preston Lancashire


More information about the Haskell-Cafe mailing list