Alex,

If I were you I'd dispense with "deriving(Read,Show)" in module Publisher,
and add an explicit instance for Read/Show on Publisher in PublisherDB.
That would solve your circularity problem.

Haskell does permit mutually recursive modules, but Hugs does not support
them, and GHC requires some help (described in the user manual; basically
you need to give it an "interface file" to get started).

Simon

> I wanted to represent a reasonably small list of Publishers.
> So I created:
> 
> > module Publisher where
> > data Publisher = Publisher { name::String, func::Registration->Bool}
> > data Registration = 
> >     Registration { data::String, pub::Publisher} deriving (Read,Show)
> 
> Notice that the Publisher data type includes functions so I can't just
> store these publishers as tuples in a database.  Instead I store
> information on each publisher in a file e.g. Yahoo.lhs CNN.lhs
> DoubleClick.lhs
> 
> > module Yahoo where
> > import Publisher
> > Yahoo = Publisher "Yahoo" (\x -> x)
> 
> Another file, PublisherDB.lhs, imports each of these 
> 
> > module PublisherDB where
> > import Yahoo
> > import DoubleClick
> > publishers = [("Yahoo",Yahoo),("DoubleClick",DoubleClick)]
> > getPublishers::String -> Publisher
> > getPublisher name = lookup publishers name
> 
> The trouble I have is that Registration requires me to define
> read/show for Publisher and read/show requires access to getPublisher
> which leads to a circular import problem:
> * getPublisher needs to be defined in PublisherDB because it requires a
> complete list of Publishers.  
> * PublisherDB imports each individual publisher (e.g. Yahoo, DoubleClick)
> Individual publishers import Publisher
> 
> For literate programming reasons, as well as general program modularity
> reasons, I would prefer not to merge all of these into a single large
> file.
> 
> Is there another way?
> 
> 
> -Alex-
> 
> ___________________________________________________________________
> S. Alexander Jacobson                 i2x Media  
> 1-212-697-0184 voice                  1-212-697-1427 fax



Reply via email to