1
1
mirror of https://github.com/github/semantic.git synced 2025-01-03 04:51:57 +03:00

Add a fallback term constructor for other languages.

This commit is contained in:
Rob Rix 2016-09-07 15:14:20 -04:00
parent a1be4c2841
commit 1e9785fc67
2 changed files with 22 additions and 1 deletions

View File

@ -1,6 +1,13 @@
{-# LANGUAGE DataKinds #-}
module Language where
import Data.Record
import Info
import Prologue
import Source
import SourceSpan
import qualified Syntax as S
import Term
-- | A programming language.
data Language =
@ -30,3 +37,17 @@ languageForType mediaType = case mediaType of
".js" -> Just JavaScript
".rb" -> Just Ruby
_ -> Nothing
termConstructor
:: Source Char -- ^ The source that the term occurs within.
-> IO SourceSpan -- ^ The span that the term occupies. This is passed in 'IO' to guarantee some access constraints & encourage its use only when needed (improving performance).
-> Text -- ^ The name of the production for this node.
-> Range -- ^ The character range that the term occupies.
-> [Term Text (Record '[Range, Category])] -- ^ The child nodes of the term.
-> IO (Term Text (Record '[Range, Category])) -- ^ The resulting term, in IO.
termConstructor source sourceSpan name range children
| name == "ERROR" = sourceSpan >>= withDefaultInfo . (`S.Error` children)
| otherwise = withDefaultInfo $ case (name, children) of
(_, []) -> S.Leaf . toText $ slice range source
_ -> S.Indexed children
where withDefaultInfo syntax = pure $! cofree ((range .: Other name .: RNil) :< syntax)

View File

@ -55,4 +55,4 @@ documentToTerm language document blob = alloca $ \ root -> do
termConstructor = case language of
JavaScript -> JS.termConstructor
C -> C.termConstructor
_ -> JS.termConstructor
_ -> Language.termConstructor