Skip to content

Commit

Permalink
Merge pull request #356 from mumuki/feature-normalize-partial-functions
Browse files Browse the repository at this point in the history
Feature normalize functions by parts
  • Loading branch information
flbulgarelli committed Mar 21, 2023
2 parents be40ca2 + 566b3b9 commit b7742d4
Show file tree
Hide file tree
Showing 7 changed files with 49 additions and 10 deletions.
21 changes: 20 additions & 1 deletion spec/GenericSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ import Language.Mulang.Normalizers.Haskell (haskellNormalizationOption
import Language.Mulang.Parsers.Haskell
import Language.Mulang.Parsers.Java (java)
import Language.Mulang.Parsers.JavaScript
import Language.Mulang.Parsers.Python (py2, py3)
import Language.Mulang.Parsers.Python (npy, py2, py3)
import Language.Mulang.Transform.Normalizer

nhs = normalize haskellNormalizationOptions . hs
Expand Down Expand Up @@ -82,10 +82,29 @@ spec = do
it "is False when constant is declared with a variable literal" $ do
declaresFunction (named "f") (hs "f = snd") `shouldBe` False

describe "with function declarations, npy" $ do
it "is True when a function by parts is declared" $ do
declaresFunction (named "f") (npy "def f(x):\n\tif x > 4:\n\t\treturn 1\n\telse:\n\t\treturn 5") `shouldBe` True

it "is True when a function by parts is declared using an imperative style" $ do
declaresFunction (named "f") (npy "def f(x):\n\tif x > 4:\n\t\treturn 1\n\treturn 5") `shouldBe` True

it "is False when a partial function is declared" $ do
declaresFunction (named "f") (npy "def f(x):\n\tif x > 4:\n\t\treturn 1\n") `shouldBe` False

describe "with function declarations, js" $ do
it "is True when functions is declared" $ do
declaresFunction (named "f") (js "function f(x) {return 1}") `shouldBe` True

it "is True when a function by parts is declared" $ do
declaresFunction (named "f") (js "function f(x) { if (x > 4) { return 1 } else { return 5 } }") `shouldBe` True

it "is True when a function by parts is declared using an imperative style" $ do
declaresFunction (named "f") (js "function f(x) { if (x > 4) { return 1 } return 5 }") `shouldBe` True

it "is False when a partial function is declared" $ do
declaresFunction (named "f") (js "function f(x) { if (x > 4) { return 1 } }") `shouldBe` False

it "is True when functions is declared" $ do
declaresFunction (named "f") (js "function f(x) {return 1}") `shouldBe` True

Expand Down
8 changes: 3 additions & 5 deletions spec/NormalizerSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,14 +6,12 @@ module NormalizerSpec (spec) where
import Language.Mulang.Parsers.Haskell (hs)
import Language.Mulang.Parsers.Java (java)
import Language.Mulang.Parsers.JavaScript (js)
import Language.Mulang.Parsers.Python (py)
import Language.Mulang.Parsers.Python (npy, py)
import Language.Mulang.Normalizers.Java (javaNormalizationOptions)
import Language.Mulang.Normalizers.Python (pythonNormalizationOptions)
import Language.Mulang.Normalizers.Haskell (haskellNormalizationOptions)
import Language.Mulang.Transform.Normalizer

njava = normalize javaNormalizationOptions . java
npy = normalize pythonNormalizationOptions . py
nhs = normalize haskellNormalizationOptions . hs

spec :: Spec
Expand Down Expand Up @@ -79,10 +77,10 @@ module NormalizerSpec (spec) where
let n = normalize options

it "does not insert return in single literal statement" $ do
n (py "def x(): x = 1") `shouldBe` SimpleProcedure "x" [] (Assignment "x" (MuNumber 1.0))
n (npy "def x(): x = 1") `shouldBe` SimpleProcedure "x" [] (Assignment "x" (MuNumber 1.0))

it "inserts return in single literal expression" $ do
n (py "def x(): 3") `shouldBe` SimpleProcedure "x" [] (Return (MuNumber 3.0))
n (npy "def x(): 3") `shouldBe` SimpleProcedure "x" [] (Return (MuNumber 3.0))

it "does not insert return in empty block" $ do
n (SimpleFunction "x" [] None) `shouldBe` (SimpleFunction "x" [] None)
Expand Down
1 change: 1 addition & 0 deletions src/Language/Mulang/Analyzer/Analysis/Json.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ instance FromJSON NormalizationOptions where
<*> v .:? "convertObjectLevelLambdaVariableIntoMethod" .!= convertObjectLevelLambdaVariableIntoMethod d
<*> v .:? "convertObjectLevelVariableIntoAttribute" .!= convertObjectLevelVariableIntoAttribute d
<*> v .:? "convertObjectIntoDict" .!= convertObjectIntoDict d
<*> v .:? "convertProcedureByPartsIntoFunction" .!= convertProcedureByPartsIntoFunction d
<*> v .:? "sortSequenceDeclarations" .!= sortSequenceDeclarations d
<*> v .:? "insertImplicitReturn" .!= insertImplicitReturn d
<*> v .:? "compactSequences" .!= compactSequences d
Expand Down
3 changes: 2 additions & 1 deletion src/Language/Mulang/Normalizers/JavaScript.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,5 +9,6 @@ javaScriptNormalizationOptions = unnormalized {
convertObjectLevelFunctionIntoMethod = True,
convertObjectLevelLambdaVariableIntoMethod = True,
convertObjectLevelVariableIntoAttribute = True,
sortSequenceDeclarations = SortUniqueNonVariables
sortSequenceDeclarations = SortUniqueNonVariables,
convertProcedureByPartsIntoFunction = True
}
3 changes: 2 additions & 1 deletion src/Language/Mulang/Normalizers/Python.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,5 +4,6 @@ import Language.Mulang.Transform.Normalizer (unnormalized, NormalizationOptions(

pythonNormalizationOptions :: NormalizationOptions
pythonNormalizationOptions = unnormalized {
sortSequenceDeclarations = SortAllNonVariables
sortSequenceDeclarations = SortUniqueNonVariables,
convertProcedureByPartsIntoFunction = True
}
6 changes: 5 additions & 1 deletion src/Language/Mulang/Parsers/Python.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
module Language.Mulang.Parsers.Python (
npy,
py,
py2,
py3,
Expand All @@ -10,9 +11,11 @@ import qualified Language.Mulang.Ast as M
import qualified Language.Mulang.Ast.Operator as O
import Language.Mulang.Builder (compactMap, compactTuple)
import Language.Mulang.Parsers
import Language.Mulang.Transform.Normalizer (normalize)

import qualified Language.Python.Version3.Parser as Python3
import qualified Language.Python.Version2.Parser as Python2
import Language.Mulang.Normalizers.Python (pythonNormalizationOptions)
import Language.Python.Common.Token (Token)
import Language.Python.Common.AST

Expand All @@ -23,7 +26,8 @@ import Data.Maybe (fromMaybe, listToMaybe)
import Control.Fallible
import Control.Monad (msum)

py, py2, py3 :: Parser
npy, py, py2, py3 :: Parser
npy = normalize pythonNormalizationOptions . py
py = py3
py2 = parsePythonOrFail Python2.parseModule
py3 = parsePythonOrFail Python3.parseModule
Expand Down
17 changes: 16 additions & 1 deletion src/Language/Mulang/Transform/Normalizer.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveGeneric, ViewPatterns #-}

module Language.Mulang.Transform.Normalizer (
normalize,
Expand All @@ -25,6 +25,7 @@ data NormalizationOptions = NormalizationOptions {
convertObjectLevelLambdaVariableIntoMethod :: Bool,
convertObjectLevelVariableIntoAttribute :: Bool,
convertObjectIntoDict :: Bool,
convertProcedureByPartsIntoFunction :: Bool,
sortSequenceDeclarations :: SequenceSortMode,
insertImplicitReturn :: Bool,
compactSequences :: Bool,
Expand All @@ -46,6 +47,7 @@ unnormalized = NormalizationOptions {
convertObjectLevelLambdaVariableIntoMethod = False,
convertObjectLevelVariableIntoAttribute = False,
convertObjectIntoDict = False,
convertProcedureByPartsIntoFunction = False,
sortSequenceDeclarations = SortNothing,
insertImplicitReturn = False,
compactSequences = False,
Expand All @@ -59,6 +61,7 @@ normalize ops (Application (Primitive op) [e1, e2]) | isCommutative op = Applica
normalize ops (LValue n (Lambda vars e)) | convertLambdaVariableIntoFunction ops = SimpleFunction n vars (normalize ops e)
normalize ops (LValue n (MuObject e)) | convertObjectVariableIntoObject ops = Object n (normalizeObjectLevel ops e)
normalize ops (MuObject e) | convertObjectIntoDict ops = MuDict . normalize ops . normalizeArrows $ e
normalize ops (SimpleProcedure name params body) | convertProcedureByPartsIntoFunction ops && isBodyByParts body = SimpleFunction name params (normalize ops body)
normalize ops (Object n e) = Object n (normalizeObjectLevel ops e)
normalize ops (Sequence es) = normalizeSequence ops . sortDeclarations ops . mapNormalize ops $ es
--
Expand Down Expand Up @@ -106,6 +109,18 @@ normalizeObjectLevel ops (LValue n e) | convertObjectLevelVariab
normalizeObjectLevel ops (Sequence es) = normalizeSequence ops (map (normalizeObjectLevel ops) es)
normalizeObjectLevel ops e = normalize ops e

isBodyByParts (If _ ifTrue ifFalse) = isBodyPart ifTrue && isBodyPart ifFalse
isBodyByParts (Sequence
(reverse ->
(If _ ifTrue ifFalse) : _)) = isBodyPart ifTrue && isBodyPart ifFalse
isBodyByParts _ = False

isBodyPart (Return _) = True
isBodyPart (Sequence
(reverse ->
(Return _ : _))) = True
isBodyPart _ = False

normalizeEquation :: NormalizationOptions -> Equation -> Equation
normalizeEquation ops = mapEquation (normalize ops) (normalizeBody ops)

Expand Down

0 comments on commit b7742d4

Please sign in to comment.