mirror of
https://github.com/github/semantic.git
synced 2024-11-24 08:54:07 +03:00
Merge remote-tracking branch 'origin/master' into infinite-loops
This commit is contained in:
commit
8b2f2656cb
@ -6,6 +6,7 @@ module Data.Abstract.Number
|
||||
, liftReal
|
||||
, liftIntegralFrac
|
||||
, liftedExponent
|
||||
, liftedFloorDiv
|
||||
) where
|
||||
|
||||
import Data.Scientific
|
||||
@ -96,3 +97,8 @@ liftedExponent (Integer i) (Integer j) = whole (i ^ j)
|
||||
liftedExponent (Ratio i) (Integer j) = ratio (i ^^ j)
|
||||
liftedExponent i j = decim (fromFloatDigits (munge i ** munge j))
|
||||
where munge = (toRealFloat . toScientific) :: Number a -> Double
|
||||
|
||||
liftedFloorDiv :: Number a -> Number b -> SomeNumber
|
||||
liftedFloorDiv (Integer i) (Integer j) = whole (i `div` j)
|
||||
liftedFloorDiv i j = decim (fromIntegral @Prelude.Integer (floor (fromFloatDigits (munge i / munge j))))
|
||||
where munge = (toRealFloat . toScientific) :: Number a -> Double
|
||||
|
@ -2,10 +2,9 @@
|
||||
module Data.Syntax.Expression where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Number (liftIntegralFrac, liftReal, liftedExponent)
|
||||
import Data.Abstract.Number (liftIntegralFrac, liftReal, liftedExponent, liftedFloorDiv)
|
||||
import Data.Fixed
|
||||
import Diffing.Algorithm
|
||||
import Prelude
|
||||
import Prologue
|
||||
|
||||
-- | Typical prefix function application, like `f(x)` in many languages, or `f x` in Haskell.
|
||||
@ -50,6 +49,7 @@ data Arithmetic a
|
||||
| Minus !a !a
|
||||
| Times !a !a
|
||||
| DividedBy !a !a
|
||||
| FloorDivision !a !a
|
||||
| Modulo !a !a
|
||||
| Power !a !a
|
||||
| Negate !a
|
||||
@ -61,13 +61,14 @@ instance Show1 Arithmetic where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Arithmetic where
|
||||
eval = traverse subtermValue >=> go where
|
||||
go (Plus a b) = liftNumeric2 add a b where add = liftReal (+)
|
||||
go (Minus a b) = liftNumeric2 sub a b where sub = liftReal (-)
|
||||
go (Times a b) = liftNumeric2 mul a b where mul = liftReal (*)
|
||||
go (DividedBy a b) = liftNumeric2 div' a b where div' = liftIntegralFrac div (/)
|
||||
go (Modulo a b) = liftNumeric2 mod'' a b where mod'' = liftIntegralFrac mod mod'
|
||||
go (Power a b) = liftNumeric2 liftedExponent a b
|
||||
go (Negate a) = liftNumeric negate a
|
||||
go (Plus a b) = liftNumeric2 add a b where add = liftReal (+)
|
||||
go (Minus a b) = liftNumeric2 sub a b where sub = liftReal (-)
|
||||
go (Times a b) = liftNumeric2 mul a b where mul = liftReal (*)
|
||||
go (DividedBy a b) = liftNumeric2 div' a b where div' = liftIntegralFrac div (/)
|
||||
go (Modulo a b) = liftNumeric2 mod'' a b where mod'' = liftIntegralFrac mod mod'
|
||||
go (Power a b) = liftNumeric2 liftedExponent a b
|
||||
go (Negate a) = liftNumeric negate a
|
||||
go (FloorDivision a b) = liftNumeric2 liftedFloorDiv a b
|
||||
|
||||
-- | Regex matching operators (Ruby's =~ and ~!)
|
||||
data Match a
|
||||
|
@ -23,10 +23,8 @@ type Syntax =
|
||||
, Literal.Float
|
||||
, Literal.KeyValue
|
||||
, Literal.Null
|
||||
, Literal.String
|
||||
, Literal.TextElement
|
||||
, Syntax.Error
|
||||
, []
|
||||
]
|
||||
|
||||
type Term = Term.Term (Union Syntax) (Record Location)
|
||||
|
@ -297,7 +297,7 @@ binaryOperator = makeTerm' <$> symbol BinaryOperator <*> children (infixTerm exp
|
||||
, (inj .) . Expression.Times <$ symbol AnonStar
|
||||
, (inj .) . Expression.Times <$ symbol AnonAt -- Matrix multiplication, TODO: May not want to assign to Expression.Times.
|
||||
, (inj .) . Expression.DividedBy <$ symbol AnonSlash
|
||||
, (inj .) . Expression.DividedBy <$ symbol AnonSlashSlash
|
||||
, (inj .) . Expression.FloorDivision <$ symbol AnonSlashSlash
|
||||
, (inj .) . Expression.Modulo <$ symbol AnonPercent
|
||||
, (inj .) . Expression.Power <$ symbol AnonStarStar
|
||||
, (inj .) . Expression.BOr <$ symbol AnonPipe
|
||||
|
@ -63,12 +63,12 @@
|
||||
(
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
{+(DividedBy
|
||||
{+(Integer)+}
|
||||
{+(Identifier)+})+}
|
||||
{-(Times
|
||||
{ (Times
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})
|
||||
{-(Integer)-})
|
||||
->(DividedBy
|
||||
{+(Integer)+}
|
||||
{+(Identifier)+}) })
|
||||
(Empty)))
|
||||
(Pattern
|
||||
{ (Identifier)
|
||||
@ -80,12 +80,12 @@
|
||||
(
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
{+(Times
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+}
|
||||
{-(DividedBy
|
||||
{ (DividedBy
|
||||
{-(Integer)-}
|
||||
{-(Identifier)-})-})
|
||||
{-(Identifier)-})
|
||||
->(Times
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+}) })
|
||||
(Empty)))
|
||||
(Pattern
|
||||
(Identifier)
|
||||
|
@ -63,12 +63,12 @@
|
||||
(
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
{+(Times
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+}
|
||||
{-(DividedBy
|
||||
{ (DividedBy
|
||||
{-(Integer)-}
|
||||
{-(Identifier)-})-})
|
||||
{-(Identifier)-})
|
||||
->(Times
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+}) })
|
||||
(Empty)))
|
||||
(Pattern
|
||||
{ (Identifier)
|
||||
@ -80,12 +80,12 @@
|
||||
(
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
{+(DividedBy
|
||||
{+(Integer)+}
|
||||
{+(Identifier)+})+}
|
||||
{-(Times
|
||||
{ (Times
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})
|
||||
{-(Integer)-})
|
||||
->(DividedBy
|
||||
{+(Integer)+}
|
||||
{+(Identifier)+}) })
|
||||
(Empty)))
|
||||
(Pattern
|
||||
(Identifier)
|
||||
|
@ -26,7 +26,7 @@
|
||||
(Modulo
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
{ (DividedBy
|
||||
{ (FloorDivision
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})
|
||||
->(Power
|
||||
@ -35,7 +35,7 @@
|
||||
{ (Power
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})
|
||||
->(DividedBy
|
||||
->(FloorDivision
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}) }
|
||||
{+(Modulo
|
||||
|
@ -29,10 +29,10 @@
|
||||
{ (Power
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})
|
||||
->(DividedBy
|
||||
->(FloorDivision
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}) }
|
||||
{ (DividedBy
|
||||
{ (FloorDivision
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})
|
||||
->(Power
|
||||
|
@ -14,7 +14,7 @@
|
||||
(Modulo
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(DividedBy
|
||||
(FloorDivision
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Power
|
||||
|
@ -17,7 +17,7 @@
|
||||
(Power
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(DividedBy
|
||||
(FloorDivision
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Modulo
|
||||
|
Loading…
Reference in New Issue
Block a user