recursive import

Brian Hulley brianh at metamilk.com
Sat Jun 3 05:38:11 EDT 2006


Serge D. Mechveliani wrote:
> People,
>
> Who knows, please, how usable are currently recursive module imports
> in Haskell, in GHC ?
> Is it essentially more difficult to `make' and support a project
> which has 50 modules, and half of all the module pairs import each
> other?
> Is recursive import in Haskell-98 ?

Newtype deriving doesn't work for recursive module imports, so I ended up 
just merging the two mutually recursive modules in my program into one 
module.

The example was something like:

module Control where
     import {-# SOURCE #-} Manager
     data Control ...
     -- functions using ManagerM

module Manager where
     import Control
     data MState = MState{keyboard:: !(Maybe Control)}
     newtype ManagerM a = ManagerM (StateT MState IO a)
         deriving (Monad, MonadIO,MonadState)

module Manager where  {- hs.boot -}
     data MState
     -- newtype decl gives a compiler error (I can't remember what it was)
     newtype ManagerM a = ManagerM (StateT MState IO a)
         deriving (Monad, MonadIO,MonadState)

So from the above experience I'd recommend not to use recursive modules at 
all.

Regards, Brian.

-- 
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 



More information about the Glasgow-haskell-users mailing list