[Hugs-users] Setup.hs for base

Ian Lynagh igloo at earth.li
Tue Nov 21 09:30:22 EST 2006


Hi all,

I'm trying to get GHC to build the libraries with cabal, but without
breaking the hugs build. For base I have a Setup.hs (attached, along
with the modified base.cabal) which does some kludging to work around
the fact that base is different for different impls. After a bit of
digging I altered libraries/tools/convert_libraries to use a
Setup.hs/Setup.lhs if it exists rather than always using
packages/Cabal/examples/hapax.hs, but I now get:

+ ../../src/runhugs -98 Setup.hs configure --verbose --hugs --prefix=/asd --scratchdir=../../hugsdir/packages/base --with-hsc2hs=../../libraries/tools/hsc2hs --with-cpphs=../../libraries/tools/cpphs --with-compiler=../../src/ffihugs
runhugs: Error occurred
ERROR "./Data/List.hs" - Module "Data.List" already loaded

so I am rather stuck.


Thanks
Ian

-------------- next part --------------

{-
We need to do some ugly hacks here as base mix of portable and
unportable stuff, as well as home to some GHC magic.
-}

module Main (main) where

import Data.List
import Distribution.Simple
import Distribution.PackageDescription
import Distribution.PreProcess
import Distribution.Setup
import Distribution.Simple.LocalBuildInfo
import System.Environment

main :: IO ()
main = do args <- getArgs
          let (ghcArgs, args') = extractGhcArgs args
          let hooks = defaultUserHooks {
                  buildHook = add_ghc_options ghcArgs
                            $ filter_modules_hook
                            $ buildHook defaultUserHooks,
                  instHook = filter_modules_hook $ instHook defaultUserHooks }
          withArgs args' $ defaultMainWithHooks hooks

extractGhcArgs :: [String] -> ([String], [String])
extractGhcArgs args
 = let f [] = ([], [])
       f (x:xs) = case f xs of
                      (ghcArgs, otherArgs) ->
                          case removePrefix "--ghc-option=" x of
                              Just ghcArg ->
                                  (ghcArg:ghcArgs, otherArgs)
                              Nothing ->
                                  (ghcArgs, x:otherArgs)
   in f args

removePrefix :: String -> String -> Maybe String
removePrefix "" ys = Just ys
removePrefix (x:xs) (y:ys)
 | x == y = removePrefix xs ys
 | otherwise = Nothing

type Hook a = PackageDescription -> LocalBuildInfo -> Maybe UserHooks -> a
           -> IO ()

add_ghc_options :: [String] -> Hook a -> Hook a
add_ghc_options args f pd lbi muhs x
 = do let lib' = case library pd of
                     Just lib ->
                         let bi = libBuildInfo lib
                             opts = options bi ++ [(GHC, args)]
                             bi' = bi { options = opts }
                         in lib { libBuildInfo = bi' }
                     Nothing -> error "Expected a library"
          pd' = pd { library = Just lib' }
      f pd' lbi muhs x

filter_modules_hook :: Hook a -> Hook a
filter_modules_hook f pd lbi muhs x
 = let build_filter = case compilerFlavor $ compiler lbi of
                          GHC -> forGHCBuild
                          _ -> isPortableBuild
       lib' = case library pd of
                  Just lib ->
                      let ems = filter build_filter (exposedModules lib)
                      in lib { exposedModules = ems }
                  Nothing -> error "Expected a library"
       pd' = pd { library = Just lib' }
   in f pd' lbi muhs x

isPortableBuild :: String -> Bool
isPortableBuild s
 | "GHC" `isPrefixOf` s = False
 | "Data.Generics" `isPrefixOf` s = False
 | otherwise = s `elem` ["Control.Parallel.Strategies",
                         "Foreign.Concurrent",
                         "System.Process"]

forGHCBuild :: String -> Bool
forGHCBuild = ("GHC.Prim" /=)

-------------- next part --------------
name:		base
version:	2.0
license:	BSD3
license-file:	LICENSE
maintainer:	libraries at haskell.org
synopsis:	Basic libraries
description:
	This package contains the Prelude and its support libraries,
	and a large collection of useful libraries ranging from data
	structures to parsing combinators and debugging utilities.
