Skip to content

Commit

Permalink
Add files via upload
Browse files Browse the repository at this point in the history
  • Loading branch information
LSinzker authored May 9, 2017
1 parent 9f90932 commit d0f00a1
Show file tree
Hide file tree
Showing 9 changed files with 513 additions and 20 deletions.
107 changes: 107 additions & 0 deletions LFCFT.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,107 @@
module LFCFT where

-- A linguagem LFCF suporta tanto
-- expressoes identificadas (LET) quanto
-- identificadores e funcoes de alta ordem
-- (com o mecanismo de expressoes lambda).

type Id = String

data Expressao = Valor Int
| Soma Expressao Expressao
| Subtracao Expressao Expressao
| Multiplicacao Expressao Expressao
| Divisao Expressao Expressao
| Let Id Expressao Expressao
| Ref Id
| Lambda Id Expressao
| App Expressao Expressao
deriving(Show, Eq)

-- O interpretador da linguagem LFCF
-- precisa ser melhor discutido, uma vez que
-- o tipo de retorno nao pode ser simplesmente
-- um inteiro. O que seria a avaliacao de uma
-- expressao lambda (\x -> x + 1)?

toInt :: Expressao -> Int
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 (Lambda argFormal corpo) = (Lambda argFormal corpo)

avaliar (App exp1 exp2) =
let expLambda = avaliar exp1
in case expLambda of
(Lambda argFormal corpo) -> avaliar (substituicao argFormal exp2 corpo)
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
exp2 = expNomeada

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 (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)
107 changes: 107 additions & 0 deletions LFCFTTestes.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,107 @@
module LFCFTTestes where

import LFCFT

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"))
-- (\x -> x+x)5
-- 10

-- 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))))

--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"))
-- let x=5
-- in let y=x
-- in 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


-- argFor exp2 ---------corpo---------
-- subId expNom -------corpoExp-------
--avaliar (Let "x" (Valor 5)(Soma (Ref "x")(Valor 1))) =======> (\x -> x+x)5
--avaliar (App ("x" (Soma(Ref "x")(Valor 1))) (Valor 5))
-- -------------exp1------------ ---exp2---
--avaliar (Let subId expNomeada corpoExp) = avaliar(App (Lambda subId (corpoExp)) expNomeada)

--avaliar (App (Lambda "x" (Soma(Ref"x")(Valor 1)))())
--let expLambda = avaliar exp1
--in case expLambda of
-- (Lambda arg corpo) ->

--let01 = Let "x" (Valor 5) (Soma (Ref "x") (Ref "x"))
-- (\x -> x+x)5
-- 10
--avaliar (Let "x"(Valor 5)(Soma(Ref "x")(Ref "x")))
--

--definindo expressoes lambda:
--incre = \x -> x+1
--incre x = x+1
--
--somar = \x -> \y -> x+y
--somar x y = x+y
--
--(\x -> x+4)4
--8
--
-- Let "x" (Valor 5) (Soma(Ref "x")(Ref "y"))
-- (\x -> x+x)5
-- 10
--
--(\x -> 5+5)1
--10
30 changes: 16 additions & 14 deletions LFLE01E.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@ data Expressao = Valor Int
| Let Id Expressao Expressao
| Ref Id
| Aplicacao Nome Expressao
| ExpExp Expressao Expressao
deriving(Show, Eq)

avaliar :: Expressao -> Ambiente -> Int
Expand Down Expand Up @@ -52,33 +51,36 @@ substituicao subId val (Subtracao e d) = Subtracao (substituicao subId val e)(su
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 namedExp bodyExp)
| subId == boundId = (Let boundId namedExp bodyExp)
| otherwise = Let boundId namedExp (substituicao subId val bodyExp)
| subId == boundId = (Let boundId namedExp bodyExp)
| otherwise = Let boundId namedExp (substituicao subId val bodyExp)

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

substituicao subId val (Aplicacao nome exp) = Aplicacao nome exp

pesqArg2 (Aplicacao vn ve) = Aplicacao vn ve

substAplica :: Id -> Int -> Expressao -> Ambiente -> Expressao
substAplica subId val (Valor n) amb = Valor n
substAplica subId val (Soma e d) amb = Soma (substituicao subId val e)(substituicao subId val d)
substAplica subId val (Subtracao e d) amb = Subtracao (substituicao subId val e)(substituicao subId val d)
substAplica subId val (Multiplicacao e d) amb = Multiplicacao (substituicao subId val e)(substituicao subId val d)
substAplica subId val (Divisao e d) amb = Divisao (substituicao subId val e)(substituicao subId val d)
substAplica subId val (Let boundId namedExp bodyExp) amb
| subId == boundId = (Let boundId namedExp bodyExp)
| otherwise = Let boundId namedExp (substAplica subId val bodyExp amb)
substAplica subId val (Let boundId namedExp bodyExp) amb =
substRef subId val (Let boundId namedExp bodyExp) amb

substAplica subId val (Ref var) amb
| subId == var = (Valor val)
| otherwise = (Ref var)

substAplica subId val (Let boundId namedExp bodyExp) amb
| subId == boundId = (Let boundId namedExp bodyExp)
| otherwise = Let boundId namedExp (substAplica subId val bodyExp amb)

substAplica subId val (Aplicacao nome exp) amb =
let (DecFuncao n arg corpo) = pesquisarFuncao nome amb
in Let subId (Valor val)(Let arg exp (corpo))

substRef :: Id -> Int -> Expressao -> Ambiente -> Expressao
substRef subId val (Let boundId namedExp bodyExp) amb
| namedExp == (Ref subId) = Let boundId (Valor val) bodyExp
| otherwise = Let boundId namedExp (substAplica subId val bodyExp amb)


-- Let boundId namedExp (substAplica subId val bodyExp amb)
5 changes: 1 addition & 4 deletions LFLE01EMP.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ 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
where
Aplicacao nome e = pesqArg2 corpoExp
Aplicacao nome e = corpoExp
DecFuncao n args corpo = pesquisarFuncao nome amb
subIds = [subId] ++ args -- merge (["z"] ["y", "z"]) = ["z","y","x"]
vals = [expNomeada] ++ e -- merge ([Valor 4], [(Valor 3), (Valor 2)]) = [(Valor 4), (Valor 3), (Valor 2)]
Expand All @@ -65,9 +65,6 @@ substituicao subId val (Ref var)
| subId == var = (Valor val)
| otherwise = (Ref var)

pesqArg2 :: Expressao -> Expressao
pesqArg2 (Aplicacao vn ve) = Aplicacao vn ve

-- ["z","y","x"]
substAplica :: [Id] -> [Expressao] -> Expressao -> Expressao
substAplica subIds vals corpo = lets subIds vals corpo
Expand Down
5 changes: 3 additions & 2 deletions LFLEEMPTestes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,15 +20,16 @@ let02 = Let "z" (Valor 4)(apSub)
let03 = Let "z" (Valor 4)(apMul)

avAdd = avaliar let01 amb
avSub = avaliar let02 amb
avMul = avaliar let03 amb

-- avaliar (Let "z" (Valor 4)(Aplicacao "apAdd" [(Valor 1), (Valor 2)])) (DecFuncao "add" ["x","y"] (Soma (Ref "z")(Soma (Ref "x")(Ref "y"))))
-- let z = 4
-- in let add x y = z+x+y
-- in add 1 2
-- >9

avSub = avaliar let02 amb
-- let z = 4
-- in let sub x y = z-(y-x)
-- in sub 2 1
-- >5
avMul = avaliar let03 amb
7 changes: 7 additions & 0 deletions LFLEETestes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,13 @@ let03 = Let "y" (Valor 8)(apSub)

let04 = Let "y" (Valor 10)(apDiv)

let05 = Let "x" (Valor 5)(Let "y" (Ref "x")(Ref "y"))

let06 = Let "x" (Valor 5)
(Let "x" (Ref "x") (Ref "x"))

let07 = Let "x" (Valor 5)
(Soma (Ref "x") (Let "x" (Valor 10) (Soma (Ref "x") (Valor 3))))

let11 = Let "y" (Valor 3)(Let "x" (Valor 4) apAdd)
-- subId val -------------------corpoExp----------------
Expand Down
Loading

0 comments on commit d0f00a1

Please sign in to comment.