module Main where import Data.Char (isAlphaNum, isLetter, isNumber) import Data.Default (def) import Data.List (nub) import qualified Data.Text as T import Data.Text.Read (decimal) import Main.Utf8 (withUtf8) import qualified Relude.Extra.Map as Map import Text.Pandoc.Class (runIOorExplode) import Text.Pandoc.Definition (Block (..), Inline (..)) import Text.Pandoc.Readers (readOrg) import Text.Pandoc.Shared (stringify) import Text.Pandoc.Walk (walkM) import Numeric (showIntAtBase, readInt) import Zettel data HeaderState = HeaderState { headerStateMap :: Map Text ((ZettelId, Text), [Text]), headerStateCurrent :: Text } isLink :: Inline -> Bool isLink Link {} = True isLink _ = False parseIds :: Text -> Text parseIds t | T.null t = "" | T.head t == '#' && T.all isAlphaNum (T.tail t) = T.tail t | otherwise = "" addLinks :: [Inline] -> Block -> State HeaderState Block addLinks il b = do let f = filter isLink il s <- get let m' = Map.insertWith (\(_, y) (z, x) -> (z, x <> y)) (headerStateCurrent s) ((mempty, mempty), filter (not . T.null) (parseIds . stringify <$> f)) (headerStateMap s) put (HeaderState m' (headerStateCurrent s)) return b getHeaders :: Block -> State HeaderState Block getHeaders h@(Header _ (a, _, _) t) = do s <- get let m' = Map.insert a ((ZettelId a, stringify t), []) (headerStateMap s) put (HeaderState m' a) return h getHeaders p@(Plain i) = addLinks i p getHeaders p@(Para i) = addLinks i p getHeaders p@(LineBlock i) = addLinks (concat i) p getHeaders p = addLinks [] p splitId :: ZettelId -> [Text] splitId (ZettelId zid) | T.null zid = [] | isNumber (T.head zid) = T.takeWhile isNumber zid : (splitId . ZettelId $ T.dropWhile isNumber zid) | isLetter (T.head zid) = T.takeWhile isLetter zid : (splitId . ZettelId $ T.dropWhile isLetter zid) | otherwise = [] combineId :: [Text] -> ZettelId combineId = ZettelId . fold intToDigit26 :: Int -> Char intToDigit26 i | i <= 25 && i >= 0 = toEnum $ fromEnum 'a' + i | otherwise = error "Integer out of range." digitToInt26 :: Char -> Int digitToInt26 c = fromEnum c - fromEnum 'a' fromBase :: Int -> String -> Maybe Int fromBase base = fmap fst . viaNonEmpty head . readInt base (( Int -> String toBase base num = showIntAtBase base intToDigit26 num "" opOnBase26 :: (Int -> Int) -> Text -> Maybe Text opOnBase26 f t = fromString . toBase 26 . f <$> fromBase 26 (toString t) opOnIdPart :: (Int -> Int) -> Text -> Maybe Text opOnIdPart f t | T.null t = Nothing | isNumber $ T.head t = case decimal t of Right (a, _) -> Just . show $ f a _ -> Nothing | isLetter $ T.head t = opOnBase26 f t | otherwise = Nothing defPredId :: ZettelId -> Maybe ZettelId defPredId z = case nonEmpty (splitId z) of Just ne -> if last ne == "a" || last ne == "1" then Just (combineId (init ne)) else combineId . (init ne <>) . (: []) <$> opOnIdPart (subtract 1) (last ne) Nothing -> Nothing quoted :: Text -> Text quoted t = "\"" <> t <> "\"" toDot :: [Text] -> (Text, [Text]) -> Text toDot _ (t, l) = foldMap (\l' -> quoted l' <> " -> " <> quoted t <> ";\n") l toDotNodes :: ZettelId -> Text toDotNodes (ZettelId t) | T.null t = "" | isNumber $ T.head t = quoted t <> " [color=" <> T.singleton (T.head t) <> "];\n" | otherwise = "" addSelfLinks :: Map Text ((ZettelId, Text), [Text]) -> ZettelId -> Map Text ((ZettelId, Text), [Text]) addSelfLinks m z = Map.insertWith (\((_, _), l') ((z', t), l) -> ((z', t), l ++ l')) (unZettelId z) ((mempty, mempty), [unZettelId z]) m addSelfLinks2 :: ((ZettelId, b), [Text]) -> ((ZettelId, b), [Text]) addSelfLinks2 ((t, b), l) = ((t, b), maybeToList (unZettelId <$> defPredId t) <> l) main :: IO () main = withUtf8 $ do let fl = ["/home/ymherklotz/Dropbox/zk/verification.org", "/home/ymherklotz/Dropbox/zk/mathematics.org", "/home/ymherklotz/Dropbox/zk/hls.org", "/home/ymherklotz/Dropbox/zk/computing.org", "/home/ymherklotz/Dropbox/zk/hardware.org"] fs <- mapM readFileText fl x <- mapM (runIOorExplode . readOrg def) fs let (_, s) = runState (forM x (walkM getHeaders)) (HeaderState mempty "toplevel") let allZettel = second nub . addSelfLinks2 <$> headerStateMap s writeFileText "out.dot" $ "digraph G {\nnode [colorscheme=pastel28,style=filled];\n" <> foldMap (toDotNodes . fst . fst) allZettel <> foldMap (toDot (foldMap snd allZettel) . (\((ZettelId a, _), b) -> (a, b))) allZettel <> "}\n" -- forM_ allZettel (\(_, ((a, _), _)) -> do -- t <- runIOorExplode $ writeMarkdown def p -- writeFileText ("neuron/" <> toString a <> ".md") t -- )