hirarchical modules
Iavor Diatchki
diatchki@cse.ogi.edu
Thu, 29 May 2003 11:57:00 -0700
hello,
Malcolm Wallace wrote:
> The "powers that be" are the compiler maintainers. If you can't
> persuade them (all) to adopt your proposal, then de facto it won't fly.
> But by-and-large, we are reasonable people. :-) You just need to
> be sufficiently persuasive.
hmm... what should i do? implement 50 libraries using the broken system
just to illustrate that it is broken?
>>suggestions on how to rewrite the imports/exports above more concisely
>>are welcome.
>
> The exports at least can be made shorter as follows.
>
> module Control.Monad.Experimental.State
> (State,
> ,runState
> ,runStateS
> ,module T) where
>
> import Control.Monad.Experimental.Identity
> import qualified Control.Monad.Experimental.StateT as S
> import qualified Control.Monad.Experimental.Trans as T
>
> type State s = S.StateT s Identity
>
> runState :: s -> State s a -> a
> runState s m = runIdentity (S.runState s m)
>
> runStateS :: s -> State s a -> (a,s)
> runStateS s m = runIdentity (S.runStateS s m)
yes, i was also thinking of that, and it works for this particular case.
i didn't like it becasue it means that i have to use qualified names
everywhere in the module. and i have to do that not to avoid clashes,
but so that i can write a shorter entry in the exoprt list. and don't
you think the code bellow is better? not to mention that moving the
library to a new localtion would be practically for free (as far as the
library is concerned, the users may still have to adjust their imports)
> module State (State,runState,runStateS,module Trans) where
>
> import Identity
> import StateT
> import Trans
>
> type State s = StateT s Identity
>
> runState :: s -> State s a -> a
> runState s m = runIdentity (StateT.runState s m)
>
> runStateS :: s -> State s a -> (a,s)
> runStateS s m = runIdentity (StateT.runStateS s m)
bye
iavor