ghci module re exporting qualified as

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 works but no browsing info shows up #+BEGIN_EXAMPLE λ⊢ :show modules T1 .... λ⊢ :show imports import T1 -- added automatically import Prelude -- implicit λ⊢ fromList [] <interactive>:114:1-8: error: Variable not in scope: fromList ∷ [a0] → t λ⊢ Data.Map.fromList [] fromList [] λ⊢ :browse! T1 λ⊢ #+END_EXAMPLE #+BEGIN_SRC haskell :tangle T2.hs module T2 ( module Map) where import qualified Data.Map as Map #+END_SRC #+BEGIN_EXAMPLE λ⊢ :show modules T2 :show imports import T2 -- added automatically import Prelude -- implicit λ⊢ fromList [] <interactive>:119:1-8: error: Variable not in scope: fromList ∷ [a0] → t λ⊢ Map.fromList [] <interactive>:120:1-12: error: Not in scope: ‘Map.fromList’ No module named ‘Map’ is imported. λ⊢ Data.Map.fromList [] fromList [] λ⊢ :browse! T2 λ⊢ #+END_EXAMPLE -- -- Researching the dual problem of finding the function that has a given point as fixpoint.

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?

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
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.

On Wed, 18 Nov 2020, Immanuel Litzroth wrote:
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
Hm. Was the module compiled? You can only benefit from imports, if the module is interpreted.

I'm under the impression that they want to export names qualified, but qualification only happens on import. If you export names from an imported module, they will appear to be from the imported module, not the original. On Wed, Nov 18, 2020, 11:32 Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Wed, 18 Nov 2020, Immanuel Litzroth wrote:
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
Hm. Was the module compiled? You can only benefit from imports, if the module is interpreted._______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Wed, 18 Nov 2020, Brandon Allbery wrote:
I'm under the impression that they want to export names qualified, but qualification only happens on import. If you export names from an imported module, they will appear to be from the imported module, not the original.
That's true for compiled Haskell. But I know I have already re-used the qualifications within interpreted modules in GHCi.
participants (3)
-
Brandon Allbery
-
Henning Thielemann
-
Immanuel Litzroth