Skip to content

Commit

Permalink
Merge pull request #90 from mumuki/feature-java
Browse files Browse the repository at this point in the history
Feature java
  • Loading branch information
flbulgarelli authored Jul 23, 2017
2 parents e6f4d59 + 3ce4373 commit ab04e6b
Show file tree
Hide file tree
Showing 19 changed files with 525 additions and 57 deletions.
18 changes: 11 additions & 7 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -92,20 +92,22 @@ Nice, we know. But not very awesome, it only can tell you if you are using a _bi

1. `assigns`: **any paradigm** is the given variable or attribute assigned?
1. `declares`: **any paradigm** is the given element declared?
1. `declaresAttribute`: **objects paradigm** is a given attribute declared?
1. `declaresClass`: **objects paradigm** is a given class declared?
1. `declaresAttribute`: **object oriented paradigm** is a given attribute declared?
1. `declaresClass`: **object oriented paradigm** is a given class declared?
1. `declaresComputation`: **any paradigm** that is, does the given computation - method, predicate, function, etc - exist?
1. `declaresComputationWithArity`: **any paradigm** that is, does the given computation have the exact given arity?
1. `declaresEntryPoint`: **any paradigm** is there a program entry point, like a `main` procedure?
1. `declaresEnumeration`: **imperative paradigm** is a given enumeration declared?
1. `declaresFact`: **logic paradigm** is a given logic fact declared?
1. `declaresFunction`: **functional/imperative paradigm** is a given function declared?
1. `declaresMethod`: **objects paradigm** is a given method declared?
1. `declaresObject`: **objects paradigm** is a given named object declared?
1. `declaresInterface`: **object oriented paradigm** is a given interface declared?
1. `declaresMethod`: **object oriented paradigm** is a given method declared?
1. `declaresObject`: **object oriented paradigm** is a given named object declared?
1. `declaresPredicate`: **logic paradigm** is a given rule o fact declared?
1. `declaresProcedure`: **imperative paradigm** is a given procedure declared?
1. `declaresRecursively`: **any paradigm** is a given computation declared using recusion?
1. `declaresRule`: **logic paradigm** is a given logic rule declared?
1. `declaresSuperclass`: **objects paradigm** is a given class declared as superclass?
1. `declaresSuperclass`: **object oriented paradigm** is a given class declared as superclass?
1. `declaresTypeAlias`: **any paradigm** is a given type synonym declared?
1. `declaresTypeSignature`: **any paradigm** is a given computation type signature declared?
1. `declaresVariable`: **any paradigm** is a given local o global variable declared?
Expand All @@ -123,6 +125,8 @@ Nice, we know. But not very awesome, it only can tell you if you are using a _bi
1. `hasRedundantReduction`: **logic paradigm** is a is-operator used to unify individuals that don't require a reduction, like `X is 4`
1. `hasTooShortBindings`: **any paradigm** whether a binding is too short and not part of domain language's jargon
1. `hasWrongCaseBindings`: **any paradigm** whether a binding does not match the domain language's case style
1. `implements`: **object oriented paradigm** is the given interface implemented?
1. `instantiates`: **object oriented paradigm** is the given class instantiated?
1. `isLongCode`: **any paradigm** has the code long sequences of statements?
1. `returnsNull`
1. `uses`: **any paradigm** is there any reference to the given element?
Expand All @@ -136,14 +140,14 @@ Nice, we know. But not very awesome, it only can tell you if you are using a _bi
1. `usesForall`: **logic paradigm** is the logic `forall` consult used?
1. `usesGuards`
1. `usesIf`: **any paradigm** is an `if` control structure used?
1. `usesInheritance`: **objects paradigm** is a superclass explicitly declared?
1. `usesInheritance`: **object oriented paradigm** is a superclass explicitly declared?
1. `usesLambda`
1. `usesNot`
1. `usesPatternMatching`
1. `usesRepeat`
1. `usesSwitch`
1. `usesUnificationOperator`: **logic paradigm** is the logic unification operator `=` used?
1. `usesWhile`
1. `usesWhile`: **imperative paradigm** is a `while` control structure used?

For example, let's go trickier:

