1
1
mirror of https://github.com/github/semantic.git synced 2024-12-25 07:55:12 +03:00

Depend on newer semantic-source.

This commit is contained in:
Patrick Thomson 2020-01-28 12:42:42 -05:00
parent a1f46b26e1
commit 9ecaeedcc3
17 changed files with 33 additions and 171 deletions

View File

@ -52,7 +52,6 @@ library
Analysis.FlowInsensitive Analysis.FlowInsensitive
Analysis.ImportGraph Analysis.ImportGraph
Analysis.Intro Analysis.Intro
Analysis.Language
Analysis.Name Analysis.Name
Analysis.Typecheck Analysis.Typecheck
Control.Carrier.Fail.WithLoc Control.Carrier.Fail.WithLoc
@ -71,7 +70,7 @@ library
, pathtype ^>= 0.8.1 , pathtype ^>= 0.8.1
, prettyprinter >= 1.2 && < 2 , prettyprinter >= 1.2 && < 2
, prettyprinter-ansi-terminal ^>= 1.1.1 , prettyprinter-ansi-terminal ^>= 1.1.1
, semantic-source ^>= 0.0.1 , semantic-source ^>= 0.0.2
, semilattices , semilattices
, terminal-size ^>= 0.3 , terminal-size ^>= 0.3
, text ^>= 1.2.3.1 , text ^>= 1.2.3.1

View File

@ -6,10 +6,10 @@ module Analysis.File
, fromPath , fromPath
) where ) where
import Analysis.Language as Language
import Data.Maybe (fromJust, listToMaybe) import Data.Maybe (fromJust, listToMaybe)
import Data.Semilattice.Lower import Data.Semilattice.Lower
import GHC.Stack import GHC.Stack
import Source.Language as Language
import Source.Span import Source.Span
import qualified System.Path as Path import qualified System.Path as Path
import qualified System.Path.PartClass as Path.PartClass import qualified System.Path.PartClass as Path.PartClass

View File

@ -1,136 +0,0 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Analysis.Language
( Language (..)
, SLanguage (..)
, extensionsForLanguage
, knownLanguage
, forPath
, textToLanguage
, languageToText
) where
import Data.Aeson
import Data.Hashable (Hashable)
import qualified Data.Languages as Lingo
import qualified Data.Map.Strict as Map
import qualified Data.Text as T
import GHC.Generics (Generic)
import qualified System.Path as Path
import qualified System.Path.PartClass as Path.PartClass
-- | The various languages we support.
data Language
= Unknown
| Go
| Haskell
| Java
| JavaScript
| JSON
| JSX
| Markdown
| Python
| Ruby
| TypeScript
| PHP
| TSX
deriving (Eq, Generic, Ord, Read, Show, Bounded, Hashable, ToJSON, Enum)
-- | Reifies a proxied type-level 'Language' to a value.
class SLanguage (lang :: Language) where
reflect :: proxy lang -> Language
instance SLanguage 'Unknown where
reflect _ = Unknown
instance SLanguage 'Go where
reflect _ = Go
instance SLanguage 'Haskell where
reflect _ = Haskell
instance SLanguage 'Java where
reflect _ = Java
instance SLanguage 'JavaScript where
reflect _ = JavaScript
instance SLanguage 'JSON where
reflect _ = JSON
instance SLanguage 'JSX where
reflect _ = JSX
instance SLanguage 'Markdown where
reflect _ = Markdown
instance SLanguage 'Python where
reflect _ = Python
instance SLanguage 'Ruby where
reflect _ = Ruby
instance SLanguage 'TypeScript where
reflect _ = TypeScript
instance SLanguage 'PHP where
reflect _ = PHP
instance FromJSON Language where
parseJSON = withText "Language" $ \l ->
pure $ textToLanguage l
-- | Predicate failing on 'Unknown' and passing in all other cases.
knownLanguage :: Language -> Bool
knownLanguage = (/= Unknown)
extensionsForLanguage :: Language -> [String]
extensionsForLanguage language = T.unpack <$> maybe mempty Lingo.languageExtensions (Map.lookup (languageToText language) Lingo.languages)
forPath :: Path.PartClass.AbsRel ar => Path.File ar -> Language
forPath path =
let spurious lang = lang `elem` [ "Hack" -- .php files
, "GCC Machine Description" -- .md files
, "XML" -- .tsx files
]
allResults = Lingo.languageName <$> Lingo.languagesForPath (Path.toString path)
in case filter (not . spurious) allResults of
[result] -> textToLanguage result
_ -> Unknown
languageToText :: Language -> T.Text
languageToText = \case
Unknown -> "Unknown"
Go -> "Go"
Haskell -> "Haskell"
Java -> "Java"
JavaScript -> "JavaScript"
JSON -> "JSON"
JSX -> "JSX"
Markdown -> "Markdown"
Python -> "Python"
Ruby -> "Ruby"
TypeScript -> "TypeScript"
TSX -> "TSX"
PHP -> "PHP"
textToLanguage :: T.Text -> Language
textToLanguage = \case
"Go" -> Go
"Haskell" -> Haskell
"Java" -> Java
"JavaScript" -> JavaScript
"JSON" -> JSON
"JSX" -> JSX
"Markdown" -> Markdown
"Python" -> Python
"Ruby" -> Ruby
"TypeScript" -> TypeScript
"TSX" -> TSX
"PHP" -> PHP
_ -> Unknown

