GHC and Haskell 98
Henning Thielemann
lemming at henning-thielemann.de
Sat Jun 18 20:47:37 CEST 2011
On Fri, 17 Jun 2011, Simon Peyton-Jones wrote:
> BUT (A) means that this module becomes un-compilable:
> module Main where
> import Random
> import Data.List
> Why? Because 'Random' comes from 'haskell98' and 'Data.List' comes from 'base'. But if you say
> ghc -c Main.hs -package base -package haskell98
> then the (implicit) import of 'Prelude' will say "Ambiguous module name: Prelude", because it's exported by both 'base' and 'haskell98'. To fix this you have to change 'import Random' to 'import System.Random'. But the latter's API is different, so you may have to change the source code that uses it.
It would mean to change the import to
import System.Random
import Data.List
which is fairly easy and would cleanly separate between haskell98-based
code and base-based code.
If someone wants to mix haskell98 and base, then he might want to write:
{-# LANGUAGE NoImplicitPrelude #-}
import Random
import Data.List
import haskell98:Prelude
More information about the Libraries
mailing list