Expand Down
2 changes: 2 additions & 0 deletions mulang.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,7 @@ library
Language.Mulang.Parsers
Language.Mulang.Parsers.Haskell
Language.Mulang.Parsers.Prolog
Language.Mulang.Parsers.Java
Language.Mulang.Parsers.JavaScript
Language.Mulang.Analyzer
Language.Mulang.Analyzer.Analysis
Expand All @@ -72,6 +73,7 @@ library
scientific ,
vector ,
haskell-src ,
language-java ,
language-javascript ,
aeson ,
inflections ,
Expand Down
4 changes: 4 additions & 0 deletions spec/ExpectationsCompilerSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ import Language.Mulang.Analyzer hiding (spec)
import Language.Mulang.Analyzer.ExpectationsCompiler (compileExpectation)
import Language.Mulang.Parsers.Haskell
import Language.Mulang.Parsers.JavaScript
import Language.Mulang.Parsers.Java

spec :: Spec
spec = do
Expand Down Expand Up @@ -166,3 +167,6 @@ spec = do
it "works with UsesLambda" $ do
run (hs "f 3 = 3") "f" "UsesLambda" `shouldBe` False

it "works with Implements" $ do
run (java "class Foo implements Bar {}") "Foo" "Implements:Bar" `shouldBe` True
run (java "class Foo implements Bar {}") "Foo" "Implements:Baz" `shouldBe` False
39 changes: 38 additions & 1 deletion spec/InspectorSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ import Test.Hspec
import Language.Mulang
import Language.Mulang.Parsers.Haskell
import Language.Mulang.Parsers.JavaScript
import Language.Mulang.Parsers.Java (java)
import Language.Mulang.Inspector.Generic.Smell
import Data.Maybe (fromJust)

Expand Down Expand Up @@ -199,7 +200,37 @@ spec = do
it "is True when anyone present, scoped" $ do
declaresObject anyone (js "var g = {}") `shouldBe` True

describe "usesInheritance" $ do
describe "declaresEnumeration" $ do
it "is True when present" $ do
declaresEnumeration (named "Direction") (Enumeration "Direction" ["SOUTH", "EAST", "WEST", "NORTH"]) `shouldBe` True

it "is False when not present" $ do
declaresEnumeration (named "Bird") (Class "Bird" (Just "Animal") MuNull) `shouldBe` False

describe "declaresInterface" $ do
it "is True when present" $ do
declaresInterface (named "Optional") (java "interface Optional { Object get(); }") `shouldBe` True

it "is False when not present" $ do
declaresInterface (named "Bird") (java "class Bird extends Animal {}") `shouldBe` False

describe "instantiates" $ do
it "is True when instantiates" $ do
instantiates (named "Bird") (java "class Main { void main(String[] args) { Animal a = new Bird(); } }") `shouldBe` True

it "is False when not instantiates" $ do
instantiates (named "Bird") (java "class Main { void main(String[] args) { Animal a = new Mammal(); } }") `shouldBe` False

describe "implements" $ do
it "is True when implements" $ do
implements (named "Bird") (java "class Eagle implements Bird {}") `shouldBe` True

it "is False when implements declaration not present" $ do
implements (named "Bird") (java "class Cell {}") `shouldBe` False

it "is False when a superinterface is declares" $ do
implements (named "Iterable") (java "interface Collection extends Iterable {}") `shouldBe` False

it "is True when present" $ do
usesInheritance (Class "Bird" (Just "Animal") MuNull) `shouldBe` True

Expand All @@ -219,6 +250,12 @@ spec = do
it "is True when any present" $ do
declaresMethod anyone (js "var f = {x: function(){}}") `shouldBe` True

it "is True when scoped in a class" $ do
scoped (declaresMethod (named "foo")) "A" (java "class A { void foo() {} }") `shouldBe` True

it "is False when scoped in a class and not present" $ do
scoped (declaresMethod (named "foo")) "A" (java "class A { void foobar() {} }") `shouldBe` False

it "is False when not present" $ do
declaresMethod (named "m") (js "var f = {x: function(){}}") `shouldBe` False

