summaryrefslogtreecommitdiffstats
path: root/src/Zettel/Links.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Zettel/Links.hs')
-rw-r--r--src/Zettel/Links.hs81
1 files changed, 10 insertions, 71 deletions
diff --git a/src/Zettel/Links.hs b/src/Zettel/Links.hs
index 05659cf..f5638ad 100644
--- a/src/Zettel/Links.hs
+++ b/src/Zettel/Links.hs
@@ -2,87 +2,26 @@
module Zettel.Links where
-import Data.Char (isAlphaNum, isLetter, isNumber)
import Data.List (nub)
import qualified Data.Map.Strict as Map
import qualified Data.Text as T
-import Data.Text.Read (decimal)
-import Numeric (readInt, showIntAtBase)
import Text.Pandoc.Definition (Inline (..), Pandoc (..))
import Text.Pandoc.Shared (stringify)
import Text.Pandoc.Walk (query, walk)
import Zettel.Common
import Zettel.Types
-parseIds :: Text -> Text
-parseIds t
- | T.null t = ""
- | T.head t == '#' && T.all isAlphaNum (T.tail t) = T.tail t
- | otherwise = ""
-
-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 ((< base) . digitToInt26) digitToInt26
-
-toBase :: Int -> 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
-
-defNextId :: ZettelId -> Maybe ZettelId
-defNextId z =
- case nonEmpty (splitId z) of
- Just ne ->
- combineId . (init ne <>) . (: []) <$> opOnIdPart (+ 1) (last ne)
- Nothing -> Nothing
-
-defBranchId :: ZettelId -> Maybe ZettelId
-defBranchId (ZettelId t)
- | T.null t = Nothing
- | isNumber $ T.last t = Just (ZettelId (t <> "a"))
- | isLetter $ T.last t = Just (ZettelId (t <> "1"))
- | otherwise = Nothing
-
gatherForwardIds :: Inline -> [ZettelId]
-gatherForwardIds (Link _ i _) = [ZettelId . parseIds $ stringify i]
+gatherForwardIds (Link _ i _)
+ | T.null ident = []
+ | otherwise = [ZettelId ident]
+ where
+ ident = parseIds $ stringify i
+gatherForwardIds (RawInline t v)
+ | t == "markdown" && not (T.null parsed) = [ZettelId parsed]
+ | otherwise = []
+ where
+ parsed = T.takeWhile (/= '"') . T.drop 1 $ T.dropWhile (/= '"') v
gatherForwardIds _ = []
addIdPresent :: ZettelGraph -> Maybe ZettelId -> [ZettelId]