Skip to content

Commit

Permalink
FINAL
Browse files Browse the repository at this point in the history
  • Loading branch information
LSinzker committed May 11, 2017
1 parent 3ad7361 commit 105c9da
Show file tree
Hide file tree
Showing 7 changed files with 146 additions and 67 deletions.
59 changes: 59 additions & 0 deletions LFCFPTestes.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,59 @@
module LFCFPTestes where

import LFCFP

import Test.HUnit

v5 = Valor 5
v3 = Valor 3

s1 = Soma v5 v3

s2 = Soma s1 v3

-- let x = 5 in x + x
let01 = Let "x" (Valor 5) (Soma (Ref "x") (Ref "x"))

-- let x = 5 in let y = 10 in x + y
let02 = Let "x" (Valor 5)
(Let "y" (Valor 10) (Soma (Ref "x") (Ref "y")))

-- let x = 5 in x + let x = 10 in x + 3
let03 = Let "x" (Valor 5)
(Soma (Ref "x") (Let "x" (Valor 10) (Soma (Ref "x") (Valor 3))))

-- let x = 5 in let y = x in y
let04 = Let "x" (Valor 5)
(Let "y" (Ref "x") (Ref "y"))

-- let x = 5 in let x = x in x
let05 = Let "x" (Valor 5)
(Let "x" (Ref "x") (Ref "x"))

teste1 = TestCase (assertEqual "avaliar 5" 5 (toInt v5))

teste2 = TestCase (assertEqual "avaliar 5 + 3" 8 (toInt (avaliar s1 [])))

teste3 = TestCase (assertEqual "avaliar (5 + 3) + 3" 11 (toInt (avaliar s2 [])))

teste4 = TestCase (assertEqual "avaliar let x = 5 in x + x" 10 (toInt(avaliar let01 [])))

teste5 = TestCase (assertEqual "avaliar let x = 5 in let y = 10 in x + y" 15 (toInt(avaliar let02 [])))

teste6 = TestCase (assertEqual "avaliar let x = 5 in x + let x = 10 in x + 3" 18 (toInt(avaliar let03 [])))

teste7 = TestCase (assertEqual "avaliar let x = 5 in let y = x in y" 5 (toInt(avaliar let04 [])))

teste8 = TestCase (assertEqual "avaliar let x = 5 in let x = x in x" 5 (toInt(avaliar let05 [])))

todosOsTestes = TestList [ teste1
, teste2
, teste3
, teste4
, teste5
, teste6
, teste7
, teste8
]

executarTestes = runTestTT todosOsTestes
69 changes: 16 additions & 53 deletions LFCFT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,27 +29,10 @@ toInt (Valor n) = n

avaliar :: Expressao -> Expressao
avaliar (Valor n) = (Valor n)

avaliar (Soma e d) = Valor (ve + vd)
where
(Valor ve) = avaliar e
(Valor vd) = avaliar d

avaliar (Subtracao e d) = Valor (ve - vd)
where
(Valor ve) = avaliar e
(Valor vd) = avaliar d

avaliar (Multiplicacao e d) = Valor (ve * vd)
where
(Valor ve) = avaliar e
(Valor vd) = avaliar d

avaliar (Divisao e d) = Valor (ve `div` vd)
where
(Valor ve) = avaliar e
(Valor vd) = avaliar d

avaliar (Soma e d) = avaliarExpBin e d (+)
avaliar (Subtracao e d) = avaliarExpBin e d (-)
avaliar (Multiplicacao e d) = avaliarExpBin e d (*)
avaliar (Divisao e d) = avaliarExpBin e d div
avaliar (Lambda argFormal corpo) = (Lambda argFormal corpo)

avaliar (App exp1 exp2) =
Expand All @@ -59,8 +42,6 @@ avaliar (App exp1 exp2) =
otherwise -> error "aplicando uma expressao que nao eh lambda"

avaliar (Let subId expNomeada corpoExp) = avaliar (App exp1 exp2)
-- | corpoExp /= Let boundId namedExp bodyExp = substituicao subId expNomeada corpoExp
-- | otherwise = avaliar (App exp1 exp2)
where
Let boundId namedExp bodyExp = corpoExp
exp1 = Lambda subId corpoExp
Expand All @@ -70,38 +51,20 @@ avaliar (Ref var) = error "avaliando uma variavel livre."

