Skip to content

Commit

Permalink
Fixes #1484
Browse files Browse the repository at this point in the history
  • Loading branch information
yav committed Dec 20, 2022
1 parent e0d5952 commit bf99953
Show file tree
Hide file tree
Showing 4 changed files with 58 additions and 7 deletions.
40 changes: 33 additions & 7 deletions src/Cryptol/TypeCheck/Monad.hs
Original file line number Diff line number Diff line change
Expand Up @@ -857,7 +857,7 @@ lookupModule iname =
do localMods <- getScope mSubmodules
case Map.lookup m localMods of
Just names ->
do n <- genIfaceWithNames names <$> getCurScope
do n <- genIfaceWithNames names <$> getCurDecls
pure (If.ifaceForgetName n)

Nothing ->
Expand Down Expand Up @@ -1128,12 +1128,38 @@ getScope f =
rw <- IM get
pure (sconcat (f (iExtScope ro) :| map f (iScope rw)))

getCurScope :: InferM (ModuleG ScopeName)
getCurScope =
do rw <- IM get
case iScope rw of
m : _ -> pure m
[] -> panic "getCurScope" ["No current scope."]
getCurDecls :: InferM (ModuleG ())
getCurDecls =
do ro <- IM ask
rw <- IM get
pure (foldr (\m1 m2 -> mergeDecls (forget m1) m2)
(forget (iExtScope ro)) (iScope rw))

where
forget m = m { mName = () }

mergeDecls m1 m2 =
Module
{ mName = ()
, mDoc = Nothing
, mExports = mempty
, mParams = mempty
, mParamTypes = mempty
, mParamConstraints = mempty
, mParamFuns = mempty
, mNested = mempty

, mTySyns = uni mTySyns
, mNewtypes = uni mNewtypes
, mPrimTypes = uni mPrimTypes
, mDecls = uni mDecls
, mSubmodules = uni mSubmodules
, mFunctors = uni mFunctors
, mSignatures = uni mSignatures
}
where
uni f = f m1 <> f m2


addDecls :: DeclGroup -> InferM ()
addDecls ds =
Expand Down
19 changes: 19 additions & 0 deletions tests/modsys/functors/T037.cry
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
module T037 where

interface submodule I where
x : [8]

submodule F where
import interface submodule I
y = x + 1

submodule P where
x = 11

submodule X where
submodule M = submodule F { submodule P }
import submodule M

z = y

import submodule X
2 changes: 2 additions & 0 deletions tests/modsys/functors/T037.icry
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
:load T037.cry
z
4 changes: 4 additions & 0 deletions tests/modsys/functors/T037.icry.stdout
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
Loading module Cryptol
Loading module Cryptol
Loading module T037
0x0c

0 comments on commit bf99953

Please sign in to comment.