exposed-modules:
	Control.Applicative,
	Control.Arrow,
	Control.Concurrent,
	Control.Concurrent.Chan,
	Control.Concurrent.MVar,
	Control.Concurrent.QSem,
	Control.Concurrent.QSemN,
	Control.Concurrent.SampleVar,
	Control.Exception,
	Control.Monad,
	Control.Monad.Fix,
	Control.Monad.Instances,
	Control.Monad.ST,
	Control.Monad.ST.Lazy,
	Control.Monad.ST.Strict,
	Control.Parallel,
	Control.Parallel.Strategies,
	Data.Array,
	Data.Array.Base,
	Data.Array.Diff,
	Data.Array.IArray,
	Data.Array.IO,
	Data.Array.IO.Internals,
	Data.Array.MArray,
	Data.Array.ST,
	Data.Array.Storable,
	Data.Array.Unboxed,
	Data.Bits,
	Data.Bool,
	Data.ByteString,
	Data.ByteString.Char8,
    Data.ByteString.Lazy
    Data.ByteString.Lazy.Char8
    Data.ByteString.Base
    Data.ByteString.Fusion
	Data.Char,
	Data.Complex,
	Data.Dynamic,
	Data.Either,
	Data.Eq,
	Data.Foldable,
	Data.Fixed,
	Data.FunctorM,
	Data.Generics,
	Data.Generics.Aliases,
	Data.Generics.Basics,
	Data.Generics.Instances,
	Data.Generics.Schemes,
	Data.Generics.Text,
	Data.Generics.Twins,
	Data.Graph,
	Data.HashTable,
	Data.IORef,
	Data.Int,
	Data.IntMap,
	Data.IntSet,
	Data.Ix,
	Data.List,
	Data.Maybe,
	Data.Map,
	Data.Monoid,
	Data.Ord,
	Data.PackedString,
	Data.Queue,
	Data.Ratio,
	Data.STRef,
	Data.STRef.Lazy,
	Data.STRef.Strict,
	Data.Sequence,
	Data.Set,
	Data.Tree,
	Data.Traversable,
	Data.Tuple,
	Data.Typeable,
	Data.Unique,
	Data.Version,
	Data.Word,
	Debug.Trace,
	Foreign,
	Foreign.C,
	Foreign.C.Error,
	Foreign.C.String,
	Foreign.C.Types,
	Foreign.Concurrent,
	Foreign.ForeignPtr,
	Foreign.Marshal,
	Foreign.Marshal.Alloc,
	Foreign.Marshal.Array,
	Foreign.Marshal.Error,
	Foreign.Marshal.Pool,
	Foreign.Marshal.Utils,
	Foreign.Ptr,
	Foreign.StablePtr,
	Foreign.Storable,
	GHC.Arr,
	GHC.Base,
	GHC.Conc,
	GHC.ConsoleHandler,
	GHC.Dotnet,
	GHC.Dynamic,
	GHC.Enum,
	GHC.Err,
	GHC.Exception,
	GHC.Exts,
	GHC.Float,
	GHC.ForeignPtr,
	GHC.Handle,
	GHC.IO,
	GHC.IOBase,
	GHC.Int,
	GHC.List,
	GHC.Num,
	GHC.PArr,
	GHC.Pack,
	GHC.Prim,
	GHC.PrimopWrappers,
	GHC.Ptr,
	GHC.Read,
	GHC.Real,
	GHC.ST,
	GHC.STRef,
	GHC.Show,
	GHC.Stable,
	GHC.Storable,
	GHC.TopHandler,
	GHC.Unicode,
	GHC.Weak,
	GHC.Word,
	Numeric,
	Prelude,
	System.Cmd,
	System.Console.GetOpt,
	System.CPUTime,
	System.Directory,
	System.Directory.Internals,
	System.Environment,
	System.Exit,
	System.IO,
	System.IO.Error,
	System.IO.Unsafe,
	System.Info,
	System.Locale,
	System.Mem,
	System.Mem.StableName,
	System.Mem.Weak,
	System.Posix.Internals,
	System.Posix.Signals,
	System.Posix.Types,
	System.Process,
	System.Process.Internals,
	System.Random,
	System.Time,
	Text.ParserCombinators.ReadP,
	Text.ParserCombinators.ReadPrec,
	Text.PrettyPrint,
	Text.PrettyPrint.HughesPJ,
	Text.Printf,
	Text.Read,
	Text.Read.Lex,
	Text.Show,
	Text.Show.Functions
include-dirs:	include, ../../ghc/includes
includes:	HsBase.h
extensions:	CPP


More information about the Hugs-Users mailing list