--show :: a -> String --show x = data Pair a = P a a instance Show a => Show (Pair a) where show (P x y) = "<" ++ show x ++ ";" ++ show y ++ ">" data NestedList a = Atom { fromAtom :: a } | List { fromList :: [NestedList a] } instance Show a => Show (NestedList a) where show (Atom x) = "<" ++ show x ++ ">" show (List l) = "{" ++ (show $ head l) ++ concat (zipWith (++) (repeat ", ") $ map show $ tail l) ++ "}" ---------------- tableToFunc :: [(Char, Char)] -> (Char -> Char) tableToFunc t key = value where (_, value) : _ = filter ((key ==) . fst) t substCrypt :: [(Char, Char)] -> String -> String --substCrypt t s = map (\c -> tableToFunc t c) s --substCrypt t = map (\c -> tableToFunc t c) --substCrypt t = map (tableToFunc t) --substCrypt t = (map . tableToFunc) t substCrypt = map . tableToFunc {- substCrypt t --> (tableToFunc t)->f --> (map f) ((substCrypt t) s) --> (map f) s -} ------------ din cursul anterior: data Tree a = Nil | Leaf a | Node a [Tree a] deriving Eq instance Show a => Show (Tree a) where show tree = pt 0 tree where pt level tree = case tree of Nil -> space level ++ "- \n" Leaf val -> space level ++ show val ++ "\n" Node val children -> space level ++ show val ++ "\n" ++ if all isNil children then "" else concatMap (pt $ level + 1) children space sp = [' ' | _ <- [1..sp * 2]] isNil Nil = True isNil _ = False limit 0 _ = Nil limit n t = case t of Node v children -> Node v (map (limit (n-1)) children) otherwise -> t preord Nil = [] preord (Leaf val) = [val] preord (Node val children) = foldl (++) [val] $ map preord children treeB = mkTree 1 where mkTree n = Node n $ map mkTree $ map (+(2*n)) [0,1] ----------------------------------- class TreeLike t where toTree :: Eq a => (t a) -> Tree a instance TreeLike Tree where toTree = id instance TreeLike NestedList where toTree (Atom x) = Leaf x toTree (List []) = Nil toTree (List l@(_:_)) = Node x $ map toTree rest where -- l este x și rest (x, List rest) = findAtom l findAtom :: [NestedList a] -> (a, NestedList a) -- val de tip a este sub un Atom findAtom (Atom x : rest) = (x, List rest) findAtom (List l : rest) = let (r, restImbricat) = findAtom l in (r, List $ restImbricat : rest) l2 = List [List [List [Atom 1, Atom 2, Atom 3], Atom 4, Atom 5], List [Atom 6, Atom 7], Atom 8] l3 = List [List [Atom 1, Atom 2, Atom 3], Atom 4, Atom 5] {-- pentru l2 îmi doresc: (((1 2 3) 4 5) (6 7) 8) 1 2 6 8 3 4 5 7 --} -------------------------------- data Graph a = G { edges :: [(a, a)] } graph = G [(3, 8), (3, 10), (3, 5), (5, 11), (7, 8), (7, 11), (8, 3), (8, 8), (8, 9), (11, 2), (11, 5), (11, 9), (11, 10)] nodes (G []) = [] --nodes (G ((x, y):g)) = [x, y] ++ (filter (\n -> not $ elem n [x, y]) $ nodes $ G g) nodes (G ((x, y):g)) = [x, y] ++ (filter (not . (flip elem $ [x, y])) $ nodes $ G g) --outgoing v g = map snd $ filter (\e -> fst e == v) $ edges g outgoing v = map snd . filter ((==v) . fst) . edges instance TreeLike Graph where toTree g@(G edges) = dfs [] $ head $ nodes g where dfs visited v | elem v visited = Nil | otherwise = case filter (not . flip elem (v : visited)) $ outgoing v g of [] -> Leaf v children@(_:_) -> Node v $ foldl dfsChild [] children where -- map (dfs (v : visited)) children dfsChild previousTrees c = previousTrees ++ [dfs (v : visited ++ concatMap preord previousTrees) c] -- ^nod v ^deasupra lui v ^nodurile din copiii anteriori ai lui v {- formă generală foldl: foldl \acc elem -> acc2 acc0 lista-de-elem -> acc-total -}