mirror of
https://github.com/github/semantic.git
synced 2024-12-26 00:12:29 +03:00
Get rid of the underscore names
This commit is contained in:
parent
3f0b1e678f
commit
d2a4257f94
@ -33,12 +33,10 @@ instance Evaluatable Function where
|
||||
where paramNames = foldMap (maybeToList . declaredName . subterm)
|
||||
|
||||
instance Tokenize Function where
|
||||
tokenize Function{..} = within TFunction $ do
|
||||
yield TOpen
|
||||
tokenize Function{..} = within' TFunction $ do
|
||||
functionName
|
||||
surround_ TParams (sep functionParameters)
|
||||
within' TParams $ sequenceA_ (sep functionParameters)
|
||||
functionBody
|
||||
yield TClose
|
||||
|
||||
instance Declarations1 Function where
|
||||
liftDeclaredName declaredName = declaredName . functionName
|
||||
@ -68,12 +66,10 @@ instance Evaluatable Method where
|
||||
where paramNames = foldMap (maybeToList . declaredName . subterm)
|
||||
|
||||
instance Tokenize Method where
|
||||
tokenize Method{..} = within TMethod $ do
|
||||
yield TOpen
|
||||
tokenize Method{..} = within' TMethod $ do
|
||||
methodName
|
||||
surround_ TParams (sep methodParameters)
|
||||
within' TParams $ sequenceA_ (sep methodParameters)
|
||||
methodBody
|
||||
yield TClose
|
||||
|
||||
instance Declarations1 Method where
|
||||
liftDeclaredName declaredName = declaredName . methodName
|
||||
|
@ -2,7 +2,7 @@
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Literal where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Evaluatable as Eval
|
||||
import Data.JSON.Fields
|
||||
import Data.Scientific.Exts
|
||||
import qualified Data.Text as T
|
||||
@ -11,7 +11,7 @@ import Numeric.Exts
|
||||
import Prelude hiding (Float, null)
|
||||
import Prologue hiding (Set, hash, null)
|
||||
import Proto3.Suite.Class
|
||||
import Reprinting.Tokenize
|
||||
import Reprinting.Tokenize as Tok
|
||||
import Text.Read (readMaybe)
|
||||
|
||||
-- Boolean
|
||||
@ -212,7 +212,7 @@ instance Evaluatable Array where
|
||||
eval (Array a) = rvalBox =<< array =<< traverse subtermAddress a
|
||||
|
||||
instance Tokenize Array where
|
||||
tokenize = list_ . arrayElements
|
||||
tokenize = list . arrayElements
|
||||
|
||||
newtype Hash a = Hash { hashElements :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
@ -222,10 +222,10 @@ instance Ord1 Hash where liftCompare = genericLiftCompare
|
||||
instance Show1 Hash where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Hash where
|
||||
eval t = rvalBox =<< (hash <$> traverse (subtermValue >=> asPair) (hashElements t))
|
||||
eval t = rvalBox =<< (Eval.hash <$> traverse (subtermValue >=> asPair) (hashElements t))
|
||||
|
||||
instance Tokenize Hash where
|
||||
tokenize = hash_ . hashElements
|
||||
tokenize = Tok.hash . hashElements
|
||||
|
||||
data KeyValue a = KeyValue { key :: !a, value :: !a }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
@ -239,7 +239,7 @@ instance Evaluatable KeyValue where
|
||||
rvalBox =<< (kvPair <$> key <*> value)
|
||||
|
||||
instance Tokenize KeyValue where
|
||||
tokenize (KeyValue k v) = pair_ k v
|
||||
tokenize (KeyValue k v) = pair k v
|
||||
|
||||
newtype Tuple a = Tuple { tupleContents :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
|
@ -30,7 +30,7 @@ instance Evaluatable Statements where
|
||||
eval (Statements xs) = maybe (rvalBox unit) (runApp . foldMap1 (App . subtermRef)) (nonEmpty xs)
|
||||
|
||||
instance Tokenize Statements where
|
||||
tokenize = imperative_
|
||||
tokenize = imperative
|
||||
|
||||
-- | Conditional. This must have an else block, which can be filled with some default value when omitted in the source, e.g. 'pure ()' for C-style if-without-else or 'pure Nothing' for Ruby-style, in both cases assuming some appropriate Applicative context into which the If will be lifted.
|
||||
data If a = If { ifCondition :: !a, ifThenBody :: !a, ifElseBody :: !a }
|
||||
|
@ -70,7 +70,7 @@ instance Tokenize Send where
|
||||
tokenize Send{..} = within TCall $ do
|
||||
maybe (pure ()) (\r -> r *> yield TSep) sendReceiver
|
||||
fromMaybe (pure ()) sendSelector
|
||||
surround_ TParams (sep sendArgs)
|
||||
within' TParams $ sequenceA_ (sep sendArgs)
|
||||
fromMaybe (pure ()) sendBlock
|
||||
|
||||
data Require a = Require { requireRelative :: Bool, requirePath :: !a }
|
||||
|
@ -10,17 +10,15 @@ module Reprinting.Tokenize
|
||||
, yield
|
||||
, control
|
||||
, within
|
||||
, within'
|
||||
, log
|
||||
, ignore
|
||||
|
||||
, sep
|
||||
, sepTrailing
|
||||
, surround_
|
||||
, list_
|
||||
, hash_
|
||||
, pair_
|
||||
, imperative_
|
||||
|
||||
, list
|
||||
, hash
|
||||
, pair
|
||||
, imperative
|
||||
-- * Tokenize interface
|
||||
, Tokenize (..)
|
||||
-- * Invocation/results
|
||||
@ -28,7 +26,7 @@ module Reprinting.Tokenize
|
||||
) where
|
||||
|
||||
import Prelude hiding (fail, log)
|
||||
import Prologue hiding (Element)
|
||||
import Prologue hiding (hash, Element)
|
||||
|
||||
import Control.Monad.Effect
|
||||
import Control.Monad.Effect.Reader
|
||||
@ -66,6 +64,10 @@ log = control . Log
|
||||
within :: Context -> Tokenizer () -> Tokenizer ()
|
||||
within c r = control (Enter c) *> r <* control (Exit c)
|
||||
|
||||
-- | Like 'within', but adds 'TOpen' and 'TClose' elements around the action.
|
||||
within' :: Context -> Tokenizer () -> Tokenizer ()
|
||||
within' c x = within c $ yield TOpen *> x <* yield TClose
|
||||
|
||||
-- | Emit a sequence of tokens interspersed with 'TSep'.
|
||||
sep :: Foldable t => t (Tokenizer ()) -> [Tokenizer ()]
|
||||
sep = intersperse (yield TSep) . toList
|
||||
@ -74,29 +76,24 @@ sep = intersperse (yield TSep) . toList
|
||||
sepTrailing :: Foldable t => t (Tokenizer ()) -> [Tokenizer ()]
|
||||
sepTrailing = foldr (\x acc -> x : yield TSep : acc) mempty
|
||||
|
||||
-- | Emit a sequence of tokens within the given context with appropriate
|
||||
-- 'TOpen', 'TClose' tokens surrounding.
|
||||
surround_ :: Foldable t => Context -> t (Tokenizer ()) -> Tokenizer ()
|
||||
surround_ c xs = within c $ yield TOpen *> sequenceA_ xs <* yield TClose
|
||||
|
||||
-- | Emit a sequence of tokens within a 'TList' Context with appropriate 'TOpen',
|
||||
-- 'TClose' tokens surrounding.
|
||||
list_ :: Foldable t => t (Tokenizer ()) -> Tokenizer ()
|
||||
list_ = surround_ TList . sep
|
||||
list :: Foldable t => t (Tokenizer ()) -> Tokenizer ()
|
||||
list = within' TList . sequenceA_ . sep
|
||||
|
||||
-- | Emit a sequence of tokens within a 'THash' Context with appropriate
|
||||
-- 'TOpen', 'TClose' tokens surrounding and interspersing 'TSep'.
|
||||
hash_ :: Foldable t => t (Tokenizer ()) -> Tokenizer ()
|
||||
hash_ = surround_ THash . sep
|
||||
hash :: Foldable t => t (Tokenizer ()) -> Tokenizer ()
|
||||
hash = within' THash . sequenceA_ . sep
|
||||
|
||||
-- | Emit key value tokens with a 'TSep' within an TPair Context
|
||||
pair_ :: Tokenizer () -> Tokenizer () -> Tokenizer ()
|
||||
pair_ k v = within TPair $ k *> yield TSep <* v
|
||||
pair :: Tokenizer () -> Tokenizer () -> Tokenizer ()
|
||||
pair k v = within TPair $ k *> yield TSep <* v
|
||||
|
||||
-- | Emit a sequence of tokens within an Imperative Context with appropriate
|
||||
-- 'TOpen', 'TClose' tokens surrounding and interspersing 'TSep'.
|
||||
imperative_ :: Foldable t => t (Tokenizer ()) -> Tokenizer ()
|
||||
imperative_ = surround_ Imperative . sep
|
||||
imperative :: Foldable t => t (Tokenizer ()) -> Tokenizer ()
|
||||
imperative = within' Imperative . sequenceA_ . sep
|
||||
|
||||
-- | Shortcut for @const (pure ())@, useful for when no action
|
||||
-- should be taken.
|
||||
@ -118,7 +115,7 @@ instance (HasField fields History, Show (Record fields), Tokenize a) => Tokenize
|
||||
tokenize t = withHistory t (tokenize (termFOut t))
|
||||
|
||||
instance Tokenize [] where
|
||||
tokenize = imperative_
|
||||
tokenize = imperative
|
||||
|
||||
-- | The top-level function. Pass in a 'Source' and a 'Term' and
|
||||
-- you'll get out a 'Seq' of 'Token's for later processing.
|
||||
|
Loading…
Reference in New Issue
Block a user