example for recursive import
Serge D. Mechveliani
mechvel at botik.ru
Wed Jun 7 06:52:22 EDT 2006
Concering adding an argument to a function intstead of using
recursive import, Christian Maeder wrote on Jun 07, 2006
> >I do not know. Will the source look natural?
>
> That depends on g and h, a generalization can look natural or artifical.
>
> >Can you explain this more precisely: what to change in f, g, and h
> >?
> >Let it be f, g, h :: Int -> Int.
>
> new situtation:
>
> module F where
> import G
> import H
>
> f :: Int -> Int
>
> f x = ... g f (... x ...) ... h f (... x ...)
>
> module G where
>
> g :: (Int -> Int) -> Int -> Int
>
> g f x = ...
>
> module H ...
>
Thank you for pointing at such possibility.
Still I think, such a program looks more natural when it uses
recursive modules rather than adding extra arguments to functions.
Also this is not only for functions.
Instances often use each other in a recursive way:
module A where ... instance Foo1 Data1 where ...
module B where ... instance Foo2 Data2 where ...
module C where ... instance Foo3 Data3 where ...
-----------------
Serge Mechveliani
mechvel at botik.ru
More information about the Glasgow-haskell-users
mailing list