Hiding top level declaration with tilde
Herbert Valerio Riedel
hvr at gnu.org
Thu Jan 9 09:30:45 UTC 2014
On 2014-01-09 at 08:46:28 +0100, Ramin Honary wrote:
[...]
> So as we all know, when there is no exports list in a module declaration,
> everything in the top level is exported by default.
>
> If you provide an exports list, everything is hidden except what you
> declare in the exports list.
Btw, that's almost symmetric with an import statement lacking an
'impspec' and one providing a non-"hiding" 'impspec';
Otoh I've been wondering for some time why the export declaration
doesn't support the "hiding" modifier, e.g.
module M hiding (A, B(..), C(..), abc) where
...
to make the export declaration a bit more symmetric with 'impsec' on the
import side.
> I think a good way to hide things without an exports list might be to
> simply prefix the type signature with a tilde character. For example:
>
> module M where
>
> ~type A = ()
> ~newtype B = B ()
> ~data C = MkB1 () | MkB2 ()
>
> ~abc :: ()
> abc = ()
>
> increment :: Int -> Int
> increment = (+1)
>
> So in this example, the module M would only export the "increment"
> function, everything else would be hidden.
So in order to hide a function/value this way, you have to write
a type-signature for 'abc', in order to be able to declare 'abc'
non-exported?
[...]
Cheers,
hvr
More information about the Haskell-prime
mailing list