2015-12-01 22:18:13 +03:00
|
|
|
module Split where
|
2015-12-01 19:33:16 +03:00
|
|
|
|
|
|
|
import Diff
|
2015-12-01 22:18:13 +03:00
|
|
|
import Patch
|
|
|
|
import Syntax
|
|
|
|
import Term
|
|
|
|
import Unified
|
2015-12-01 22:35:23 +03:00
|
|
|
import Control.Comonad.Cofree
|
2015-12-02 00:34:26 +03:00
|
|
|
import Control.Monad.Free
|
2015-12-01 23:31:02 +03:00
|
|
|
import qualified Data.Map as Map
|
2015-12-01 23:39:45 +03:00
|
|
|
import qualified Data.Set as Set
|
2015-12-01 19:33:16 +03:00
|
|
|
import Rainbow
|
|
|
|
|
2015-12-01 22:35:23 +03:00
|
|
|
type ClassName = String
|
|
|
|
type Element a = Cofree (Syntax a) (Maybe ClassName, String)
|
2015-12-01 22:18:13 +03:00
|
|
|
|
2015-12-01 23:31:02 +03:00
|
|
|
data HTML =
|
|
|
|
Text String
|
2015-12-01 23:39:21 +03:00
|
|
|
| Span (Maybe ClassName) String
|
|
|
|
| Ul (Maybe ClassName) [HTML]
|
2015-12-02 00:18:19 +03:00
|
|
|
| Dl (Maybe ClassName) [HTML]
|
2015-12-02 00:18:08 +03:00
|
|
|
| Dt String
|
2015-12-01 23:31:02 +03:00
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2015-12-01 19:33:16 +03:00
|
|
|
split :: Diff a Info -> String -> String -> IO ByteString
|
2015-12-01 22:18:13 +03:00
|
|
|
split _ _ _ = return mempty
|
|
|
|
|
2015-12-02 17:51:38 +03:00
|
|
|
splitDiff :: Diff a Info -> String -> String -> Patch (HTML, Range)
|
2015-12-02 00:36:43 +03:00
|
|
|
splitDiff diff before after = iter toElements $ splitPatch before after <$> diff
|
2015-12-02 00:34:26 +03:00
|
|
|
where
|
2015-12-02 17:51:38 +03:00
|
|
|
toElements (Annotated (left, right) (Leaf _)) = Replace (leafToElement before left) (leafToElement after right)
|
2015-12-01 22:18:13 +03:00
|
|
|
|
2015-12-02 00:34:26 +03:00
|
|
|
leafToElement source (Info range _ categories) = (Span (classify categories) $ substring range source, range)
|
|
|
|
|
2015-12-02 17:51:38 +03:00
|
|
|
splitPatch :: String -> String -> Patch (Term a Info) -> Patch (HTML, Range)
|
|
|
|
splitPatch before after (Replace a b) = Replace (splitTerm before a) (splitTerm after b)
|
|
|
|
splitPatch _ after (Insert b) = Insert $ splitTerm after b
|
|
|
|
splitPatch before _ (Delete a) = Delete $ splitTerm before a
|
2015-12-01 22:18:13 +03:00
|
|
|
|
2015-12-02 00:34:26 +03:00
|
|
|
splitTerm :: String -> Term a Info -> (HTML, Range)
|
2015-12-02 17:26:36 +03:00
|
|
|
splitTerm source = cata toElement where
|
2015-12-01 23:56:15 +03:00
|
|
|
toElement (Info range lineRange categories) (Leaf _) = (Span (classify categories) $ substring range source, range)
|
2015-12-02 00:07:45 +03:00
|
|
|
toElement (Info range lineRange categories) (Indexed i) = makeList i range categories
|
2015-12-02 00:07:53 +03:00
|
|
|
toElement (Info range lineRange categories) (Fixed i) = makeList i range categories
|
2015-12-02 00:18:49 +03:00
|
|
|
toElement (Info range lineRange categories) (Keyed k) = makeMap (Map.toList k) range categories
|
2015-12-02 00:07:45 +03:00
|
|
|
|
2015-12-01 23:57:44 +03:00
|
|
|
accumulate (children, previous) (child, range) = (children ++ [ subtext previous $ start range, child ], end range)
|
2015-12-02 00:18:36 +03:00
|
|
|
accumulateFromMap (children, previous) (key, (child, range)) = (children ++ [ subtext previous $ start range, Dt key, child ], end range)
|
2015-12-02 00:07:45 +03:00
|
|
|
|
|
|
|
makeList i range categories = (Ul (classify categories) items, range)
|
|
|
|
where
|
|
|
|
(children, previous) = foldl accumulate ([], start range) i
|
|
|
|
items = children ++ [ subtext previous $ end range ]
|
|
|
|
|
2015-12-02 00:18:43 +03:00
|
|
|
makeMap k range categories = (Dl (classify categories) items, range)
|
|
|
|
where
|
|
|
|
(children, previous) = foldl accumulateFromMap ([], start range) k
|
|
|
|
items = children ++ [ subtext previous $ end range ]
|
|
|
|
|
2015-12-01 23:57:37 +03:00
|
|
|
subtext :: Int -> Int -> HTML
|
|
|
|
subtext start end = Text $ substring (Range start end) source
|
2015-12-01 23:39:45 +03:00
|
|
|
|
2015-12-02 18:09:29 +03:00
|
|
|
splitHTMLIntoLines :: HTML -> [HTML]
|
|
|
|
splitHTMLIntoLines (Text string) = Text <$> lines string
|
2015-12-02 18:12:11 +03:00
|
|
|
splitHTMLIntoLines (Span className string) = Span className <$> lines string
|
2015-12-02 18:16:41 +03:00
|
|
|
splitHTMLIntoLines (Ul className children) = Ul className . splitHTMLIntoLines <$> children
|
2015-12-02 18:14:53 +03:00
|
|
|
splitHTMLIntoLines (Dt string) = [ Dt string ]
|
2015-12-02 18:09:29 +03:00
|
|
|
|
2015-12-01 23:39:45 +03:00
|
|
|
classify :: Set.Set Category -> Maybe ClassName
|
2015-12-02 17:26:36 +03:00
|
|
|
classify = foldr (const . Just) Nothing
|