[Haskell-cafe] Proposal: Pragma EXPORT

Wvv vitea3v at rambler.ru
Tue Sep 17 01:09:17 CEST 2013


I suggest to add instead of (or with) export section Pragma EXPORT:

We have 3 values: public, abstract and private.
Data(with newtypes and types,..) could be public, like `Data(...)` or
abstract `Data`.
Other cases abstract = public.

{-# EXPORT <smth> #-} pragma is valid till next {-# EXPORT <smth> #-}.

We also can add local pragma: 
{-# EXPORT <smth> from #-}  ... {-# EXPORT <smth> untill #-}
Outside of block is rule of previous {-# EXPORT <smth> #-}.

Finally we also have rule for 1: {-# EXPORT <smth> one #-}

Example

module C where
{-# EXPORT public #-}
data A1...                
data A2...                
{-# EXPORT abstract from #-}
newtype A3...             
data A4...                
{-# EXPORT abstract until #-}
type A5...                
{-# EXPORT private one #-}
data A6...                

foo = ...                 
{-# EXPORT private one #-}
bar = ...                 
baz = ...                 
lorem = ...               
{-# EXPORT private #-}
insput ...                
dolor = ..                
sit = ...                 
{-# EXPORT public one #-}
amen = ...                
consectetur = ...         
adipisicing = ...         
elit = ...                
sed = ...                 
eiusmod  = ...            
tempor  = ...             
incididunt = ...          
{-# EXPORT public from #-}
ut = ...                  
labore = ...              
et = ...                  
{-# EXPORT public until #-}
dolore = ...              
magna = ...               
aliqua = ...  



is the same as 

module C (
  A1(..)
, A2(..)
, A3
, A4  
, A5(..)
, foo
, baz
, lorem
, amen
, ut
, labore
, et
) where 

data A1...                
data A2...                
newtype A3...             
data A4...                
type A5...                
data A6...                

foo = ...                 
bar = ...                 
baz = ...                 
lorem = ...               
insput ...                
dolor = ..                
sit = ...                 
amen = ...                
consectetur = ...         
adipisicing = ...         
elit = ...                
sed = ...                 
eiusmod  = ...            
tempor  = ...             
incididunt = ...          
ut = ...                  
labore = ...              
et = ...                  
dolore = ...              
magna = ...               
aliqua = ...        


We also could have complex pragma, like
{-# EXPORT inherit one foo #-}
bar=...

Backward compatibility:
module A where  ... ~  module A where {-# EXPORT public #-} ...
module B ( .... ) where ... ~ module B ( .... ) where {-# EXPORT private #-}
...



--
View this message in context: http://haskell.1045720.n5.nabble.com/Proposal-Pragma-EXPORT-tp5736547.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.



More information about the Haskell-Cafe mailing list