mirror of
https://github.com/github/semantic.git
synced 2024-11-26 09:07:39 +03:00
Add semantic-typescript
This commit is contained in:
parent
d6311fc79b
commit
e4bf165276
@ -7,6 +7,7 @@ packages: .
|
||||
semantic-json
|
||||
semantic-python
|
||||
semantic-ruby
|
||||
semantic-typescript
|
||||
semantic-tags
|
||||
|
||||
jobs: $ncpus
|
||||
@ -20,6 +21,9 @@ package semantic-analysis
|
||||
package semantic-core
|
||||
ghc-options: -Werror
|
||||
|
||||
package semantic-go
|
||||
ghc-options: -Werror
|
||||
|
||||
package semantic-java
|
||||
ghc-options: -Werror
|
||||
|
||||
@ -29,6 +33,9 @@ package semantic-json
|
||||
package semantic-python
|
||||
ghc-options: -Werror
|
||||
|
||||
package semantic-ruby
|
||||
ghc-options: -Werror
|
||||
|
||||
package semantic-tags
|
||||
ghc-options: -Werror
|
||||
|
||||
|
@ -45,6 +45,7 @@ function flags {
|
||||
echo "-isemantic-json/src"
|
||||
echo "-isemantic-python/src"
|
||||
echo "-isemantic-ruby/src"
|
||||
echo "-isemantic-typescript/src"
|
||||
echo "-isemantic-tags/src"
|
||||
echo "-iapp"
|
||||
echo "-isrc"
|
||||
|
@ -17,3 +17,4 @@ echo "semantic-java/semantic-java.cabal"
|
||||
echo "semantic-json/semantic-json.cabal"
|
||||
echo "semantic-python/semantic-python.cabal"
|
||||
echo "semantic-ruby/semantic-ruby.cabal"
|
||||
echo "semantic-typescript/semantic-typescript.cabal"
|
||||
|
21
semantic-typescript/LICENSE
Normal file
21
semantic-typescript/LICENSE
Normal file
@ -0,0 +1,21 @@
|
||||
MIT License
|
||||
|
||||
Copyright (c) 2019 GitHub
|
||||
|
||||
Permission is hereby granted, free of charge, to any person obtaining a copy
|
||||
of this software and associated documentation files (the "Software"), to deal
|
||||
in the Software without restriction, including without limitation the rights
|
||||
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
|
||||
copies of the Software, and to permit persons to whom the Software is
|
||||
furnished to do so, subject to the following conditions:
|
||||
|
||||
The above copyright notice and this permission notice shall be included in all
|
||||
copies or substantial portions of the Software.
|
||||
|
||||
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
|
||||
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
|
||||
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
|
||||
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
|
||||
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
|
||||
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
|
||||
SOFTWARE.
|
3
semantic-typescript/README.md
Normal file
3
semantic-typescript/README.md
Normal file
@ -0,0 +1,3 @@
|
||||
# Semantic support for TypeScript
|
||||
|
||||
This package implements `semantic` support for TypeScript using the `semantic-core` intermediate language.
|
2
semantic-typescript/Setup.hs
Normal file
2
semantic-typescript/Setup.hs
Normal file
@ -0,0 +1,2 @@
|
||||
import Distribution.Simple
|
||||
main = defaultMain
|
54
semantic-typescript/semantic-typescript.cabal
Normal file
54
semantic-typescript/semantic-typescript.cabal
Normal file
@ -0,0 +1,54 @@
|
||||
cabal-version: 2.4
|
||||
|
||||
name: semantic-typescript
|
||||
version: 0.0.0.0
|
||||
synopsis: Semantic support for TypeScript.
|
||||
description: Semantic support for TypeScript using the semantic-core intermediate language.
|
||||
homepage: https://github.com/github/semantic/tree/master/semantic-typescript#readme
|
||||
bug-reports: https://github.com/github/semantic/issues
|
||||
license: MIT
|
||||
license-file: LICENSE
|
||||
author: The Semantic authors
|
||||
maintainer: opensource+semantic@github.com
|
||||
copyright: (c) 2019 GitHub, Inc.
|
||||
category: Language
|
||||
build-type: Simple
|
||||
stability: alpha
|
||||
extra-source-files: README.md
|
||||
|
||||
tested-with: GHC == 8.6.5
|
||||
|
||||
common haskell
|
||||
default-language: Haskell2010
|
||||
build-depends: base ^>= 4.13
|
||||
, fused-effects ^>= 1.0
|
||||
, fused-syntax
|
||||
, parsers ^>= 0.12.10
|
||||
, semantic-core ^>= 0.0
|
||||
, semantic-source ^>= 0.0
|
||||
, semantic-tags ^>= 0.0
|
||||
, text ^>= 1.2.3
|
||||
, tree-sitter ^>= 0.7.2
|
||||
, tree-sitter-typescript ^>= 0.4
|
||||
|
||||
ghc-options:
|
||||
-Weverything
|
||||
-Wno-missing-local-signatures
|
||||
-Wno-missing-import-lists
|
||||
-Wno-implicit-prelude
|
||||
-Wno-safe
|
||||
-Wno-unsafe
|
||||
-Wno-name-shadowing
|
||||
-Wno-monomorphism-restriction
|
||||
-Wno-missed-specialisations
|
||||
-Wno-all-missed-specialisations
|
||||
-Wno-star-is-type
|
||||
if (impl(ghc >= 8.8))
|
||||
ghc-options: -Wno-missing-deriving-strategies
|
||||
|
||||
library
|
||||
import: haskell
|
||||
exposed-modules:
|
||||
Language.TypeScript
|
||||
Language.TypeScript.Tags
|
||||
hs-source-dirs: src
|
21
semantic-typescript/src/Language/TypeScript.hs
Normal file
21
semantic-typescript/src/Language/TypeScript.hs
Normal file
@ -0,0 +1,21 @@
|
||||
{-# OPTIONS_GHC -freduction-depth=0 #-}
|
||||
-- | Semantic functionality for TypeScript programs.
|
||||
module Language.TypeScript
|
||||
( Term(..)
|
||||
, TreeSitter.TypeScript.tree_sitter_typescript
|
||||
) where
|
||||
|
||||
|
||||
import qualified Language.TypeScript.Tags as TsTags
|
||||
import qualified Tags.Tagging.Precise as Tags
|
||||
import qualified TreeSitter.TypeScript (tree_sitter_typescript)
|
||||
import qualified TreeSitter.TypeScript.AST as TypeScript
|
||||
import qualified TreeSitter.Unmarshal as TS
|
||||
|
||||
newtype Term a = Term { getTerm :: TypeScript.Program a }
|
||||
|
||||
instance TS.Unmarshal Term where
|
||||
unmarshalNode node = Term <$> TS.unmarshalNode node
|
||||
|
||||
instance Tags.ToTags Term where
|
||||
tags src = Tags.runTagging src . TsTags.tags . getTerm
|
124
semantic-typescript/src/Language/TypeScript/Tags.hs
Normal file
124
semantic-typescript/src/Language/TypeScript/Tags.hs
Normal file
@ -0,0 +1,124 @@
|
||||
{-# LANGUAGE AllowAmbiguousTypes, DataKinds, DisambiguateRecordFields, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, NamedFieldPuns, PartialTypeSignatures, ScopedTypeVariables, TypeApplications, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
{-# OPTIONS_GHC -freduction-depth=0 #-}
|
||||
module Language.TypeScript.Tags
|
||||
( ToTags(..)
|
||||
) where
|
||||
|
||||
import AST.Element
|
||||
import Control.Effect.Reader
|
||||
import Control.Effect.Writer
|
||||
import Data.Monoid (Ap (..))
|
||||
import Data.Text as Text
|
||||
import GHC.Generics
|
||||
import Source.Loc
|
||||
import Source.Source as Source
|
||||
import Tags.Tag
|
||||
import qualified Tags.Tagging.Precise as Tags
|
||||
import qualified TreeSitter.TypeScript.AST as Ts
|
||||
|
||||
class ToTags t where
|
||||
tags
|
||||
:: ( Has (Reader Source) sig m
|
||||
, Has (Writer Tags.Tags) sig m
|
||||
)
|
||||
=> t Loc
|
||||
-> m ()
|
||||
|
||||
instance (ToTagsBy strategy t, strategy ~ ToTagsInstance t) => ToTags t where
|
||||
tags = tags' @strategy
|
||||
|
||||
|
||||
class ToTagsBy (strategy :: Strategy) t where
|
||||
tags'
|
||||
:: ( Has (Reader Source) sig m
|
||||
, Has (Writer Tags.Tags) sig m
|
||||
)
|
||||
=> t Loc
|
||||
-> m ()
|
||||
|
||||
|
||||
data Strategy = Generic | Custom
|
||||
|
||||
type family ToTagsInstance t :: Strategy where
|
||||
ToTagsInstance (_ :+: _) = 'Custom
|
||||
ToTagsInstance Ts.Function = 'Custom
|
||||
ToTagsInstance Ts.FunctionSignature = 'Custom
|
||||
ToTagsInstance Ts.FunctionDeclaration = 'Custom
|
||||
ToTagsInstance Ts.MethodDefinition = 'Custom
|
||||
ToTagsInstance Ts.ClassDeclaration = 'Custom
|
||||
ToTagsInstance Ts.CallExpression = 'Custom
|
||||
ToTagsInstance _ = 'Generic
|
||||
|
||||
instance ToTagsBy 'Custom Ts.Function where
|
||||
tags' t@Ts.Function
|
||||
{ ann = loc@Loc { byteRange }
|
||||
, name = Just Ts.Identifier { text }
|
||||
} = yieldTag text Function loc byteRange >> gtags t
|
||||
tags' t = gtags t
|
||||
|
||||
instance ToTagsBy 'Custom Ts.FunctionSignature where
|
||||
tags' t@Ts.FunctionSignature
|
||||
{ ann = loc@Loc { byteRange }
|
||||
, name = Ts.Identifier { text }
|
||||
} = yieldTag text Function loc byteRange >> gtags t
|
||||
|
||||
instance ToTagsBy 'Custom Ts.FunctionDeclaration where
|
||||
tags' t@Ts.FunctionDeclaration
|
||||
{ ann = loc@Loc { byteRange }
|
||||
, name = Ts.Identifier { text }
|
||||
} = yieldTag text Function loc byteRange >> gtags t
|
||||
|
||||
instance ToTagsBy 'Custom Ts.MethodDefinition where
|
||||
tags' t@Ts.MethodDefinition
|
||||
{ ann = loc@Loc { byteRange }
|
||||
, name
|
||||
} = case name of
|
||||
Prj Ts.PropertyIdentifier { text } -> yield text
|
||||
-- TODO: There are more here
|
||||
_ -> gtags t
|
||||
where
|
||||
yield name = yieldTag name Call loc byteRange >> gtags t
|
||||
|
||||
instance ToTagsBy 'Custom Ts.ClassDeclaration where
|
||||
tags' t@Ts.ClassDeclaration
|
||||
{ ann = loc@Loc { byteRange }
|
||||
, name = Ts.TypeIdentifier { text }
|
||||
} = yieldTag text Class loc byteRange >> gtags t
|
||||
|
||||
instance ToTagsBy 'Custom Ts.CallExpression where
|
||||
tags' t@Ts.CallExpression
|
||||
{ ann = loc@Loc { byteRange }
|
||||
, function = Ts.Expression expr
|
||||
} = match expr
|
||||
where
|
||||
match expr = case expr of
|
||||
Prj Ts.Identifier { text } -> yield text
|
||||
Prj Ts.NewExpression { constructor = Prj Ts.Identifier { text } } -> yield text
|
||||
-- Prj Ts.MemberExpression { property = Ts.PropertyIdentifier { text }, object = (Ts.Expression expr) } -> yieldTag text Call loc byteRange >> match expr
|
||||
Prj Ts.CallExpression { function = Ts.Expression expr } -> match expr
|
||||
Prj Ts.MemberExpression { property = Ts.PropertyIdentifier { text } } -> yield text
|
||||
_ -> gtags t
|
||||
yield name = yieldTag name Call loc byteRange >> gtags t
|
||||
|
||||
instance (ToTags l, ToTags r) => ToTagsBy 'Custom (l :+: r) where
|
||||
tags' (L1 l) = tags l
|
||||
tags' (R1 r) = tags r
|
||||
|
||||
gtags
|
||||
:: ( Has (Reader Source) sig m
|
||||
, Has (Writer Tags.Tags) sig m
|
||||
, Generic1 t
|
||||
, Tags.GFoldable1 ToTags (Rep1 t)
|
||||
)
|
||||
=> t Loc
|
||||
-> m ()
|
||||
gtags = getAp . Tags.gfoldMap1 @ToTags (Ap . tags) . from1
|
||||
|
||||
instance (Generic1 t, Tags.GFoldable1 ToTags (Rep1 t)) => ToTagsBy 'Generic t where
|
||||
tags' = gtags
|
||||
|
||||
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> Kind -> Loc -> Range -> m ()
|
||||
yieldTag name kind loc range = do
|
||||
src <- ask @Source
|
||||
let sliced = slice src range
|
||||
Tags.yield (Tag name kind loc (Tags.firstLine sliced) Nothing)
|
@ -290,6 +290,7 @@ library
|
||||
, semantic-json ^>= 0
|
||||
, semantic-python ^>= 0
|
||||
, semantic-ruby ^>= 0
|
||||
, semantic-typescript ^>= 0
|
||||
, semantic-tags ^>= 0
|
||||
, semigroupoids ^>= 5.3.2
|
||||
, split ^>= 0.2.3.3
|
||||
|
@ -154,6 +154,7 @@ data PerLanguageModes = PerLanguageModes
|
||||
{ pythonMode :: LanguageMode
|
||||
, rubyMode :: LanguageMode
|
||||
, goMode :: LanguageMode
|
||||
, typescriptMode :: LanguageMode
|
||||
}
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
@ -162,6 +163,7 @@ defaultLanguageModes = PerLanguageModes
|
||||
{ pythonMode = ALaCarte
|
||||
, rubyMode = ALaCarte
|
||||
, goMode = ALaCarte
|
||||
, typescriptMode = ALaCarte
|
||||
}
|
||||
|
||||
data LanguageMode
|
||||
|
@ -103,7 +103,7 @@ augmentedAssignmentExpression = makeTerm' <$> symbol AugmentedAssignmentExpressi
|
||||
, assign Expression.LShift <$ symbol AnonLAngleLAngleEqual
|
||||
, assign Expression.BOr <$ symbol AnonPipeEqual ])
|
||||
where assign :: (f :< TypeScript.Syntax) => (Term Loc -> Term Loc -> f (Term Loc)) -> Term Loc -> Term Loc -> Sum TypeScript.Syntax (Term Loc)
|
||||
assign c l r = inject (Statement.Assignment [] l (makeTerm1 (c l r)))
|
||||
assign c l r = inject (Statement.AugmentedAssignment (makeTerm1 (c l r)))
|
||||
|
||||
|
||||
awaitExpression :: Assignment (Term Loc)
|
||||
|
@ -93,6 +93,7 @@ type Syntax =
|
||||
, Literal.TextElement
|
||||
, Literal.Regex
|
||||
, Statement.Assignment
|
||||
, Statement.AugmentedAssignment
|
||||
, Statement.Break
|
||||
, Statement.Catch
|
||||
, Statement.Continue
|
||||
|
@ -20,6 +20,8 @@ module Parsing.Parser
|
||||
, rubyParserPrecise
|
||||
, rubyParser
|
||||
, tsxParser
|
||||
, typescriptParserALaCarte
|
||||
, typescriptParserPrecise
|
||||
, typescriptParser
|
||||
-- * Modes by term type
|
||||
, TermMode
|
||||
@ -48,7 +50,8 @@ import qualified Language.Python.Assignment as PythonALaCarte
|
||||
import qualified Language.Ruby as RubyPrecise
|
||||
import qualified Language.Ruby.Assignment as RubyALaCarte
|
||||
import qualified Language.TSX.Assignment as TSX
|
||||
import qualified Language.TypeScript.Assignment as TypeScript
|
||||
import qualified Language.TypeScript as TypeScriptPrecise
|
||||
import qualified Language.TypeScript.Assignment as TypeScriptALaCarte
|
||||
import Prelude hiding (fail)
|
||||
import Prologue
|
||||
import TreeSitter.Go
|
||||
@ -160,19 +163,27 @@ rubyParser modes = case rubyMode modes of
|
||||
tsxParser :: c TSX.Term => (Language, SomeParser c Loc)
|
||||
tsxParser = (TSX, SomeParser (AssignmentParser (ASTParser tree_sitter_tsx) TSX.assignment))
|
||||
|
||||
typescriptParser :: c TypeScript.Term => (Language, SomeParser c Loc)
|
||||
typescriptParser = (TypeScript, SomeParser (AssignmentParser (ASTParser tree_sitter_typescript) TypeScript.assignment))
|
||||
typescriptParserALaCarte :: c TypeScriptALaCarte.Term => (Language, SomeParser c Loc)
|
||||
typescriptParserALaCarte = (TypeScript, SomeParser (AssignmentParser (ASTParser tree_sitter_typescript) TypeScriptALaCarte.assignment))
|
||||
|
||||
typescriptParserPrecise :: c TypeScriptPrecise.Term => (Language, SomeParser c Loc)
|
||||
typescriptParserPrecise = (TypeScript, SomeParser (UnmarshalParser @TypeScriptPrecise.Term TypeScriptPrecise.tree_sitter_typescript))
|
||||
|
||||
typescriptParser :: (c TypeScriptALaCarte.Term, c TypeScriptPrecise.Term) => PerLanguageModes -> (Language, SomeParser c Loc)
|
||||
typescriptParser modes = case typescriptMode modes of
|
||||
ALaCarte -> typescriptParserALaCarte
|
||||
Precise -> typescriptParserPrecise
|
||||
|
||||
|
||||
-- | A type family selecting the language mode for a given term type.
|
||||
type family TermMode term where
|
||||
TermMode GoPrecise.Term = 'Precise
|
||||
TermMode Java.Term = 'Precise
|
||||
TermMode JSON.Term = 'Precise
|
||||
TermMode PythonPrecise.Term = 'Precise
|
||||
TermMode RubyPrecise.Term = 'Precise
|
||||
TermMode _ = 'ALaCarte
|
||||
|
||||
TermMode GoPrecise.Term = 'Precise
|
||||
TermMode Java.Term = 'Precise
|
||||
TermMode JSON.Term = 'Precise
|
||||
TermMode PythonPrecise.Term = 'Precise
|
||||
TermMode RubyPrecise.Term = 'Precise
|
||||
TermMode TypeScriptPrecise.Term = 'Precise
|
||||
TermMode _ = 'ALaCarte
|
||||
|
||||
-- | The canonical set of parsers producing à la carte terms.
|
||||
aLaCarteParsers
|
||||
@ -182,7 +193,7 @@ aLaCarteParsers
|
||||
, c PythonALaCarte.Term
|
||||
, c RubyALaCarte.Term
|
||||
, c TSX.Term
|
||||
, c TypeScript.Term
|
||||
, c TypeScriptALaCarte.Term
|
||||
)
|
||||
=> Map Language (SomeParser c Loc)
|
||||
aLaCarteParsers = Map.fromList
|
||||
@ -193,7 +204,7 @@ aLaCarteParsers = Map.fromList
|
||||
, phpParser
|
||||
, pythonParserALaCarte
|
||||
, rubyParserALaCarte
|
||||
, typescriptParser
|
||||
, typescriptParserALaCarte
|
||||
, tsxParser
|
||||
]
|
||||
|
||||
@ -204,6 +215,7 @@ preciseParsers
|
||||
, c PythonPrecise.Term
|
||||
, c RubyPrecise.Term
|
||||
, c GoPrecise.Term
|
||||
, c TypeScriptPrecise.Term
|
||||
)
|
||||
=> Map Language (SomeParser c Loc)
|
||||
preciseParsers = Map.fromList
|
||||
@ -212,6 +224,7 @@ preciseParsers = Map.fromList
|
||||
, pythonParserPrecise
|
||||
, rubyParserPrecise
|
||||
, goParserPrecise
|
||||
, typescriptParserPrecise
|
||||
]
|
||||
|
||||
-- | The canonical set of all parsers for the passed per-language modes.
|
||||
@ -227,7 +240,8 @@ allParsers
|
||||
, c RubyALaCarte.Term
|
||||
, c RubyPrecise.Term
|
||||
, c TSX.Term
|
||||
, c TypeScript.Term
|
||||
, c TypeScriptALaCarte.Term
|
||||
, c TypeScriptPrecise.Term
|
||||
)
|
||||
=> PerLanguageModes
|
||||
-> Map Language (SomeParser c Loc)
|
||||
@ -241,6 +255,6 @@ allParsers modes = Map.fromList
|
||||
, phpParser
|
||||
, pythonParser modes
|
||||
, rubyParser modes
|
||||
, typescriptParser
|
||||
, typescriptParser modes
|
||||
, tsxParser
|
||||
]
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE AllowAmbiguousTypes, DataKinds, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, RankNTypes, RecordWildCards, ScopedTypeVariables, TypeApplications, TypeFamilies, UndecidableInstances #-}
|
||||
{-# OPTIONS_GHC -freduction-depth=0 #-}
|
||||
module Semantic.Api.Terms
|
||||
( termGraph
|
||||
, parseTermBuilder
|
||||
@ -43,6 +44,7 @@ import qualified Language.JSON as JSON
|
||||
import qualified Language.Go as GoPrecise
|
||||
import qualified Language.Python as PythonPrecise
|
||||
import qualified Language.Ruby as RubyPrecise
|
||||
import qualified Language.TypeScript as TypeScriptPrecise
|
||||
|
||||
|
||||
termGraph :: (Traversable t, Has Distribute sig m, Has (Error SomeException) sig m, Has Parse sig m) => t Blob -> m ParseTreeGraphResponse
|
||||
@ -124,6 +126,9 @@ instance ShowTermBy 'Precise PythonPrecise.Term where
|
||||
instance ShowTermBy 'Precise RubyPrecise.Term where
|
||||
showTermBy = serialize Show . void . RubyPrecise.getTerm
|
||||
|
||||
instance ShowTermBy 'Precise TypeScriptPrecise.Term where
|
||||
showTermBy = serialize Show . void . TypeScriptPrecise.getTerm
|
||||
|
||||
instance (Recursive (term Loc), Show1 syntax, Base (term Loc) ~ TermF syntax Loc) => ShowTermBy 'ALaCarte term where
|
||||
showTermBy = serialize Show . quieterm
|
||||
|
||||
@ -155,6 +160,9 @@ instance SExprTermBy 'Precise PythonPrecise.Term where
|
||||
instance SExprTermBy 'Precise RubyPrecise.Term where
|
||||
sexprTermBy = SExpr.Precise.serializeSExpression . RubyPrecise.getTerm
|
||||
|
||||
instance SExprTermBy 'Precise TypeScriptPrecise.Term where
|
||||
sexprTermBy = SExpr.Precise.serializeSExpression . TypeScriptPrecise.getTerm
|
||||
|
||||
instance (Recursive (term Loc), SExpr.ToSExpression (Base (term Loc))) => SExprTermBy 'ALaCarte term where
|
||||
sexprTermBy = SExpr.serializeSExpression ByConstructorName
|
||||
|
||||
|
@ -183,6 +183,11 @@ languageModes = Language.PerLanguageModes
|
||||
<> metavar "ALaCarte|Precise"
|
||||
<> value Language.ALaCarte
|
||||
<> showDefault)
|
||||
<*> option auto ( long "typescript-mode"
|
||||
<> help "The AST representation to use for TypeScript sources"
|
||||
<> metavar "ALaCarte|Precise"
|
||||
<> value Language.ALaCarte
|
||||
<> showDefault)
|
||||
|
||||
filePathReader :: ReadM File
|
||||
filePathReader = fileForPath <$> str
|
||||
|
@ -109,7 +109,7 @@ analysisParsers = Map.fromList
|
||||
, phpParser
|
||||
, pythonParserALaCarte
|
||||
, rubyParserALaCarte
|
||||
, typescriptParser
|
||||
, typescriptParserALaCarte
|
||||
, tsxParser
|
||||
]
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user