Allow applications to appear in function OR module contexts

This commit is contained in:
Frederik Hanghøj Iversen 2019-10-11 16:55:48 +02:00
parent 04253ffef8
commit 38098122f3
4 changed files with 35 additions and 23 deletions

View file

@ -51,3 +51,5 @@ So for instance. The monomorphic type `Parser Function` is a
procedure that generates a value of type `Function`: procedure that generates a value of type `Function`:
*** Live coding *** Live coding
Define an instance for `FromJSON` for `Function`. Define an instance for `FromJSON` for `Function`.
Define an instance for `FromJSON` for `Definition`.

View file

@ -25,6 +25,7 @@ module M
end end
module K module K
f
end end
f(2) f(2)

View file

@ -61,10 +61,10 @@ instance ToJSON Definition where
x -> x x -> x
instance FromJSON Definition where instance FromJSON Definition where
parseJSON val parseJSON v
= (DefModule <$> parseJSON val) = (DefModule <$> parseJSON v)
<|> (DefFunction <$> parseJSON val) <|> (DefFunction <$> parseJSON v)
<|> (DefSend <$> parseJSON val) <|> (DefSend <$> parseJSON v)
newtype Namespace = Namespace [Name] newtype Namespace = Namespace [Name]

View file

@ -8,6 +8,7 @@ module Rubyhs.References
, Env(..) , Env(..)
, Result(..) , Result(..)
, Namespace(..) , Namespace(..)
, Context(..)
) where ) where
import Frelude import Frelude
@ -21,8 +22,6 @@ import Data.Aeson ((.=))
import qualified Data.Aeson as Aeson import qualified Data.Aeson as Aeson
import Data.List import Data.List
import Data.HashMap.Strict (HashMap) import Data.HashMap.Strict (HashMap)
import Data.Text.Prettyprint.Doc.Render.Text (renderStrict)
import Data.Text.Prettyprint.Doc (layoutCompact)
import Data.Set (Set) import Data.Set (Set)
import qualified Data.Set as Set import qualified Data.Set as Set
@ -68,21 +67,26 @@ prettyFQN FQN{namespace, name} = case namespace of
prettyNamespace :: Namespace -> Text prettyNamespace :: Namespace -> Text
prettyNamespace = convertString . intercalate "::" . fmap convertString . reverse . toList prettyNamespace = convertString . intercalate "::" . fmap convertString . reverse . toList
data Context = ContextFun FQN | ContextMod Namespace
deriving stock instance Eq Context
deriving stock instance Ord Context
class Monad m => MyMonad (m :: Type -> Type) where class Monad m => MyMonad (m :: Type -> Type) where
declaration :: FQN -> m () declaration :: FQN -> m ()
application :: Namespace -> FQN -> m () application :: Context -> FQN -> m ()
getContext :: m Namespace getContext :: m Context
writeContext :: Namespace -> m () writeContext :: Context -> m ()
data Env = Env data Env = Env
{ declarations :: Set FQN { declarations :: Set FQN
, applications :: Map Namespace (Set FQN) , applications :: Map Context (Set FQN)
, context :: Namespace , context :: Context
} }
data Result = Result data Result = Result
{ declarations :: Set FQN { declarations :: Set FQN
, applications :: Map Namespace (Set FQN) , applications :: Map Context (Set FQN)
} }
instance ToJSON Result where instance ToJSON Result where
toJSON Result{declarations,applications} = Aeson.object toJSON Result{declarations,applications} = Aeson.object
@ -91,13 +95,12 @@ instance ToJSON Result where
] ]
where where
f x = fromList @(HashMap _ _) $ go <$> toList x f x = fromList @(HashMap _ _) $ go <$> toList x
go (x, y) = (renderStrict $ layoutCompact $ pretty x, y) go (x, y) = (prettyContext x, y)
instance Semigroup Env where prettyContext :: Context -> Text
Env a0 a1 a2 <> Env b0 b1 b2 = Env (a0 <> b0) (a1 <> b1) (a2 <> b2) prettyContext = \case
ContextFun q -> prettyFQN q
instance Monoid Env where ContextMod ns -> prettyNamespace ns
mempty = Env mempty mempty mempty
instance MyMonad (State Env) where instance MyMonad (State Env) where
declaration q = modify go declaration q = modify go
@ -113,7 +116,7 @@ instance MyMonad (State Env) where
where where
go env = env { context = q } go env = env { context = q }
updateContext :: MyMonad m => (Namespace -> Namespace) -> m () updateContext :: MyMonad m => (Context -> Context) -> m ()
updateContext f = getContext >>= \c -> writeContext (f c) updateContext f = getContext >>= \c -> writeContext (f c)
locally :: MyMonad m => m a -> m a locally :: MyMonad m => m a -> m a
@ -126,7 +129,8 @@ locally act = do
appendToContext :: MyMonad m => Name -> m () appendToContext :: MyMonad m => Name -> m ()
appendToContext n = updateContext go appendToContext n = updateContext go
where where
go q = name2ns n <> q go (ContextMod q) = ContextMod $ name2ns n <> q
go _ = error "Cannot append module to context in function context"
name2ns :: Name -> Namespace name2ns :: Name -> Namespace
name2ns (Name o) = go o name2ns (Name o) = go o
@ -144,7 +148,8 @@ class References a where
references :: Block -> Result references :: Block -> Result
references q = Result{declarations, applications} references q = Result{declarations, applications}
where where
Env{declarations,applications} = execState (entries @_ @(State Env) q) mempty Env{declarations,applications} = execState (entries @_ @(State Env) q) emptyEnv
emptyEnv = Env mempty mempty (ContextMod mempty)
instance References Block where instance References Block where
entries :: forall m . MyMonad m => Block -> m () entries :: forall m . MyMonad m => Block -> m ()
@ -163,8 +168,12 @@ instance References Module where
instance References Function where instance References Function where
entries Function{name, block} = do entries Function{name, block} = do
namespace <- getContext namespace <- getContext >>= \case
ContextMod c -> pure c
_ -> error "Cannot have a function declaration in a function context"
declaration $ qual namespace name declaration $ qual namespace name
locally $ do
writeContext (ContextFun $ qual namespace name)
entries block entries block
qual :: Namespace -> Name -> FQN qual :: Namespace -> Name -> FQN