-- IMPORTY -------------------------------------------------- {{{ {-# LANGUAGE TemplateHaskell, NoMonomorphismRestriction #-} module Lecture07 where import Control.Lens import Data.Semigroup import Data.Monoid hiding (First, Last) import qualified Data.Set as S -- }}} -- DATOVÉ STRUKTURY ----------------------------------------- {{{ type User = String data Issue = Issue { _reporter :: User , _assignee :: Maybe User , _weight :: Int , _closed :: Bool } deriving Show data Repo = Repo { _maintainer :: User , _issues :: [Issue] } deriving Show data Project = Project { _codeRepo :: Repo , _wikiRepo :: Maybe Repo } deriving Show makeLenses ''Issue makeLenses ''Repo makeLenses ''Project -- }}} -- VSTUPY NA HRANÍ ------------------------------------------ {{{ -- Tip: na výpis použijte 'pprint' ib015 = Project (Repo "xstill" -- Reporter Assignee Weight Closed [ Issue "xmatous3" (Just "xmatous3") 10 True , Issue "xjonas" Nothing 15 False , Issue "xjonas" (Just "xstill") 2 False , Issue "xstill" (Just "xstill") 0 False , Issue "xchlup2" Nothing 8 False , Issue "xmatous3" (Just "xbarnat") (-1) True ]) (Just $ Repo "xmatous3" -- Reporter Assignee Weight Closed [ Issue "xstill" Nothing 0 False , Issue "xbarnat" (Just "xmatous3") 5 True , Issue "xmatous3" (Just "xstill") 10 False , Issue "xmatous3" (Just "xmatous3") 0 True ]) ib016 = Project (Repo "xmatous3" -- Reporter Assignee Weight Closed [ Issue "xstill" Nothing 4 False , Issue "xkurecka" Nothing 10 True , Issue "xmatous3" (Just "xmichel") 10 False , Issue "xmatous3" (Just "xchlup2") 8 False , Issue "xmichel" (Just "xstill") 2 True ]) Nothing -- -- Krasopisce -------------------------- {{{ -- Tohle nijak nesouvisí s čočkami, je to zbastlené během hodiny a zarovnávání -- je nastavené natvrdo. Jediný účel je, aby výpisy dat na hraní vypadaly trochu -- lépe a vy jste mohli místo luštění výstupu věnovat čas skládání čoček :-). class Show a => Pretty a where pshow :: a -> String pshow = show pshowlist :: [a] -> String pshowlist xs = '[' : go (0 :: Int) xs where go _ [] = "\n]" go n (x:xs) = let comma = if n > 0 then "\n," else "" in comma ++ rpad 2 (pshow n) ++ ": " ++ pshow x ++ go (n+1) xs pprint :: a -> IO () pprint = putStrLn . pshow instance Pretty a => Pretty [a] where pshow = pshowlist instance Pretty Int instance Pretty Bool instance Pretty Char where pshowlist str = '"' : str ++ "\"" instance Pretty a => Pretty (Maybe a) where pshow Nothing = "Nothing" pshow (Just x) = "Just (" ++ pshow x ++ ")" instance Pretty Issue where pshow (Issue r a w c) = "Issue " ++ r' ++ a' ++ " W" ++ w' ++ " " ++ c' where r' = rpad 12 $ pshow r a' = case a of Just x -> " -> " ++ rpad 12 (pshow x) _ -> " " ++ rpad 12 "(unassg.)" w' = rpad 3 $ pshow w c' = if c then " closed " else "[ OPEN ]" instance Pretty Repo where pshow (Repo m i) = "Repo (" ++ pshow m ++ ") with issues:\n" ++ indent 5 (pshow i) instance Pretty Project where pshow (Project cr wr) = "Project\n" ++ repos where repos = "code: " ++ (indentafter $ pshow cr) ++ "\nwiki: " ++ (indentafter $ pshow wr) indentafter s = drop 6 (indent 6 s) rpad :: Int -> String -> String rpad n s | n <= len = s | otherwise = replicate (n - len) ' ' ++ s where len = length s indent :: Int -> String -> String indent n = init . unlines . map (replicate n ' ' ++) . lines -- -- }}} -- vim: fdm=marker -- }}}