1
1
mirror of https://github.com/github/semantic.git synced 2024-11-28 01:47:01 +03:00

Replace Core.Stack with Syntax.Stack.

This commit is contained in:
Rob Rix 2019-10-10 15:19:04 -04:00
parent 7df71e359e
commit 5b378da075
No known key found for this signature in database
GPG Key ID: F188A01508EA1CF7
5 changed files with 2 additions and 46 deletions

View File

@ -55,7 +55,6 @@ library
Core.Loc
Core.Name
Core.Scope
Core.Stack
build-depends:
algebraic-graphs ^>= 0.3
, base >= 4.12 && < 5

View File

@ -40,7 +40,6 @@ import Control.Effect.Carrier
import Core.Loc
import Core.Name
import Core.Scope
import Core.Stack
import Data.Bifunctor (Bifunctor (..))
import Data.Foldable (foldl')
import Data.List.NonEmpty (NonEmpty (..))
@ -49,6 +48,7 @@ import Data.Text (Text)
import GHC.Generics (Generic1)
import GHC.Stack
import Source.Span
import Syntax.Stack
import Syntax.Module
import Syntax.Term

View File

@ -12,11 +12,11 @@ import Core.Core
import Core.File
import Core.Name
import Core.Scope
import Core.Stack
import Data.Foldable (toList)
import Data.Text.Prettyprint.Doc
import qualified Data.Text.Prettyprint.Doc.Render.String as Pretty
import qualified Data.Text.Prettyprint.Doc.Render.Terminal as Pretty
import Syntax.Stack
import Syntax.Term
showCore :: Term Core Name -> String

View File

@ -12,15 +12,12 @@ module Core.Scope
, instantiate1
, instantiate
, instantiateEither
, unprefix
, unprefixEither
) where
import Control.Applicative (liftA2)
import Control.Effect.Carrier
import Control.Monad ((>=>), guard)
import Control.Monad.Trans.Class
import Core.Stack
import Data.Function (on)
import Syntax.Module
@ -108,25 +105,3 @@ instantiate f = instantiateEither (either f pure)
instantiateEither :: Monad f => (Either a b -> f c) -> Scope a f b -> f c
instantiateEither f = unScope >=> incr (f . Left) (>>= f . Right)
-- | Unwrap a (possibly-empty) prefix of @a@s wrapping a @t@ using a helper function.
--
-- This allows us to peel a prefix of syntax, typically binders, off of a term, returning a stack of prefixing values (e.g. variables) and the outermost subterm rejected by the function.
unprefix
:: (Int -> t -> Maybe (a, t)) -- ^ A function taking the 0-based index into the prefix & the current term, and optionally returning a pair of the prefixing value and the inner subterm.
-> t -- ^ The initial term.
-> (Stack a, t) -- ^ A stack of prefixing values & the final subterm.
unprefix from = unprefixEither (matchMaybe . from)
-- | Unwrap a (possibly-empty) prefix of @a@s wrapping a @b@ within a @t@ using a helper function.
--
-- Compared to 'unprefix', this allows the helper function to extract inner terms of a different type, for example when @t@ is a right @b@-module.
unprefixEither
:: (Int -> t -> Either (a, t) b) -- ^ A function taking the 0-based index into the prefix & the current term, and returning either a pair of the prefixing value and the next inner subterm of type @t@, or the final inner subterm of type @b@.
-> t -- ^ The initial term.
-> (Stack a, b) -- ^ A stack of prefixing values & the final subterm.
unprefixEither from = go (0 :: Int) Nil
where go i bs t = case from i t of
Left (b, t) -> go (succ i) (bs :> b) t
Right b -> (bs, b)

View File

@ -1,18 +0,0 @@
{-# LANGUAGE DeriveTraversable #-}
module Core.Stack
( Stack(..)
) where
data Stack a
= Nil
| Stack a :> a
deriving (Eq, Foldable, Functor, Ord, Show, Traversable)
infixl 4 :>
instance Semigroup (Stack a) where
xs <> Nil = xs
xs <> (ys :> y) = (xs <> ys) :> y
instance Monoid (Stack a) where
mempty = Nil