[Haskell-cafe] ghci module re exporting qualified as

Immanuel Litzroth immanuel.litzroth at gmail.com
Wed Nov 18 16:27:58 UTC 2020


You mean this?
#+BEGIN_SRC haskell :tangle T1.hs
module T1 where
import Data.Map as Map
#+END_SRC

that doesn't seem to do it:
#+BEGIN_EXAMPLE
λ⊢ :show modules
T1
λ⊢ :show imports
import T1 -- added automatically
import Prelude -- implicit
λ⊢ fromList

<interactive>:143:1-8: error: Variable not in scope: fromList
λ⊢ Map.fromList

<interactive>:144:1-12: error:
    Not in scope: ‘Map.fromList’
    No module named ‘Map’ is imported.
λ⊢ Data.Map.FromList

<interactive>:145:1-17: error:
    Not in scope: data constructor ‘Data.Map.FromList’
    No module named ‘Data.Map’ is imported.
λ⊢
#+END_EXAMPLE

On Wed, Nov 18, 2020 at 4:14 PM Henning Thielemann
<lemming at henning-thielemann.de> wrote:
>
>
> On Wed, 18 Nov 2020, Immanuel Litzroth wrote:
>
> > I'm trying to make a test module to run tests.
> > I want to import the test functionality + imported functionality in
> > the scope of the test module under ghci.
> > I also want to have short names in the  Test module for reexported
> > modules. I am using Data.Map and Data.Set ... so lot's of conflicting
> > exports.
> > Is this possible?
> >
> >
> > #+BEGIN_SRC haskell :tangle T1.hs
> > module T1 (
> >   module Data.Map) where
> > import qualified Data.Map
> > #+END_SRC
>
> Maybe omit the export list?



-- 
-- Researching the dual problem of finding the function that has a
given point as fixpoint.


More information about the Haskell-Cafe mailing list