{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.FiberBundle.Section
(
BundleSection
, value
, insert
, insertLeft
, insertRight
, fromList
, fromListLeft
, fromListRight
, map
, mapMonotonic
, toList
) where
import Data.FiberBundle
import Data.Foldable (foldl')
import Data.Group (Group (..))
import Data.Map.Strict (Map)
import Data.Maybe (fromMaybe)
import Prelude hiding (map)
import qualified Data.Map.Strict as Map
import qualified Data.Map.Merge.Strict as Map.Merge
newtype BundleSection a = BundleSection (Map (Base a) a)
instance (Show a, Show (Base a)) => Show (BundleSection a) where
show (BundleSection m) = show m
instance (Eq a, Eq (Base a)) => Eq (BundleSection a) where
(BundleSection m1) == (BundleSection m2) = m1 == m2
(BundleSection m1) /= (BundleSection m2) = m1 /= m2
instance (MonoidBundle a, Ord (Base a), Eq a) => Semigroup (BundleSection a) where
(<>) = sectionCombine
instance (MonoidBundle a, Ord (Base a), Eq a) => Monoid (BundleSection a) where
mempty = sectionUnit
instance (GroupBundle a, Ord (Base a), Eq a) => Group (BundleSection a) where
invert = sectionInvert
value :: (MonoidBundle a, Ord (Base a)) => BundleSection a -> Base a -> a
value (BundleSection m) b = fromMaybe (unit b) (Map.lookup b m)
insert ::
(AbelianBundle a, MonoidBundle a, Ord (Base a), Eq a) =>
a -> BundleSection a -> BundleSection a
insert = insertLeft
insertLeft ::
(MonoidBundle a, Ord (Base a), Eq a) =>
a -> BundleSection a -> BundleSection a
insertLeft a (BundleSection m) =
let
b = base a
in
if a == unit b
then BundleSection m
else BundleSection (Map.alter f (base a) m)
where
f Nothing = Just a
f (Just a') = combineNotNull a a'
insertRight ::
(MonoidBundle a, Ord (Base a), Eq a) =>
a -> BundleSection a -> BundleSection a
insertRight a (BundleSection m) =
let
b = base a
in
if a == unit b
then BundleSection m
else BundleSection (Map.alter f (base a) m)
where
f Nothing = Just a
f (Just a') = combineNotNull a' a
combineNotNull :: (MonoidBundle a, Eq a) => a -> a -> Maybe a
combineNotNull x y =
case combine x y of
Nothing -> Nothing
Just z ->
if z == unitOf x
then Nothing
else Just z
fromList ::
(AbelianBundle a, MonoidBundle a, Ord (Base a), Eq a) =>
[a] -> BundleSection a
fromList = fromListLeft
fromListLeft ::
(MonoidBundle a, Ord (Base a), Eq a) =>
[a] -> BundleSection a
fromListLeft = foldl' (flip insertLeft) sectionUnit
fromListRight ::
(MonoidBundle a, Ord (Base a), Eq a) =>
[a] -> BundleSection a
fromListRight = foldl' (flip insertRight) sectionUnit
toList :: BundleSection a -> [a]
toList (BundleSection m) = Map.elems m
map ::
(AbelianBundle b, MonoidBundle b, Ord (Base b), Eq b) =>
BundleMorphism a b -> BundleSection a -> BundleSection b
map (BundleMorphism f g) (BundleSection m) =
BundleSection $
Map.filter (not . isUnit) $
Map.mapKeysWith unsafeCombine g $
Map.map f m
mapMonotonic ::
(MonoidBundle b, Ord (Base b), Eq b) =>
BundleMorphism a b -> BundleSection a -> BundleSection b
mapMonotonic (BundleMorphism f g) (BundleSection m) =
BundleSection $
Map.mapKeysMonotonic g $
Map.mapMaybe f' m
where
f' x =
let
y = f x
in
if isUnit y then Nothing else Just y
sectionUnit :: MonoidBundle a => BundleSection a
sectionUnit = BundleSection Map.empty
sectionCombine ::
(MonoidBundle a, Ord (Base a), Eq a) =>
BundleSection a -> BundleSection a -> BundleSection a
sectionCombine (BundleSection m1) (BundleSection m2) = BundleSection m
where
m =
Map.Merge.merge
Map.Merge.preserveMissing
Map.Merge.preserveMissing
(Map.Merge.zipWithMaybeMatched (const combineNotNull))
m1
m2
sectionInvert ::
(GroupBundle a, Ord (Base a)) =>
BundleSection a -> BundleSection a
sectionInvert (BundleSection m) = BundleSection (fmap inverse m)