module Graphics.Vty.DisplayAttributes where
import Graphics.Vty.Attributes
import Data.Bits ((.&.))
fixDisplayAttr :: FixedAttr -> Attr -> FixedAttr
fixDisplayAttr fattr attr
    = FixedAttr (fixStyle (fixedStyle fattr)     (attrStyle attr))
                (fixColor (fixedForeColor fattr) (attrForeColor attr))
                (fixColor (fixedBackColor fattr) (attrBackColor attr))
    where
        fixStyle _s Default           = defaultStyleMask
        fixStyle s KeepCurrent        = s
        fixStyle _s (SetTo newStyle)  = newStyle
        fixColor _c Default           = Nothing
        fixColor c KeepCurrent        = c
        fixColor _c (SetTo c)         = Just c
data DisplayAttrDiff = DisplayAttrDiff
    { styleDiffs    :: [StyleStateChange]
    , foreColorDiff :: DisplayColorDiff
    , backColorDiff :: DisplayColorDiff
    }
    deriving (Show)
instance Monoid DisplayAttrDiff where
    mempty = DisplayAttrDiff [] NoColorChange NoColorChange
    mappend d0 d1 =
        let ds  = simplifyStyleDiffs (styleDiffs d0)    (styleDiffs d1)
            fcd = simplifyColorDiffs (foreColorDiff d0) (foreColorDiff d1)
            bcd = simplifyColorDiffs (backColorDiff d0) (backColorDiff d1)
        in DisplayAttrDiff ds fcd bcd
simplifyStyleDiffs :: [StyleStateChange] -> [StyleStateChange] -> [StyleStateChange]
simplifyStyleDiffs cs0 cs1 = cs0 `mappend` cs1
simplifyColorDiffs :: DisplayColorDiff -> DisplayColorDiff -> DisplayColorDiff
simplifyColorDiffs _cd             ColorToDefault = ColorToDefault
simplifyColorDiffs cd              NoColorChange  = cd
simplifyColorDiffs _cd             (SetColor !c)  = SetColor c
data DisplayColorDiff
    = ColorToDefault
    | NoColorChange
    | SetColor !Color
    deriving (Show, Eq)
data StyleStateChange
    = ApplyStandout
    | RemoveStandout
    | ApplyUnderline
    | RemoveUnderline
    | ApplyReverseVideo
    | RemoveReverseVideo
    | ApplyBlink
    | RemoveBlink
    | ApplyDim
    | RemoveDim
    | ApplyBold
    | RemoveBold
    deriving (Show, Eq)
displayAttrDiffs :: FixedAttr -> FixedAttr -> DisplayAttrDiff
displayAttrDiffs attr attr' = DisplayAttrDiff
    { styleDiffs    = diffStyles (fixedStyle attr)      (fixedStyle attr')
    , foreColorDiff = diffColor  (fixedForeColor attr) (fixedForeColor attr')
    , backColorDiff = diffColor  (fixedBackColor attr) (fixedBackColor attr')
    }
diffColor :: Maybe Color -> Maybe Color -> DisplayColorDiff
diffColor Nothing  (Just c') = SetColor c'
diffColor (Just c) (Just c')
    | c == c'   = NoColorChange
    | otherwise = SetColor c'
diffColor Nothing  Nothing = NoColorChange
diffColor (Just _) Nothing = ColorToDefault
diffStyles :: Style -> Style -> [StyleStateChange]
diffStyles prev cur
    = mconcat
    [ styleDiff standout      ApplyStandout     RemoveStandout
    , styleDiff underline     ApplyUnderline    RemoveUnderline
    , styleDiff reverseVideo  ApplyReverseVideo RemoveReverseVideo
    , styleDiff blink         ApplyBlink        RemoveBlink
    , styleDiff dim           ApplyDim          RemoveDim
    , styleDiff bold          ApplyBold         RemoveBold
    ]
    where
        styleDiff s sm rm
            = case (0 == prev .&. s, 0 == cur .&. s) of
                
                (True, True)   -> []
                
                (False, False) -> []
                
                (True, False)  -> [sm]
                
                (False, True)  -> [rm]