Is it possible to import a type and the derived "show" function for it
without having to import all the type's constuctors?  For example, in
the following I attempt to import just Lexeme into Token as the
internal details of Lexeme should not be known to Token :-

>module Lexeme where
>data Lexeme = Symbol_Lexeme Symbol | Int_Lexeme | ...
>  deriving(Eq,Text)

>module Token where
>import Lexeme(Lexeme)
>data Token = Token Lexeme ...
>  deriving(Text)

However, HBC claims that Lexeme is not an instance of Text when I
compile the Token module.  This seems quite fair since I'm trying to
use Lexeme as an ADT and if it allowed the above it would break
abstraction.  The question is, how do I import the derived functions
for "show" ... etc. so that I can derive Text for Token?

I tried :-

>import Lexeme(Lexeme,shows)

and combinations thereof, but with no success.

The solution I'm using at the moment is to define the function
"show_lexeme" in the Lexeme module, import it into the Token module
and then explicitly make Token an instance of Text i.e. 

>import Lexeme(Lexeme,show_lexeme)

>instance Text Token where
>  showsPrec _ (Token l ...) = show_lexeme l . ...
>  ...

However, this is tedious if Token has lots of alternatives.  Anyone
have a better way?

bevan

Reply via email to