How about using + and - prefixes instead of implicit and explicit clause? \begin{code} module T where
import Data.Map (Map, (\\)) import qualified Data.Map as M hiding (lookup) f :: (Ord k) => Map k v -> k -> Map k v f m k = m \\ M.singleton k (m M.! k) \end{code} the following import command would mean the same: import qualified Data.Map as M (+Map, -lookup, +singleton, +(\\)) On 7/8/08, Neil Mitchell <[EMAIL PROTECTED]> wrote: > Hi, > > It seems that the qualified import syntax is a bit awkward. At the > moment, its common to see: > > import qualified Data.Map as M > import Data.Map(Map) > > i.e. import a module, give it an alias (M), and put some things in the > current namespace (Map). > > Another way some people sometimes do it is: > > import qualified Data.Map as M > import Data.Map hiding (lookup) > > i.e. import a module, give it an alias (M), and exclude some things > from the current namespace. > > Both of these require two imports, yet feel like they should require > only one. It seems as though the import syntax more naturally promotes > security (preventing access to some functions), rather than > namespacing. > > I think a better design for namespacing might be: > > import Data.Map as M implicit (Map) > import Data.Map as M explicit (lookup) > > If this was the design, I'm not sure either qualified or hiding would > be necessary for namespacing. You'd get module names aligning up in > the same column after the import rather than being broken up with > qualified. You'd only need one import of a module for most purposes. > The hiding keyword might still be nice for lambdabot style > applications, but that is probably a secondary concern, and better > handled in other ways. > > Thoughts? Is this design flawed in some way? Does the existing design > have some compelling benefit I've overlooked? > > Thanks > > Neil > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe