[Haskell-cafe] Proposal for an extension: in-module namespaces

Aura Kelloniemi kaura.dev at sange.fi
Mon Mar 27 21:11:24 UTC 2017


Hello

I've been thinking about an extension to GHC which would allow creating new
module-like namespaces within normal Haskell modules. Because this kind of
namespacing system seems quite obvious to me, I ask if it has already been
proposed or discussed in detail?

The motivation:
1. It would assist in solving the 'pollution of namespace' -problem, of which
many Haskellers have complained.

2. It would allow building bundles of related modules which can be exported
from one module and then imported into others. This could result in
radically fewer import statements.

Rant:

I'm tired of writing

import qualified Data.ByteSstring as B
import qualified Data.ByteString.Builder as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Builder as BL
import qualified Data.HashMap.Strict as HM
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as BL

A huge portion of this appears in almos all my Haskell source files. If I
wrote my code in Python, I could condense all these imports to:


So, you see, it was zero lines of code.

I'm also tired of these patterns:
(personName p), (companyName c), (objectName o), ... and I hardly
prefer (name (p :: Person)), (name (c :: Company)) or (name (o ::Object))
using the DuplicateRecordFields syntax.

Proposal:

I propose that modules can contain named submodules. They can be exported and
imported just like anything else within a module, like this:

{-# LANGUAGE Submodules #-}
module Library.Things
    (qualified module Person,
     qualified module Company,
     personWorksInCompany
    ) where

-- import ...

qualified module Person (Person (..)) where
    -- This is the module Library.Things.Person. Submodules could possibly
    -- use some other keywords than 'qualified module'. Maybe just 'module',
    -- 'submodule' or 'namespace'.
    data Person = Person {
            name :: {-# UNPACK #-} !T.Text,
            id   :: {-# UNPACK #-} !Unique,
            ...
            }

-- Back in Library.Things
qualified module Company where
    data Company = Company {
        name      :: {-# UNPACK #-} !T.Text,
        employees :: {-# UNPACK #-} !V.Vector Unique,
        ...
        }

-- back in Library.Things again:

personWorksIn :: Person.Person -> Company.Company -> Bool
personWorksIn p c = Person.id p `elem` Company.employees c

-- ... end of Library.Things

And in another file:

{-# LANGUAGE Submodules #-}

-- The following demonstrates some ways of importing submodules. They are
-- not meant to be used like this in real code:
import Library.Things
import qualified Library.Things as Things

-- Now the submodules are also in scope and can be referred to like this:
person1 :: Person.Person
person2 :: Things.Person.Person
company :: Library.Things.Company.Company

-- And we also could have written: after importing Library.Things:
import Person
-- And now data type Person, selector name, etc. are in scope
-- If we also imported the Company module:
import Things.Company
-- selector 'name' would now be ambiguous and need qualification at use site.

-- Import lists would also work when bringing submodule contents to current
-- namespace. Like this:
import Library.Things hiding (module Company)
-- or
import qualified Library.Things (module Person)
-- Which would allow Library.THings.Person.Person to be used requiring use of
-- the fully qualified name.

-- But the following would not work if Library.Things was not already
-- imported:
import Library.Things.Person
-- because there is no such module, just submodule.

-- ... end of other file

Some projects probably would like to create a module like this:

module Imports
    (qualified module B,
     qualified module HM,
     qualified module T
    ) where

import Data.ByteString as B
-- ... and so forth ...

Open questions:

- Should there be a separate keyword for importing submodules, for example
  'use' or 'import namespace'?
- Would imports be allowed within submodules? I'd say no for importing other
  modules, but importing submodules could be ok.
- Would it be possible to extend submodules after their initial definition
  by just writing a new 'qualified module' block? I'd say yes, because
  submodules are just about namespacing. It is today possible to import
  many modules qualified and put them in the same namespace, like is often
  done.
- What do you fellow Haskellers think about this all?

-- 
Aura


More information about the Haskell-Cafe mailing list