Skip to content

Instantly share code, notes, and snippets.

@JuanFdS
Created May 11, 2016 02:11
Show Gist options
  • Save JuanFdS/4ec1e4c02ca96fe24708b2924cf11cb5 to your computer and use it in GitHub Desktop.
Save JuanFdS/4ec1e4c02ca96fe24708b2924cf11cb5 to your computer and use it in GitHub Desktop.
-- TP Paradigmas - Watchmen
-- Alejo Berardino 155498-0
-- El código está escrito en inglés. Trabajo hace años así y es una costumbre difícil
-- de cambiar. De ser necesario puedo traducirlo sin problemas.
-- Por esto también incluí equivalencias al final a los nombres del enunciado en español.
-- Para simplificar la codificación del tp usé un par de packages extra.
-- Control.Lens permite la creación de "lentes" para un registro dado.
-- Una lente contienen getter y setter para una propiedad de ese registro.
-- Esto ahorra tener que escribir cosas como:
-- getName (Watchman n _ _) = n
-- setName (Watchman n s d) fn = Watchman (fn n) s d
-- La extensión del lenguaje TemplateHaskell es para crear las lentes de la sig. manera:
-- makeLenses ''Watchman
{-# LANGUAGE TemplateHaskell #-}
module TPFunctions where
import Control.Lens
import Control.Arrow
import Data.List
import Data.Ord
-- Data types
data Watchman = Watchman {_name :: String,
_skills :: [String],
_debut :: Int }
someWatchmen = [ Watchman "The Comedian" ["Strength"] 1942 ,
Watchman "Nite Owl" ["Fighting", "Engineering"] 1963,
Watchman "Rorschach" ["Perseverance", "Deduction", "Stealth"] 1964,
Watchman "Silk Spectre" ["Fighting", "Stealth", "Strength"] 1962,
Watchman "Ozymandias" ["Intelligence", "Even more intelligence"] 1968,
Watchman "Nite Owl" ["Fighting", "Intelligence", "Strength"] 1939,
Watchman "Silk Spectre" ["Fighting", "Stealth"] 1940 ]
data GovtAgent = GovtAgent {_agent :: String,
_program :: String } deriving (Show)
someGovtAgents = [ GovtAgent "Jack Bauer" "24",
GovtAgent "The Comedian" "Watchman",
GovtAgent "Dr. Manhattan" "Watchman",
GovtAgent "Liam Neeson" "Taken"]
-- Create lenses for our data types
makeLenses ''Watchman
makeLenses ''GovtAgent
-- Show instances to prettify output (helps in dev and testing the story)
instance Show Watchman where
show (Watchman name skills debut) = "\n " ++ show name ++ ", " ++ show skills ++ ", " ++ show debut
-- Eq and Ord instances where necessary
instance Eq Watchman where
(Watchman name1 _ _) == (Watchman name2 _ _) = name1 == name2
-- Aux Functions --
addCynicism :: Watchman -> Watchman
addCynicism = over skills (++ ["Cynicism"])
addCynicismIfAgent :: [GovtAgent] -> Watchman -> Watchman
addCynicismIfAgent agents wman | any ((== view name wman).view agent) agents = addCynicism wman
| otherwise = wman
keepYoungest :: Watchman -> Watchman -> Watchman
keepYoungest w1 w2 | view debut w1 > view debut w2 = w1
| otherwise = w2
removeOldWatchmen :: [Watchman] -> Watchman
removeOldWatchmen = foldr keepYoungest =<< head
-- Esto se podría hacer con Data.Time, pero no creo que entre en el scope de lo que pide el tp
currentYear :: Int
currentYear = 2016
-- (A) Eventos --
dissapearWatchman :: String -> [Watchman] -> [Watchman]
dissapearWatchman = filter. (. view name). (/=)
vietnamWar :: [GovtAgent] -> [Watchman] -> [Watchman]
vietnamWar = map. addCynicismIfAgent
labAccident :: Int -> [Watchman] -> [Watchman]
labAccident = (:). Watchman "Dr. Manhattan" ["Manipulate matter"]
keeneAct :: [Watchman] -> [Watchman]
keeneAct = map removeOldWatchmen. group. sortOn (view name)
nycDestruction :: [Watchman] -> [Watchman]
nycDestruction = dissapearWatchman "Rorschach". dissapearWatchman "Dr. Manhattan"
-- (B) Historia --
-- No entiendo que pide el enunciado, aplicar una sucesión de funciones se puede
-- escribir simplemente como la composición de las mismas:
story :: [Watchman] -> [Watchman]
story = nycDestruction.
dissapearWatchman "The Comedian".
vietnamWar someGovtAgents.
labAccident 1959.
keeneAct
playStory = story someWatchmen
-- Obviamente desde el punto de vista del lector quedaría inverso al orden normal.
-- Para eso se puede usar, por ejemplo, el operador para l2r composition de Control.Arrow:
story' = keeneAct >>>
labAccident 1959 >>>
vietnamWar someGovtAgents >>>
dissapearWatchman "The Comedian" >>>
nycDestruction
playStory' = story' someWatchmen
-- Como alternativa uno podría desarrollar su propia syntactic sugar pero sería redundante
onceUponATimeThe = id
happenedAndThenThe = flip (.)
happenedAndEverythingEndedWithThe = flip (.)
thanksTo = id
playStory'' = onceUponATimeThe keeneAct `happenedAndThenThe`
labAccident 1959 `happenedAndThenThe`
vietnamWar someGovtAgents `happenedAndThenThe`
dissapearWatchman "The Comedian" `happenedAndEverythingEndedWithThe`
nycDestruction `thanksTo` someWatchmen
-- Para testing hice otra alternativa para contar la historia en el main, ver ahí
-- (C) Grandes Héroes --
saviorsName :: [Watchman] -> String
saviorsName = view name. maximumBy (comparing $ length.view skills)
chosenOne :: [Watchman] -> String
chosenOne = head.view skills.maximumBy (comparing $ length.words.view name)
patriarch :: [Watchman] -> Int
patriarch = maximum.map ((currentYear-).view debut)
-- Dejo esto por si usan some testing automatizado y para escribir la hist en español --
-- Data types
algunosVigilantes = someWatchmen
agentesDelGobierno = someGovtAgents
-- (A) Eventos
desaparecerWatchman = dissapearWatchman
guerraDeVietnam = vietnamWar
accidenteDeLaboratorio = labAccident
actaDeKeene = keeneAct
destruccionDeNiuShork = nycDestruction
-- (C) Grandes Héroes
nombreDelSalvador = saviorsName
elElegido = chosenOne
patriarca = patriarch
-- (B) Historia
-- Nada, son a criterio propio
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment