mirror of
https://github.com/github/semantic.git
synced 2024-12-29 18:06:14 +03:00
De-prologuify the Typescript syntax modules.
This commit is contained in:
parent
ec990b4477
commit
aa8b789049
@ -1,11 +1,17 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DerivingVia, MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE DeriveTraversable #-}
|
||||
{-# LANGUAGE DerivingVia #-}
|
||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||
module Data.Syntax.Comment (module Data.Syntax.Comment) where
|
||||
|
||||
import Prologue
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Functor.Classes.Generic
|
||||
import Data.Hashable.Lifted
|
||||
import Data.JSON.Fields
|
||||
import Data.Text (Text)
|
||||
import Diffing.Algorithm
|
||||
import GHC.Generics (Generic1)
|
||||
|
||||
-- | An unnested comment (line or block).
|
||||
newtype Comment a = Comment { commentContent :: Text }
|
||||
|
@ -1,12 +1,16 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE DeriveTraversable #-}
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
module Language.TSX.Syntax.JSX (module Language.TSX.Syntax.JSX) where
|
||||
|
||||
import Prologue
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Functor.Classes.Generic
|
||||
import Data.Hashable.Lifted
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Text as T
|
||||
import Diffing.Algorithm
|
||||
import GHC.Generics (Generic1)
|
||||
|
||||
|
||||
data JsxElement a = JsxElement { jsxOpeningElement :: !a, jsxElements :: ![a], jsxClosingElement :: !a }
|
||||
|
@ -1,17 +1,28 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields, OverloadedStrings, RecordWildCards, TypeApplications #-}
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE DeriveTraversable #-}
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
module Language.TypeScript.Syntax.Import (module Language.TypeScript.Syntax.Import) where
|
||||
|
||||
import Prologue
|
||||
|
||||
import qualified Analysis.Name as Name
|
||||
import Control.Abstract hiding (Import)
|
||||
import Control.Monad
|
||||
import Data.Abstract.Evaluatable as Evaluatable
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
import Data.Aeson (ToJSON)
|
||||
import Data.Foldable
|
||||
import Data.Functor.Classes.Generic
|
||||
import Data.Hashable
|
||||
import Data.Hashable.Lifted
|
||||
import Data.JSON.Fields
|
||||
import Diffing.Algorithm
|
||||
import Language.TypeScript.Resolution
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Data.Aeson (ToJSON)
|
||||
import Data.Semilattice.Lower
|
||||
import Diffing.Algorithm
|
||||
import GHC.Generics (Generic, Generic1)
|
||||
import Language.TypeScript.Resolution
|
||||
|
||||
data Import a = Import { importSymbols :: ![Alias], importFrom :: ImportPath }
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
@ -25,7 +36,7 @@ instance Evaluatable Import where
|
||||
eval _ _ (Import symbols importPath) = do
|
||||
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
|
||||
((moduleScope, moduleFrame), _) <- require modulePath
|
||||
if Prologue.null symbols then do
|
||||
if Prelude.null symbols then do
|
||||
insertImportEdge moduleScope
|
||||
insertFrameLink ScopeGraph.Import (Map.singleton moduleScope moduleFrame)
|
||||
else do
|
||||
|
@ -1,15 +1,21 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields, RecordWildCards, TypeApplications #-}
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE DeriveTraversable #-}
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
module Language.TypeScript.Syntax.JavaScript (module Language.TypeScript.Syntax.JavaScript) where
|
||||
|
||||
import Prologue
|
||||
|
||||
import Control.Abstract.Heap
|
||||
import Control.Abstract.ScopeGraph hiding (Import)
|
||||
import Data.Abstract.Evaluatable
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
import Data.Functor.Classes.Generic
|
||||
import Data.Hashable.Lifted
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Diffing.Algorithm
|
||||
import GHC.Generics (Generic1)
|
||||
import Language.TypeScript.Resolution
|
||||
|
||||
newtype ImplementsClause a = ImplementsClause { implementsClauseTypes :: [a] }
|
||||
|
@ -1,17 +1,30 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields, FlexibleContexts, RecordWildCards, TupleSections, TypeApplications #-}
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE DeriveTraversable #-}
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
module Language.TypeScript.Syntax.TypeScript (module Language.TypeScript.Syntax.TypeScript) where
|
||||
|
||||
import Prologue
|
||||
|
||||
import Control.Abstract hiding (Import)
|
||||
import Control.Monad
|
||||
import Data.Abstract.Evaluatable as Evaluatable
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
import Data.Foldable
|
||||
import Data.Functor.Classes.Generic
|
||||
import Data.Hashable.Lifted
|
||||
import Data.JSON.Fields
|
||||
import Data.List.NonEmpty (nonEmpty)
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Data.Maybe.Exts
|
||||
import Data.Semigroup.App
|
||||
import Data.Semigroup.Foldable
|
||||
import qualified Data.Text as T
|
||||
import Data.Traversable
|
||||
import Diffing.Algorithm
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
import GHC.Generics (Generic1)
|
||||
|
||||
-- | ShorthandPropertyIdentifier used in object patterns such as var baz = { foo } to mean var baz = { foo: foo }
|
||||
newtype ShorthandPropertyIdentifier a = ShorthandPropertyIdentifier { contents :: T.Text }
|
||||
|
@ -1,14 +1,20 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields, RecordWildCards, TypeApplications #-}
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE DeriveTraversable #-}
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
module Language.TypeScript.Syntax.Types (module Language.TypeScript.Syntax.Types) where
|
||||
|
||||
import Prologue
|
||||
|
||||
import Control.Abstract hiding (Import)
|
||||
import Data.Abstract.Evaluatable as Evaluatable
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
import Data.Functor.Classes.Generic
|
||||
import Data.Hashable.Lifted
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Text as T
|
||||
import Diffing.Algorithm
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
import GHC.Generics (Generic1)
|
||||
|
||||
-- | Lookup type for a type-level key in a typescript map.
|
||||
data LookupType a = LookupType { lookupTypeIdentifier :: a, lookupTypeKey :: a }
|
||||
|
Loading…
Reference in New Issue
Block a user