mirror of
https://github.com/github/semantic.git
synced 2024-11-27 12:57:49 +03:00
Merge remote-tracking branch 'origin/shelly-git-action' into alternative-schema
This commit is contained in:
commit
48a11d88e8
@ -192,7 +192,7 @@ defineSelf :: ( Carrier sig m
|
||||
=> Evaluator term address value m ()
|
||||
defineSelf = do
|
||||
let self = Declaration X.__self
|
||||
declare self ScopeGraph.Gensym Public emptySpan ScopeGraph.Unknown Nothing
|
||||
declare self ScopeGraph.Prelude Public emptySpan ScopeGraph.Unknown Nothing
|
||||
slot <- lookupSlot self
|
||||
assign slot =<< object =<< currentFrame
|
||||
|
||||
|
@ -87,7 +87,7 @@ instance Ord AccessControl where
|
||||
|
||||
|
||||
data Relation = Default | Instance | Prelude | Gensym
|
||||
deriving (Eq, Show, Ord, Generic, NFData)
|
||||
deriving (Bounded, Enum, Eq, Show, Ord, Generic, NFData)
|
||||
|
||||
instance Lower Relation where
|
||||
lowerBound = Default
|
||||
@ -119,8 +119,31 @@ instance HasSpan ReferenceInfo where
|
||||
span = lens refSpan (\r s -> r { refSpan = s })
|
||||
{-# INLINE span #-}
|
||||
|
||||
data Kind = TypeAlias | Class | Method | QualifiedAliasedImport | QualifiedExport | DefaultExport | Module | AbstractClass | Let | QualifiedImport | UnqualifiedImport | Assignment | RequiredParameter | PublicField | VariableDeclaration | Function | Parameter | Unknown | Identifier | TypeIdentifier | This | New | MemberAccess | Call
|
||||
deriving (Eq, Show, Ord, Generic, NFData)
|
||||
data Kind = AbstractClass
|
||||
| Assignment
|
||||
| Call
|
||||
| Class
|
||||
| DefaultExport
|
||||
| Function
|
||||
| Identifier
|
||||
| Let
|
||||
| MemberAccess
|
||||
| Method
|
||||
| Module
|
||||
| New
|
||||
| Parameter
|
||||
| PublicField
|
||||
| QualifiedAliasedImport
|
||||
| QualifiedExport
|
||||
| QualifiedImport
|
||||
| RequiredParameter
|
||||
| This
|
||||
| TypeAlias
|
||||
| TypeIdentifier
|
||||
| Unknown
|
||||
| UnqualifiedImport
|
||||
| VariableDeclaration
|
||||
deriving (Bounded, Enum, Eq, Show, Ord, Generic, NFData)
|
||||
|
||||
instance Lower Kind where
|
||||
lowerBound = Unknown
|
||||
@ -393,4 +416,4 @@ formatDeclaration = formatName . unDeclaration
|
||||
-- | The type of edge from a scope to its parent scopes.
|
||||
-- Either a lexical edge or an import edge in the case of non-lexical edges.
|
||||
data EdgeLabel = Lexical | Import | Export | Superclass
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
deriving (Bounded, Enum, Eq, Ord, Show, Generic, NFData)
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE RankNTypes, KindSignatures #-}
|
||||
{-# LANGUAGE DerivingStrategies, GeneralizedNewtypeDeriving, RankNTypes, KindSignatures #-}
|
||||
|
||||
-- | -- This technique is due to Oleg Grenrus: <http://oleg.fi/gists/posts/2019-03-21-flag.html>
|
||||
-- The implementation is clean-room due to unclear licensing of the original post.
|
||||
@ -10,7 +10,7 @@ module Data.Flag
|
||||
, choose
|
||||
) where
|
||||
|
||||
import Data.Coerce
|
||||
import Prologue
|
||||
|
||||
-- | To declare a new flag, declare a singly-inhabited type:
|
||||
-- @data MyFlag = MyFlag@
|
||||
@ -19,6 +19,8 @@ import Data.Coerce
|
||||
-- working with multiple flag values in flight, as the 'toBool' deconstructor provides a witness
|
||||
-- that you really want the given semantic flag value from the flag datum.
|
||||
newtype Flag (t :: *) = Flag Bool
|
||||
deriving stock (Eq, Show)
|
||||
deriving newtype NFData
|
||||
|
||||
-- | The constructor for a 'Flag'. You specify @t@ with a visible type application.
|
||||
flag :: t -> Bool -> Flag t
|
||||
|
Loading…
Reference in New Issue
Block a user