On 2008 Sep 6, at 19:09, John Smith wrote:
Ryan Ingram wrote:
module Prob where
import qualified Data.Map as M
....
newtype Prob p a = Prob { runProb :: [(a,p)] }
combine :: (Num p, Ord a) => Prob p a -> Prob p a
combine m = Prob $
   M.assocs $
   foldl' (flip $ uncurry $ M.insertWith (+)) M.empty $
   runProb m
Do you see it?  All those "M." just seem dirty to me, especially
because the compiler should be able to deduce them from the types of
the arguments.

May I humbly suggest a much simpler solution to your problem: if an identifier is ambiguous, the compiler will use the last import. So, in your example, the compiler will assume that any instance of empty is Data.Map.empty

I don't like that idea very much; if I reorder my imports the program semantics suddenly change?

Some means of using an imported module as the default namespace, and requiring the Prelude to be qualified, may also help.

You can already do this by importing Prelude explicitly, possibly with the NoImplicitPrelude language option.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon university    KF8NH


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to