substituicao :: Id -> Expressao -> Expressao -> Expressao
substituicao subId val (Valor n) = Valor n
substituicao subId val (Soma e d)
| d == Let boundId namedExp bodyExp = Soma (substituicao subId val e)(avaliar d)
| otherwise = Soma (substituicao subId val e)(substituicao subId val d)
where
Let boundId namedExp bodyExp = d

substituicao subId val (Subtracao e d)
| d == Let boundId namedExp bodyExp = Subtracao (substituicao subId val e)(avaliar d)
| otherwise = Subtracao (substituicao subId val e)(substituicao subId val d)
where
Let boundId namedExp bodyExp = d

substituicao subId val (Multiplicacao e d)
| d == Let boundId namedExp bodyExp = Multiplicacao (substituicao subId val e)(avaliar d)
| otherwise = Multiplicacao (substituicao subId val e)(substituicao subId val d)
where
Let boundId namedExp bodyExp = d

substituicao subId val (Divisao e d)
| d == Let boundId namedExp bodyExp = Divisao (substituicao subId val e)(avaliar d)
| otherwise = Divisao (substituicao subId val e)(substituicao subId val d)
where
Let boundId namedExp bodyExp = d

substituicao subId val (Let boundId namedExp bodyExp) =
substRef subId val (Let boundId namedExp bodyExp)
substituicao subId val (Soma e d) = Soma (substituicao subId val e)(substituicao subId val d)
substituicao subId val (Subtracao e d) = Subtracao (substituicao subId val e)(substituicao subId val d)
substituicao subId val (Multiplicacao e d) = Multiplicacao (substituicao subId val e)(substituicao subId val d)
substituicao subId val (Divisao e d) = Divisao (substituicao subId val e)(substituicao subId val d)
substituicao subId val (Let boundId expNomeada corpo)
| boundId == subId = (Let boundId (substituicao subId val expNomeada) corpo)
| otherwise = (Let boundId (substituicao subId val expNomeada) (substituicao subId val corpo))

substituicao subId val (Ref var)
| subId == var = val
| otherwise = (Ref var)

substRef :: Id -> Expressao -> Expressao -> Expressao
substRef subId val (Let boundId namedExp bodyExp)
| namedExp == (Ref subId) = Let boundId val bodyExp
| otherwise = Let boundId namedExp (substituicao subId val bodyExp)
avaliarExpBin :: Expressao -> Expressao -> (Int -> Int -> Int) -> Expressao
avaliarExpBin e d op = Valor (op ve vd)
where
(Valor ve) = avaliar e
(Valor vd) = avaliar d
7 changes: 0 additions & 7 deletions LFCFTTestes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,13 +24,6 @@ let02 = Let "x" (Valor 5)
let03 = Let "x" (Valor 5)
(Soma (Ref "x") (Let "x" (Valor 10) (Soma (Ref "x") (Valor 3))))

--avaliar ( Let "x" (Valor 5) (Soma (Ref "x") (Let "x" (Valor 10) (Soma (Ref "x") (Valor 3)))) )
--avaliar ( App (Lambda "x" (Soma (Ref "x") (Let "x" (Valor 10) (Soma (Ref "x") (Valor 3))))) (Valor 5))
----e---- ---------------------d----------------------
--avaliar ( substituicao "x" (Valor 5) (Soma (Ref "x") (Let "x" (Valor 10) (Soma (Ref "x") (Valor 3) ) ) ) )
--avaliar ( Soma (substituicao "x" (Valor 5) (Ref "x") (substituicao "x" (Valor 5) (Let "x" (Valor 10) (Soma (Ref "x") (Valor 3))))))
--avaliar ( Soma (Valor 5) )

-- let x = 5 in let y = x in y
let04 = Let "x" (Valor 5)
(Let "y" (Ref "x") (Ref "y"))
Expand Down
10 changes: 3 additions & 7 deletions LFLE01EMP.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,14 +30,14 @@ avaliar (Subtracao e d) amb = avaliar e amb - avaliar d amb
avaliar (Multiplicacao e d) amb = avaliar e amb * avaliar d amb
avaliar (Divisao e d) amb = avaliar e amb `div` avaliar d amb

avaliar (Aplicacao nome exp) amb
| length arg == length exp = avaliar (substAplica arg exp corpo) amb
avaliar (Aplicacao nome exp) amb =
avaliar(lets arg exp corpo) amb
where
(DecFuncao n arg corpo) = pesquisarFuncao nome amb