View File

@ -43,7 +43,7 @@ library
-- other-extensions: -- other-extensions:
build-depends: base ^>= 4.13 build-depends: base ^>= 4.13
, tree-sitter ^>= 0.8 , tree-sitter ^>= 0.8
, semantic-source ^>= 0.0.1 , semantic-source ^>= 0.0.2
, tree-sitter-python ^>= 0.8.1 , tree-sitter-python ^>= 0.8.1
, bytestring ^>= 0.10.8.2 , bytestring ^>= 0.10.8.2
, optparse-applicative >= 0.14.3 && < 0.16 , optparse-applicative >= 0.14.3 && < 0.16

View File

@ -1,27 +1,26 @@
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableInstances #-}
module Marshal.JSON module Marshal.JSON
( MarshalJSON(..) ( MarshalJSON(..)
) where ) where
import Data.Aeson as Aeson import Data.Aeson as Aeson
import Data.List.NonEmpty (NonEmpty) import Data.List.NonEmpty (NonEmpty)
import GHC.Generics import Data.Text (Text)
import Data.Text (Text)
import qualified Data.Text as Text import qualified Data.Text as Text
import GHC.Generics
-- TODO: range and span will require a new release of semantic-source
-- TODO: use toEncoding -- direct serialization to ByteString -- TODO: use toEncoding -- direct serialization to ByteString
-- Serialize unmarshaled ASTs into JSON representation by auto-deriving Aeson instances generically -- Serialize unmarshaled ASTs into JSON representation by auto-deriving Aeson instances generically
@ -33,7 +32,7 @@ class MarshalJSON t where
fields acc = gfields acc . from1 fields acc = gfields acc . from1
-- Implement the sum case -- Implement the sum case
instance {-# OVERLAPPING #-} (MarshalJSON f, MarshalJSON g) => MarshalJSON (f :+: g) where instance {-# OVERLAPPING #-} (MarshalJSON f, MarshalJSON g) => MarshalJSON (f :+: g) where
fields acc (L1 f) = fields acc f fields acc (L1 f) = fields acc f
fields acc (R1 g) = fields acc g fields acc (R1 g) = fields acc g
@ -71,7 +70,7 @@ instance (MarshalJSON t) => GValue (Rec1 t) where
instance (GValue t) => GValue (Maybe :.: t) where instance (GValue t) => GValue (Maybe :.: t) where
gvalue (Comp1 (Just t)) = gvalue t gvalue (Comp1 (Just t)) = gvalue t
gvalue (Comp1 Nothing) = Null gvalue (Comp1 Nothing) = Null
instance (GValue t) => GValue ([] :.: t) where instance (GValue t) => GValue ([] :.: t) where
gvalue (Comp1 ts) = toJSON $ map gvalue ts gvalue (Comp1 ts) = toJSON $ map gvalue ts
@ -85,4 +84,4 @@ class GFields f where
-- gvalue is a wrapper that calls to @toJSON@ (for leaf nodes such as @Text@) or recurses via @marshal@ -- gvalue is a wrapper that calls to @toJSON@ (for leaf nodes such as @Text@) or recurses via @marshal@
class GValue f where class GValue f where
gvalue :: (ToJSON a) => f a -> Value gvalue :: (ToJSON a) => f a -> Value

View File

@ -54,7 +54,7 @@ library
, prettyprinter >= 1.2.1 && < 2 , prettyprinter >= 1.2.1 && < 2
, prettyprinter-ansi-terminal ^>= 1.1.1 , prettyprinter-ansi-terminal ^>= 1.1.1
, semantic-analysis ^>= 0 , semantic-analysis ^>= 0
, semantic-source ^>= 0.0.1 , semantic-source ^>= 0.0.2
, text ^>= 1.2.3.1 , text ^>= 1.2.3.1
, trifecta >= 2 && < 2.2 , trifecta >= 2 && < 2.2
, unordered-containers ^>= 0.2.10 , unordered-containers ^>= 0.2.10
@ -69,7 +69,7 @@ test-suite test
base base
, semantic-analysis , semantic-analysis
, semantic-core , semantic-core
, semantic-source ^>= 0.0.1 , semantic-source
, fused-effects , fused-effects
, fused-syntax , fused-syntax
, hedgehog ^>= 1 , hedgehog ^>= 1

View File

@ -25,7 +25,7 @@ common haskell
, fused-syntax , fused-syntax
, parsers ^>= 0.12.10 , parsers ^>= 0.12.10
, semantic-core ^>= 0.0 , semantic-core ^>= 0.0
, semantic-source ^>= 0.0.1 , semantic-source ^>= 0.0.2
, semantic-tags ^>= 0.0 , semantic-tags ^>= 0.0
, text ^>= 1.2.3 , text ^>= 1.2.3
, tree-sitter ^>= 0.8 , tree-sitter ^>= 0.8

View File

@ -25,7 +25,7 @@ library
build-depends: build-depends:
base >= 4.13 && < 5 base >= 4.13 && < 5
, fused-effects ^>= 1.0 , fused-effects ^>= 1.0
, semantic-source ^>= 0.0.1 , semantic-source ^>= 0.0.2
, semantic-tags ^>= 0.0 , semantic-tags ^>= 0.0
, tree-sitter ^>= 0.8 , tree-sitter ^>= 0.8
, tree-sitter-java ^>= 0.6.1 , tree-sitter-java ^>= 0.6.1

View File

@ -25,7 +25,7 @@ common haskell
, fused-syntax , fused-syntax
, parsers ^>= 0.12.10 , parsers ^>= 0.12.10
, semantic-core ^>= 0.0 , semantic-core ^>= 0.0
, semantic-source ^>= 0.0.1 , semantic-source ^>= 0.0.2
, semantic-tags ^>= 0.0 , semantic-tags ^>= 0.0
, semantic-scope-graph ^>= 0.0 , semantic-scope-graph ^>= 0.0
, semilattices ^>= 0 , semilattices ^>= 0

View File

@ -25,7 +25,7 @@ common haskell
, fused-syntax , fused-syntax
, parsers ^>= 0.12.10 , parsers ^>= 0.12.10
, semantic-core ^>= 0.0 , semantic-core ^>= 0.0
, semantic-source ^>= 0.0.1 , semantic-source ^>= 0.0.2
, semantic-tags ^>= 0.0 , semantic-tags ^>= 0.0
, text ^>= 1.2.3 , text ^>= 1.2.3
, tree-sitter ^>= 0.8 , tree-sitter ^>= 0.8

View File

@ -38,7 +38,7 @@ library
, semilattices , semilattices
, generic-monoid , generic-monoid
, pathtype , pathtype
, semantic-source ^>= 0.0 , semantic-source ^>= 0.0.2
, text ^>= 1.2.3.1 , text ^>= 1.2.3.1
hs-source-dirs: src hs-source-dirs: src
default-language: Haskell2010 default-language: Haskell2010

View File

@ -26,7 +26,7 @@ library
build-depends: build-depends:
base >= 4.13 && < 5 base >= 4.13 && < 5
, fused-effects ^>= 1.0 , fused-effects ^>= 1.0
, semantic-source ^>= 0.0.1 , semantic-source ^>= 0.0.2
, text ^>= 1.2.3.1 , text ^>= 1.2.3.1
hs-source-dirs: src hs-source-dirs: src
default-language: Haskell2010 default-language: Haskell2010

View File

@ -25,7 +25,7 @@ common haskell
, fused-syntax , fused-syntax
, parsers ^>= 0.12.10 , parsers ^>= 0.12.10
, semantic-core ^>= 0.0 , semantic-core ^>= 0.0
, semantic-source ^>= 0.0.1 , semantic-source ^>= 0.0.2
, semantic-tags ^>= 0.0 , semantic-tags ^>= 0.0
, text ^>= 1.2.3 , text ^>= 1.2.3
, tree-sitter ^>= 0.8 , tree-sitter ^>= 0.8

View File

@ -25,7 +25,7 @@ common haskell
, fused-syntax , fused-syntax
, parsers ^>= 0.12.10 , parsers ^>= 0.12.10
, semantic-core ^>= 0.0 , semantic-core ^>= 0.0
, semantic-source ^>= 0.0.1 , semantic-source ^>= 0.0.2
, semantic-tags ^>= 0.0 , semantic-tags ^>= 0.0
, text ^>= 1.2.3 , text ^>= 1.2.3
, tree-sitter ^>= 0.8 , tree-sitter ^>= 0.8

View File

@ -68,7 +68,7 @@ common dependencies
, scientific ^>= 0.3.6.2 , scientific ^>= 0.3.6.2
, safe-exceptions ^>= 0.1.7.0 , safe-exceptions ^>= 0.1.7.0
, semantic-analysis , semantic-analysis
, semantic-source ^>= 0.0.1 , semantic-source ^>= 0.0.2
, semilattices ^>= 0.0.0.3 , semilattices ^>= 0.0.0.3
, streaming ^>= 0.2.2.0 , streaming ^>= 0.2.2.0
, text ^>= 1.2.3.1 , text ^>= 1.2.3.1

View File

@ -28,13 +28,13 @@ module Data.Blob
import Prologue import Prologue
import Analysis.File (File (..)) import Analysis.File (File (..))
import Analysis.Language as Language
import Control.Effect.Error import Control.Effect.Error
import Data.Aeson import Data.Aeson
import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy as BL
import Data.Edit import Data.Edit
import Data.JSON.Fields import Data.JSON.Fields
import Data.Module import Data.Module
import Source.Language as Language
import Source.Source (Source, totalSpan) import Source.Source (Source, totalSpan)
import qualified Source.Source as Source import qualified Source.Source as Source
import qualified System.FilePath as FP import qualified System.FilePath as FP

View File

@ -1,5 +1,5 @@
module Data.Language module Data.Language
( module Analysis.Language ( module Source.Language
, LanguageMode(..) , LanguageMode(..)
, PerLanguageModes(..) , PerLanguageModes(..)
, defaultLanguageModes , defaultLanguageModes
@ -7,10 +7,10 @@ module Data.Language
, supportedExts , supportedExts
) where ) where
import Analysis.Language
import qualified Data.Languages as Lingo import qualified Data.Languages as Lingo
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import qualified Data.Text as T import qualified Data.Text as T
import Source.Language
codeNavLanguages :: [Language] codeNavLanguages :: [Language]
codeNavLanguages = [Go, Java, Ruby, Python, JavaScript, TypeScript, PHP] codeNavLanguages = [Go, Java, Ruby, Python, JavaScript, TypeScript, PHP]