Expand Down
196 changes: 196 additions & 0 deletions spec/JavaSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,196 @@
{-# LANGUAGE QuasiQuotes, OverloadedStrings #-}

module JavaSpec (spec) where

import Test.Hspec
import Language.Mulang
import Language.Mulang.Parsers.Java

import Data.Text (Text, unpack)
import NeatInterpolation (text)

run :: Text -> Expression
run = java . unpack


spec :: Spec
spec = do
describe "parse" $ do
it "parses Simple Class" $ do
run "public class Foo {}" `shouldBe` Class "Foo" Nothing MuNull

it "parsers Class With Superclass" $ do
run "public class Foo extends Bar {}" `shouldBe` Class "Foo" (Just "Bar") MuNull

it "parses Simple Interface" $ do
run "public interface Foo {}" `shouldBe` Interface "Foo" [] MuNull

it "parses Simple Interface With Messages" $ do
run "public interface Foo { void foo(); }" `shouldBe` Interface "Foo" [] (TypeSignature "foo" [] "void")

it "parses Simple Interface With Messages With Params" $ do
run "public interface Foo { void foo(String x, int y); }" `shouldBe` Interface "Foo" [] (TypeSignature "foo" ["String", "int"] "void")


it "parses Interface with superinterfaces" $ do
run "public interface Foo extends Bar, Baz {}" `shouldBe` Interface "Foo" ["Bar", "Baz"] MuNull

it "parses Class With Methods" $ do
run [text|
class Foo {
public void hello() {}
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] MuNull)

it "parses Empty Returns" $ do
run [text|class Foo {
public void hello() { return; }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (Return MuNull))

it "parses Strings In Returns" $ do
run [text|class Foo {
public String hello() { return "hello"; }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (Return (MuString "hello")))

it "parses Int In Returns" $ do
run [text|class Foo {
public int hello() { return 1; }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (Return (MuNumber 1)))

it "parses Double In Returns" $ do
run [text|class Foo {
public double hello() { return 453.2; }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (Return (MuNumber 453.2)))

it "parses Bools In Returns" $ do
run [text|class Foo {
public boolean hello() { return true; }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (Return MuTrue))

it "parses Negation In Returns" $ do
run [text|class Foo {
public boolean hello() { return !true; }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (Return (SimpleSend MuTrue "!" [])))

it "parses Chars In Returns" $ do
run [text|class Foo {
public char hello() { return 'f'; }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (Return (MuString "f")))

it "parses Parameters" $ do
run "public class Foo extends Bar { int succ(int y) {} }" `shouldBe` Class "Foo" (Just "Bar") (SimpleMethod "succ" [VariablePattern "y"] MuNull)

it "parses Enums" $ do
run "public enum Foo { A, B }" `shouldBe` Enumeration "Foo" ["A", "B"]

it "parsesMain" $ do
run [text|
public class MyMain {
public static void main(String[] args) { }
}|] `shouldBe` Class "MyMain" Nothing (EntryPoint "main" MuNull)

it "parses Variables And Ints" $ do
run [text|
class Foo {
public void hello() { int x = 1; }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (Variable "x" (MuNumber 1)))

it "parses Variables And Ints" $ do
run [text|
class Foo {
public void hello() { Foo x = this; }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (Variable "x" Self))

it "parses Variables And ternaries" $ do
run [text|
class Foo {
public void hello() { Foo x = true ? this : this; }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (Variable "x" (If MuTrue Self Self)))

it "parses Variables without initialization" $ do
run [text|
class Foo {
public void hello() { int x; }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (Variable "x" MuNull))

it "parses self-send" $ do
run [text|
class Foo {
public void hello() { f(); }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (SimpleSend Self "f" []))

it "parses self-send" $ do
run [text|
class Foo {
public void hello() { f(2); }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (SimpleSend Self "f" [MuNumber 2]))

it "parses explict self-send" $ do
run [text|
class Foo {
public void hello() { this.f(); }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (SimpleSend Self "f" []))

it "parses argument-send" $ do
run [text|
class Foo {
public void hello(String g) { g.toString(); }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [VariablePattern "g"] (SimpleSend (Reference "g") "toString" []))

it "parses expression-send" $ do
run [text|
class Foo {
public void hello(String g) { g.size().toString(); }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [VariablePattern "g"] (SimpleSend (SimpleSend (Reference "g") "size" []) "toString" []))


it "parses Ifs with empty braces" $ do
run [text|
class Foo {
public void hello() { if (true) { } }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (If MuTrue MuNull MuNull))

it "parses Ifs with return in braces" $ do
run [text|
class Foo {
public void hello() { if (true) { return true; } else { return false; } }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (If MuTrue (Return MuTrue) (Return MuFalse)))

it "parses Ifs with equal comparisons on conditions" $ do
run [text|
class Foo {
public void hello(String x) { if (x == "foo") { } }
}|] `shouldBe` Class "Foo" Nothing (
SimpleMethod "hello" [VariablePattern "x"] (
If (Send (Reference "x") Equal [MuString "foo"])
MuNull
MuNull))

it "parses Ifs with not-equal comparisons on conditions" $ do
run [text|
class Foo {
public void hello(String x) { if (x != "foo") { } }
}|] `shouldBe` Class "Foo" Nothing (
SimpleMethod "hello" [VariablePattern "x"] (
If (Send (Reference "x") NotEqual [MuString "foo"])
MuNull
MuNull))

it "parsesAssignmentsAndDoubles" $ do
run [text|class Foo {
public void hello() { double m = 1.0; m = 3.4; }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (
Sequence [
Variable "m" (MuNumber 1.0),
Assignment "m" (MuNumber 3.4)]))

it "parses Lambdas" $ do
run [text|class Foo {
public Object hello() { return (int x) -> x + 1; }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (
Return (Lambda [VariablePattern "x"] (SimpleSend (Reference "x") "+" [MuNumber 1]))))

it "parses News" $ do
run [text|class Foo {
public Foo hello() { return new Bar(3); }
}|] `shouldBe` Class "Foo" Nothing (SimpleMethod "hello" [] (
Return (New "Bar" [MuNumber 3])))
6 changes: 3 additions & 3 deletions spec/SignatureSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,13 +45,13 @@ spec = do

describe "TypedSignature" $ do
it "simple variable type declaration" $ do
signaturesOf (hs "foo :: Int") `shouldBe` [TypedSignature "foo" ["Int"]]
signaturesOf (hs "foo :: Int") `shouldBe` [TypedSignature "foo" [] "Int"]

it "simple function type declaration" $ do
signaturesOf (hs "foo :: Int -> Int") `shouldBe` [TypedSignature "foo" ["Int", "Int"]]
signaturesOf (hs "foo :: Int -> Int") `shouldBe` [TypedSignature "foo" ["Int"] "Int"]

it "simple function tuple declaration" $ do
signaturesOf (hs "foo :: b -> (Int, [a])") `shouldBe` [TypedSignature "foo" ["b", "(Int, [a])"]]
signaturesOf (hs "foo :: b -> (Int, [a])") `shouldBe` [TypedSignature "foo" ["b"] "(Int, [a])"]

describe "NamedSignature" $ do
it "empty expression" $ do
Expand Down
1 change: 1 addition & 0 deletions spec/SignaturesAnalyzerSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ run language content style = analyse (signaturesAnalysis (CodeSample language co
spec = describe "SignturesAnalyzer" $ do
it "handles MulangStyle" $ do
(run Haskell "f x = x + 1" MulangStyle ) `shouldReturn` (result ["-- f(x)"])
(run Haskell "f :: Int -> String" MulangStyle ) `shouldReturn` (result ["-- f(Int): String"])

it "handles HaskellStyle" $ do
(run Haskell "f x = x + 1" HaskellStyle ) `shouldReturn` (result ["-- f x"])
Expand Down
1 change: 1 addition & 0 deletions src/Language/Mulang/Analyzer/Analysis.hs
Original file line number Diff line number Diff line change
Expand Up @@ -100,6 +100,7 @@ data Sample

data Language
= Json
| Java
| JavaScript
| Prolog
| Haskell deriving (Show, Eq, Generic)
Expand Down
4 changes: 4 additions & 0 deletions src/Language/Mulang/Analyzer/ExpectationsCompiler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,8 +64,10 @@ compileInspectionPrimitive = f
f "DeclaresComputationWithArity4" = binded (declaresComputationWithArity 4)
f "DeclaresComputationWithArity5" = binded (declaresComputationWithArity 5)
f "DeclaresEntryPoint" = binded declaresEntryPoint
f "DeclaresEnumeration" = binded declaresEnumeration
f "DeclaresFact" = binded declaresFact
f "DeclaresFunction" = binded declaresFunction
f "DeclaresInterface" = binded declaresInterface
f "DeclaresMethod" = binded declaresMethod
f "DeclaresObject" = binded declaresObject
f "DeclaresPredicate" = binded declaresPredicate
Expand All @@ -76,6 +78,8 @@ compileInspectionPrimitive = f
f "DeclaresTypeAlias" = binded declaresTypeAlias
f "DeclaresTypeSignature" = binded declaresTypeSignature
f "DeclaresVariable" = binded declaresVariable
f "Implements" = binded implements
f "Instantiates" = binded instantiates
f "Uses" = binded uses
f "UsesAnonymousVariable" = simple usesAnonymousVariable
f "UsesComposition" = simple usesComposition
Expand Down
Loading

0 comments on commit ab04e6b

Please sign in to comment.