avaliar (Let subId expNomeada corpoExp) amb
|corpoExp /= (Aplicacao n e) = avaliar (substituicao subId (avaliar expNomeada amb) corpoExp) amb
|otherwise = avaliar (substAplica subIds vals corpo) amb
|otherwise = avaliar (lets subIds vals corpo) amb
where
Aplicacao nome e = corpoExp
DecFuncao n args corpo = pesquisarFuncao nome amb
Expand Down Expand Up @@ -65,10 +65,6 @@ substituicao subId val (Ref var)
| subId == var = (Valor val)
| otherwise = (Ref var)

-- ["z","y","x"]
substAplica :: [Id] -> [Expressao] -> Expressao -> Expressao
substAplica subIds vals corpo = lets subIds vals corpo

--subIds = ["z","y","x"]
--vals = [(Valor 4), (Valor 3), (Valor 2)]

Expand Down
1 change: 1 addition & 0 deletions LFLE02E.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@ avaliar (Aplicacao nome exp) amb ref = avaliar corpo amb ref'
(DecFuncao n arg corpo) = pesquisarFuncao nome amb
valor = avaliar exp amb ref
ref' = (arg, valor):ref

avaliar (Let subId expNomeada corpoExp) amb ref = avaliar corpoExp amb ref'
where
valor = avaliar expNomeada amb ref
Expand Down
3 changes: 3 additions & 0 deletions LFLEDTestes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,3 +22,6 @@ let01 = Let "x" (Valor 4)(apInc)
let02 = Let "y" (Valor 3)(Let "x" (Valor 4) (Aplicacao "add" (Valor 3)))

let03 = Let "x" (Valor 4)(Let "y" (Valor 3) (Aplicacao "add" (Valor 3)))

--let08 = let x=10 in let x=x+5 in x+2
let04 = Let "x" (Valor 10) (Let "x" (Soma (Ref "x")(Valor 5)) (Soma(Ref "x")(Valor 2)))
64 changes: 64 additions & 0 deletions LFLETestes.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,64 @@
module LFLETestes where

import LFLE02E

import Test.HUnit

inc :: DecFuncao
inc = DecFuncao "inc" "x" (Soma (Ref "x") (Valor 1))

sqr :: DecFuncao
sqr = DecFuncao "sqr" "x" (Multiplicacao (Ref "x") (Ref "x"))

f :: DecFuncao
f = DecFuncao "f" "p" (Ref "n")

app1 :: Expressao
app1 = Aplicacao "inc" (Valor 5)

app2 :: Expressao
app2 = Aplicacao "sqr" (Valor 5)

let1 :: Expressao
let1 = Let "x" (Valor 5) (Soma (Ref "x") (Ref "x"))

let2 :: Expressao
let2 = Let "x" (Valor 10) (Aplicacao "sqr" (Ref "x"))

let3 :: Expressao
let3 = Let "n" (Valor 5) (Aplicacao "f" (Valor 10))

let4 :: Expressao
let4 = Let "x" (Valor 10) (Soma (Ref "x") (Let "x" (Valor 5) (Soma (Ref "x") (Valor 8))))

let5 :: Expressao
let5 = Let "x" (Valor 10)
(Soma (Let "x" (Valor 5) (Soma (Ref "x") (Valor 8))) (Ref "x"))


amb = [inc, sqr, f]

testeInc = TestCase (assertEqual "avaliar inc 5" 6 (avaliar app1 amb []))

testeSqr = TestCase (assertEqual "avaliar sqr 5" 25 (avaliar app2 amb []))

testeLet1 = TestCase (assertEqual "avaliar let x = 5 in x + x" 10 (avaliar let1 [] []))

testeLet2 = TestCase (assertEqual "avaliar let x = 10 in sqr x)" 100 (avaliar let2 amb []))

testeLet3 = TestCase (assertEqual "avaliar let n = 5 in f 10)" 5 (avaliar let3 amb []))

testeLet4 = TestCase (assertEqual "avaliar let x = 10 in x + (let x = 5 in x + 8)" 28
(avaliar let4 [] []))

testeLet5 = TestCase (assertEqual "avaliar let x = 10 in (let x = 5 in x + 8) + x" 28
(avaliar let5 [] []))

todosOsTestes = TestList [ testeInc
, testeSqr
, testeLet1
, testeLet2
, testeLet3
]

executarTestes = runTestTT todosOsTestes

0 comments on commit 105c9da

Please sign in to comment.