2016-05-17 19:22:21 +03:00
|
|
|
|
{-# LANGUAGE RankNTypes #-}
|
2016-03-11 20:29:17 +03:00
|
|
|
|
module Alignment
|
2016-03-14 21:13:06 +03:00
|
|
|
|
( hasChanges
|
2016-03-11 20:29:17 +03:00
|
|
|
|
, numberedRows
|
2016-03-22 15:20:56 +03:00
|
|
|
|
, AlignedDiff
|
|
|
|
|
, alignDiff
|
2016-05-19 20:40:10 +03:00
|
|
|
|
, alignBranch
|
2016-04-25 21:42:38 +03:00
|
|
|
|
, applyThese
|
|
|
|
|
, modifyJoin
|
2016-05-25 18:13:34 +03:00
|
|
|
|
, unionThese
|
2016-03-11 20:29:17 +03:00
|
|
|
|
) where
|
2016-02-28 22:01:56 +03:00
|
|
|
|
|
2016-04-15 19:44:04 +03:00
|
|
|
|
import Control.Applicative
|
2016-05-27 16:35:26 +03:00
|
|
|
|
import Control.Arrow ((***))
|
2016-03-05 04:18:49 +03:00
|
|
|
|
import Control.Monad
|
2016-03-10 23:06:03 +03:00
|
|
|
|
import Data.Align
|
2016-04-14 23:34:49 +03:00
|
|
|
|
import Data.Biapplicative
|
2016-03-18 21:30:22 +03:00
|
|
|
|
import Data.Bifunctor.Join
|
2016-03-03 07:11:24 +03:00
|
|
|
|
import Data.Copointed
|
2016-03-12 01:59:58 +03:00
|
|
|
|
import Data.Foldable
|
2016-04-25 18:25:32 +03:00
|
|
|
|
import Data.Function
|
2016-04-04 23:25:16 +03:00
|
|
|
|
import Data.Functor.Both as Both
|
2016-05-27 16:35:26 +03:00
|
|
|
|
import Data.Functor.Foldable hiding (Foldable, fold)
|
2016-02-28 22:01:56 +03:00
|
|
|
|
import Data.Functor.Identity
|
2016-05-26 17:11:22 +03:00
|
|
|
|
import Data.List (partition)
|
2016-03-03 15:53:23 +03:00
|
|
|
|
import Data.Maybe
|
2016-04-15 18:57:26 +03:00
|
|
|
|
import Data.Monoid
|
2016-04-22 19:18:40 +03:00
|
|
|
|
import qualified Data.OrderedMap as Map
|
2016-04-15 05:00:00 +03:00
|
|
|
|
import Data.These
|
2016-02-28 22:01:56 +03:00
|
|
|
|
import Diff
|
2016-03-31 00:26:52 +03:00
|
|
|
|
import Info
|
2016-02-28 22:01:56 +03:00
|
|
|
|
import Patch
|
2016-05-26 22:25:45 +03:00
|
|
|
|
import Prologue hiding (fst, snd)
|
2016-02-28 22:01:56 +03:00
|
|
|
|
import Range
|
2016-05-17 19:01:31 +03:00
|
|
|
|
import Source hiding (break, fromList, uncons, (++))
|
2016-02-28 22:01:56 +03:00
|
|
|
|
import SplitDiff
|
|
|
|
|
import Syntax
|
|
|
|
|
import Term
|
|
|
|
|
|
2016-03-02 00:29:42 +03:00
|
|
|
|
-- | Assign line numbers to the lines on each side of a list of rows.
|
2016-04-15 04:16:02 +03:00
|
|
|
|
numberedRows :: [Join These a] -> [Join These (Int, a)]
|
2016-04-27 00:36:00 +03:00
|
|
|
|
numberedRows = countUp (both 1 1)
|
2016-05-26 22:25:45 +03:00
|
|
|
|
where countUp from (row : rows) = fromJust ((,) <$> modifyJoin (uncurry These) from `applyThese` row) : countUp (modifyJoin (fromThese identity identity) (succ <$ row) <*> from) rows
|
2016-03-08 01:13:51 +03:00
|
|
|
|
countUp _ [] = []
|
2016-03-02 00:29:42 +03:00
|
|
|
|
|
2016-03-02 16:05:18 +03:00
|
|
|
|
-- | Determine whether a line contains any patches.
|
2016-04-15 04:16:02 +03:00
|
|
|
|
hasChanges :: SplitDiff leaf Info -> Bool
|
|
|
|
|
hasChanges = or . (True <$)
|
2016-03-09 09:36:40 +03:00
|
|
|
|
|
2016-03-22 15:20:56 +03:00
|
|
|
|
type AlignedDiff leaf = [Join These (SplitDiff leaf Info)]
|
2016-03-18 19:02:07 +03:00
|
|
|
|
|
2016-05-27 20:07:32 +03:00
|
|
|
|
alignDiff :: Show leaf => Both (Source Char) -> Diff leaf Info -> AlignedDiff leaf
|
2016-05-27 16:35:26 +03:00
|
|
|
|
alignDiff sources diff = iter (alignSyntax (runBothWith ((Join .) . These)) (free . Free) getRange sources) (alignPatch sources <$> diff)
|
2016-04-15 00:03:53 +03:00
|
|
|
|
|
2016-05-27 20:07:32 +03:00
|
|
|
|
alignPatch :: Show leaf => Both (Source Char) -> Patch (Term leaf Info) -> AlignedDiff leaf
|
2016-04-15 03:27:24 +03:00
|
|
|
|
alignPatch sources patch = case patch of
|
2016-05-27 16:35:26 +03:00
|
|
|
|
Delete term -> fmap (pure . SplitDelete) <$> hylo (alignSyntax this cofree getRange (Identity (fst sources))) runCofree (Identity <$> term)
|
|
|
|
|
Insert term -> fmap (pure . SplitInsert) <$> hylo (alignSyntax that cofree getRange (Identity (snd sources))) runCofree (Identity <$> term)
|
|
|
|
|
Replace term1 term2 -> fmap (pure . SplitReplace) <$> alignWith (fmap (these identity identity const . runJoin) . Join)
|
|
|
|
|
(hylo (alignSyntax this cofree getRange (Identity (fst sources))) runCofree (Identity <$> term1))
|
|
|
|
|
(hylo (alignSyntax that cofree getRange (Identity (snd sources))) runCofree (Identity <$> term2))
|
|
|
|
|
where getRange = characterRange . extract
|
2016-04-15 03:27:24 +03:00
|
|
|
|
this = Join . This . runIdentity
|
|
|
|
|
that = Join . That . runIdentity
|
|
|
|
|
|
2016-05-13 23:39:48 +03:00
|
|
|
|
-- | The Applicative instance f is either Identity or Both. Identity is for Terms in Patches, Both is for Diffs in unchanged portions of the diff.
|
2016-05-27 20:07:32 +03:00
|
|
|
|
alignSyntax :: (Applicative f, Show term) => (forall a. f a -> Join These a) -> (CofreeF (Syntax leaf) Info term -> term) -> (term -> Range) -> f (Source Char) -> CofreeF (Syntax leaf) (f Info) [Join These term] -> [Join These term]
|
2016-05-27 16:35:26 +03:00
|
|
|
|
alignSyntax toJoinThese toNode getRange sources (infos :< syntax) = case syntax of
|
2016-04-05 00:18:29 +03:00
|
|
|
|
Leaf s -> catMaybes $ wrapInBranch (const (Leaf s)) . fmap (flip (,) []) <$> sequenceL lineRanges
|
2016-05-19 20:26:36 +03:00
|
|
|
|
Indexed children -> catMaybes $ wrapInBranch (Indexed . fmap runIdentity) <$> alignBranch getRange (Identity <$> children) (modifyJoin (fromThese [] []) lineRanges)
|
|
|
|
|
Fixed children -> catMaybes $ wrapInBranch (Fixed . fmap runIdentity) <$> alignBranch getRange (Identity <$> children) (modifyJoin (fromThese [] []) lineRanges)
|
2016-05-19 20:38:24 +03:00
|
|
|
|
Keyed children -> catMaybes $ wrapInBranch (Keyed . Map.fromList) <$> alignBranch getRange (Map.toList children) (modifyJoin (fromThese [] []) lineRanges)
|
2016-04-05 00:18:29 +03:00
|
|
|
|
where lineRanges = toJoinThese $ actualLineRanges <$> (characterRange <$> infos) <*> sources
|
2016-05-27 16:35:26 +03:00
|
|
|
|
wrapInBranch constructor = applyThese $ toJoinThese ((\ info (range, children) -> toNode (info { characterRange = range } :< constructor children)) <$> infos)
|
2016-03-22 15:20:56 +03:00
|
|
|
|
|
2016-05-13 23:40:10 +03:00
|
|
|
|
{-
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
We align asymmetrically since the first child is asymmetrical, and then continue aligning symmetrically afterwards:
|
|
|
|
|
[ | [
|
|
|
|
|
a |
|
|
|
|
|
, b | b
|
|
|
|
|
] | ]
|
|
|
|
|
|
|
|
|
|
The first child is asymmetrical but there is also a symmetrical child on the same line, so we align symmetrically, producing:
|
|
|
|
|
[ a, b ] | [ b ]
|
|
|
|
|
|
|
|
|
|
and not:
|
|
|
|
|
[ a, b ] |
|
|
|
|
|
| [ b ]
|
|
|
|
|
|
|
|
|
|
We align the child symmetrically, and thus have to take the first line range on the right asymmetrically so as not to break the child’s alignment.
|
|
|
|
|
| [
|
|
|
|
|
[ b ] | b
|
|
|
|
|
| ]
|
|
|
|
|
(Eventually, we’ll align the left hand side of this up a line, but that constraint is undecidable for now.)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
If a is replaced with b in a Replace patch, we would like to align them side by side (that’s what makes it a replacement—they correlate), but a catamorphism which loses the Replace relationship (by splitting it into two SplitReplaces) can’t know that they’re related:
|
|
|
|
|
[ a ] | [ b ]
|
|
|
|
|
|
|
|
|
|
If a is deleted and b is coincidentally inserted, we want to separate them, because they’re semantically unrelated:
|
|
|
|
|
[ a ] |
|
|
|
|
|
| [ b ]
|
|
|
|
|
|
|
|
|
|
The presence of a symmetrical child forces it to be symmetrical again:
|
|
|
|
|
[ a, c ] | [ c, b ]
|
|
|
|
|
|
|
|
|
|
We might split up children so `This` and `That` aren’t 1:1 with `Delete` and `Insert`. This is because earlier symmetrical children take precedence over later ones:
|
|
|
|
|
[ a, b ] | [ a
|
|
|
|
|
| , b
|
|
|
|
|
| ]
|
|
|
|
|
|
|
|
|
|
Lines without children on them are aligned irrespective of their textual content:
|
|
|
|
|
[\n | [\n
|
|
|
|
|
a\n | a, b\n
|
|
|
|
|
,\n | \n
|
|
|
|
|
b\n | \n
|
|
|
|
|
] | ]
|
|
|
|
|
|
2016-05-17 19:11:46 +03:00
|
|
|
|
We should avoid taking asymmetrical children greedily so as not to misalign asymmetrical children before symmetrical children on the same line:
|
|
|
|
|
| [ a
|
|
|
|
|
[ b, c ] | , c
|
|
|
|
|
| ]
|
|
|
|
|
|
2016-05-13 23:40:10 +03:00
|
|
|
|
-}
|
|
|
|
|
|
2016-05-13 23:40:46 +03:00
|
|
|
|
-- | Given a function to get the range, a list of already-aligned children, and the lists of ranges spanned by a branch, return the aligned lines.
|
2016-05-27 20:07:32 +03:00
|
|
|
|
alignBranch :: (Copointed c, Functor c, Show term) => (term -> Range) -> [c [Join These term]] -> Both [Range] -> [Join These (Range, [c term])]
|
2016-05-25 17:28:56 +03:00
|
|
|
|
-- The first child is empty, and so can safely be dropped.
|
|
|
|
|
alignBranch getRange (first:children) ranges | null (copoint first) = alignBranch getRange children ranges
|
2016-05-13 23:40:46 +03:00
|
|
|
|
-- There are no more ranges, so we’re done.
|
2016-05-26 21:58:20 +03:00
|
|
|
|
alignBranch _ [] (Join ([], [])) = []
|
|
|
|
|
alignBranch _ children (Join ([], [])) = trace ("exhausted ranges with " ++ show (length children) ++ " children remaining") []
|
2016-05-13 23:40:46 +03:00
|
|
|
|
-- There are no more children, so we can just zip the remaining ranges together.
|
|
|
|
|
alignBranch _ [] ranges = runBothWith (alignWith Join) (fmap (flip (,) []) <$> ranges)
|
|
|
|
|
-- There are both children and ranges, so we need to proceed line by line
|
2016-05-13 23:46:53 +03:00
|
|
|
|
alignBranch getRange children ranges = case intersectingChildren of
|
2016-05-18 21:55:31 +03:00
|
|
|
|
-- No child intersects the current ranges on either side, so advance.
|
2016-05-13 23:46:53 +03:00
|
|
|
|
[] -> (flip (,) [] <$> headRanges) : alignBranch getRange children (drop 1 <$> ranges)
|
2016-05-18 21:55:31 +03:00
|
|
|
|
-- At least one child intersects on at least one side.
|
2016-05-27 17:08:41 +03:00
|
|
|
|
_ -> case fromThese True True . runJoin . intersectsFirstLine getRange headRanges . copoint <$> listToMaybe remainingIntersectingChildren of
|
2016-05-18 22:51:49 +03:00
|
|
|
|
-- At least one child intersects on both sides, so align symmetrically.
|
2016-05-26 23:33:12 +03:00
|
|
|
|
Just (True, True) -> let (line, remaining) = lineAndRemaining intersectingChildren headRanges in
|
|
|
|
|
line : alignBranch getRange (remaining ++ nonIntersectingChildren) (drop 1 <$> ranges)
|
2016-05-18 22:51:49 +03:00
|
|
|
|
-- A symmetrical child intersects on the right, so align asymmetrically on the left.
|
|
|
|
|
Just (False, True) -> let (leftLine, remainingAtLeft) = maybe (id, []) (first (:)) $ lineAndRemaining asymmetricalChildren <$> leftRange in
|
2016-05-19 00:22:02 +03:00
|
|
|
|
leftLine $ alignBranch getRange (remainingAtLeft ++ remainingIntersectingChildren ++ nonIntersectingChildren) (modifyJoin (first (drop 1)) ranges)
|
2016-05-18 22:51:49 +03:00
|
|
|
|
-- A symmetrical child intersects on the left, so align asymmetrically on the right.
|
|
|
|
|
Just (True, False) -> let (rightLine, remainingAtRight) = maybe (id, []) (first (:)) $ lineAndRemaining asymmetricalChildren <$> rightRange in
|
2016-05-19 00:22:02 +03:00
|
|
|
|
rightLine $ alignBranch getRange (remainingAtRight ++ remainingIntersectingChildren ++ nonIntersectingChildren) (modifyJoin (second (drop 1)) ranges)
|
2016-05-18 22:51:49 +03:00
|
|
|
|
-- No symmetrical child intersects, so align asymmetrically, picking the left side first to match the deletion/insertion order convention in diffs.
|
2016-05-27 17:59:40 +03:00
|
|
|
|
_ -> if any (maybe False (isThis . runJoin) . head . copoint) asymmetricalChildren
|
|
|
|
|
then let (leftLine, remainingAtLeft) = maybe (identity, []) (first (:)) $ lineAndRemaining asymmetricalChildren <$> leftRange in
|
|
|
|
|
leftLine $ alignBranch getRange (remainingAtLeft ++ nonIntersectingChildren) (modifyJoin (first (drop 1)) ranges)
|
|
|
|
|
else let (rightLine, remainingAtRight) = maybe (identity, []) (first (:)) $ lineAndRemaining asymmetricalChildren <$> rightRange in
|
|
|
|
|
rightLine $ alignBranch getRange (remainingAtRight ++ nonIntersectingChildren) (modifyJoin (second (drop 1)) ranges)
|
2016-05-27 17:08:41 +03:00
|
|
|
|
where (intersectingChildren, nonIntersectingChildren) = partition (or . intersectsFirstLine getRange headRanges . copoint) children
|
2016-05-27 17:10:58 +03:00
|
|
|
|
(remainingIntersectingChildren, asymmetricalChildren) = partition (maybe False (isThese . runJoin) . head . copoint) intersectingChildren
|
2016-05-27 18:00:43 +03:00
|
|
|
|
Just headRanges = sequenceL (listToMaybe <$> Join (runBothWith These ranges))
|
2016-05-18 22:51:49 +03:00
|
|
|
|
(leftRange, rightRange) = splitThese headRanges
|
2016-05-18 23:19:40 +03:00
|
|
|
|
lineAndRemaining children ranges = let (intersections, remaining) = alignChildren getRange children ranges in
|
2016-05-27 17:23:38 +03:00
|
|
|
|
((,) <$> ranges `applyToBoth` intersections, remaining)
|
2016-05-26 21:49:57 +03:00
|
|
|
|
|
2016-05-27 17:07:32 +03:00
|
|
|
|
intersectsFirstLine :: (term -> Range) -> Join These Range -> [Join These term] -> Join These Bool
|
|
|
|
|
intersectsFirstLine getRange ranges = maybe (False <$ ranges) (intersects getRange ranges) . listToMaybe
|
|
|
|
|
|
2016-05-17 19:22:21 +03:00
|
|
|
|
-- | Given a list of aligned children, produce lists of their intersecting first lines, and a list of the remaining lines/nonintersecting first lines.
|
2016-05-19 20:26:36 +03:00
|
|
|
|
alignChildren :: (Copointed c, Functor c) => (term -> Range) -> [c [Join These term]] -> Join These Range -> (Both [c term], [c [Join These term]])
|
2016-05-18 23:19:40 +03:00
|
|
|
|
alignChildren _ [] _ = (both [] [], [])
|
2016-05-19 20:26:36 +03:00
|
|
|
|
alignChildren getRange (first:rest) headRanges
|
|
|
|
|
| (firstLine:restOfLines) <- copoint first
|
|
|
|
|
, ~(l, r) <- splitThese firstLine
|
2016-05-27 17:07:45 +03:00
|
|
|
|
= case fromThese False False . runJoin $ intersectsFirstLine getRange headRanges (copoint first) of
|
2016-05-27 17:38:20 +03:00
|
|
|
|
-- It intersects on both sides, so we can just take the first line whole.
|
|
|
|
|
(True, True) -> ((++) <$> toTerms firstLine <*> firstRemaining, (restOfLines <$ first) : restRemaining)
|
|
|
|
|
-- It only intersects on the left, so split it up.
|
|
|
|
|
(True, False) -> ((++) <$> toTerms (fromJust l) <*> firstRemaining, (maybe identity (:) r restOfLines <$ first) : restRemaining)
|
|
|
|
|
-- It only intersects on the right, so split it up.
|
|
|
|
|
(False, True) -> ((++) <$> toTerms (fromJust r) <*> firstRemaining, (maybe identity (:) l restOfLines <$ first) : restRemaining)
|
|
|
|
|
-- It doesn’t intersect at all, so skip it and move along.
|
|
|
|
|
(False, False) -> (firstRemaining, first:restRemaining)
|
2016-05-19 23:12:51 +03:00
|
|
|
|
| otherwise = alignChildren getRange rest headRanges
|
2016-05-18 23:19:40 +03:00
|
|
|
|
where (firstRemaining, restRemaining) = alignChildren getRange rest headRanges
|
2016-05-19 20:26:36 +03:00
|
|
|
|
toTerms line = modifyJoin (fromThese [] []) (pure . (<$ first) <$> line)
|
2016-05-17 19:22:21 +03:00
|
|
|
|
|
2016-04-15 19:45:33 +03:00
|
|
|
|
unionThese :: (Alternative f, Foldable f, Monoid (f a)) => f (Join These a) -> Join These (f a)
|
|
|
|
|
unionThese as = fromMaybe (Join (These empty empty)) . getUnion . fold $ Union . Just . fmap pure <$> as
|
2016-04-14 16:59:46 +03:00
|
|
|
|
|
2016-04-15 16:35:41 +03:00
|
|
|
|
-- | Test ranges and terms for intersection on either or both sides.
|
2016-04-15 03:27:24 +03:00
|
|
|
|
intersects :: (term -> Range) -> Join These Range -> Join These term -> Join These Bool
|
2016-05-27 17:25:05 +03:00
|
|
|
|
intersects getRange ranges line = intersectsRange <$> ranges `applyToBoth` modifyJoin (fromThese (Range (-1) (-1)) (Range (-1) (-1))) (getRange <$> line)
|
2016-03-29 01:27:01 +03:00
|
|
|
|
|
2016-04-15 16:31:28 +03:00
|
|
|
|
-- | Split a These value up into independent These values representing the left and right sides, if any.
|
2016-04-15 16:33:30 +03:00
|
|
|
|
splitThese :: Join These a -> (Maybe (Join These a), Maybe (Join These a))
|
|
|
|
|
splitThese these = fromThese Nothing Nothing $ bimap (Just . Join . This) (Just . Join . That) (runJoin these)
|
2016-03-29 01:46:22 +03:00
|
|
|
|
|
|
|
|
|
infixl 4 `applyThese`
|
|
|
|
|
|
2016-04-15 16:29:23 +03:00
|
|
|
|
-- | Like `<*>`, but it returns its result in `Maybe` since the result is the intersection of the shapes of the inputs.
|
2016-03-29 01:46:22 +03:00
|
|
|
|
applyThese :: Join These (a -> b) -> Join These a -> Maybe (Join These b)
|
2016-04-15 16:29:23 +03:00
|
|
|
|
applyThese (Join fg) (Join ab) = fmap Join . uncurry maybeThese $ uncurry (***) (bimap (<*>) (<*>) (unpack fg)) (unpack ab)
|
|
|
|
|
where unpack = fromThese Nothing Nothing . bimap Just Just
|
2016-03-29 16:58:31 +03:00
|
|
|
|
|
2016-05-27 17:22:51 +03:00
|
|
|
|
infixl 4 `applyToBoth`
|
|
|
|
|
|
2016-05-27 17:22:24 +03:00
|
|
|
|
-- | Like `<*>`, but it takes a `Both` on the right to ensure that it can always return a value.
|
|
|
|
|
applyToBoth :: Join These (a -> b) -> Both a -> Join These b
|
|
|
|
|
applyToBoth (Join fg) (Join (a, b)) = Join $ these (This . ($ a)) (That . ($ b)) (\ f g -> These (f a) (g b)) fg
|
|
|
|
|
|
2016-04-15 16:30:20 +03:00
|
|
|
|
-- Map over the bifunctor inside a Join, producing another Join.
|
2016-03-24 21:18:53 +03:00
|
|
|
|
modifyJoin :: (p a a -> q b b) -> Join p a -> Join q b
|
2016-03-24 21:26:25 +03:00
|
|
|
|
modifyJoin f = Join . f . runJoin
|
2016-04-15 04:47:18 +03:00
|
|
|
|
|
|
|
|
|
-- | Given a pair of Maybes, produce a These containing Just their values, or Nothing if they haven’t any.
|
|
|
|
|
maybeThese :: Maybe a -> Maybe b -> Maybe (These a b)
|
|
|
|
|
maybeThese (Just a) (Just b) = Just (These a b)
|
|
|
|
|
maybeThese (Just a) _ = Just (This a)
|
|
|
|
|
maybeThese _ (Just b) = Just (That b)
|
|
|
|
|
maybeThese _ _ = Nothing
|
|
|
|
|
|
2016-04-15 19:15:47 +03:00
|
|
|
|
-- | A Monoid wrapping Join These, for which mappend is the smallest shape covering both arguments.
|
|
|
|
|
newtype Union a = Union { getUnion :: Maybe (Join These a) }
|
2016-04-22 17:39:15 +03:00
|
|
|
|
deriving (Eq, Functor, Show)
|
2016-04-15 16:23:41 +03:00
|
|
|
|
|
|
|
|
|
|
2016-04-15 16:26:16 +03:00
|
|
|
|
-- | Instances
|
|
|
|
|
|
2016-04-15 19:15:47 +03:00
|
|
|
|
instance Monoid a => Monoid (Union a) where
|
2016-04-15 04:47:18 +03:00
|
|
|
|
mempty = Union Nothing
|
2016-04-15 19:15:47 +03:00
|
|
|
|
Union (Just a) `mappend` Union (Just b) = Union $ Join <$> uncurry maybeThese (uncurry (***) (bimap mappend mappend (unpack a)) (unpack b))
|
|
|
|
|
where unpack = fromThese Nothing Nothing . runJoin . fmap Just
|
2016-04-15 04:47:18 +03:00
|
|
|
|
Union (Just a) `mappend` _ = Union $ Just a
|
|
|
|
|
Union _ `mappend` Union (Just b) = Union $ Just b
|
|
|
|
|
_ `mappend` _ = Union Nothing
|
2016-04-15 16:26:16 +03:00
|
|
|
|
|
|
|
|
|
instance Bicrosswalk t => Crosswalk (Join t) where
|
|
|
|
|
crosswalk f = fmap Join . bicrosswalk f f . runJoin
|