-- | Class interface to different free module implementations. -- -- Free modules are like maps from a base type to a numeric type, -- with the additional invariant that the values are never zero. {-# LANGUAGE TypeFamilies, FlexibleContexts, CPP #-} module Math.FreeModule.Class where -------------------------------------------------------------------------------- -- | generic baseMap implementation, converts to list and back. baseMap :: (FreeModule x, FreeModule y, Coeff x ~ Coeff y) => (Base x -> Base y) -> x -> y baseMap f = fromList . map h . toList where h (b,c) = (f b, c) -- | generic coeffMap implementation, converts to list and back. coeffMap :: (FreeModule x, FreeModule y, Base x ~ Base y) => (Coeff x -> Coeff y) -> x -> y coeffMap g = fromList . map h . toList where h (b,c) = (b, g c) -------------------------------------------------------------------------------- class (Ord (Base a), Eq (Coeff a), Num (Coeff a)) => FreeModule a where type Base a :: * type Coeff a :: * isZero :: a -> Bool zero :: a fromBase :: Base a -> a fromTerm :: Base a -> Coeff a -> a (^+^) :: a -> a -> a (^-^) :: a -> a -> a neg :: a -> a scalarMul :: Coeff a -> a -> a -- | We should call the function even when the given base is present -- only in one of the arguments! So that @unionWith (-)@ works correctly. unionWith :: (Coeff a -> Coeff a -> Coeff a) -> a -> a -> a coeff :: Base a -> a -> Coeff a size :: a -> Int minTerm :: a -> (Base a, Coeff a) maxTerm :: a -> (Base a, Coeff a) -- | split into two approximately equal parts @x@ and @y@, such that -- @maxTerm x < minTerm y@ split :: a -> (a, a) -- | we assume that @maxTerm x < minTerm y@ unsafeJoin :: a -> a -> a toList :: a -> [(Base a, Coeff a)] fromList :: [(Base a, Coeff a)] -> a fromAscendingList :: [(Base a, Coeff a)] -> a isZero x = (size x == 0) neg x = scalarMul (-1) x x ^+^ y = unionWith (+) x y x ^-^ y = unionWith (-) x y -- x ^+^ (neg y) fromAscendingList = fromList fromBase b = fromTerm b 1 fromTerm b c = scalarMul c (fromBase b) -------------------------------------------------------------------------------- (*^) :: FreeModule a => Coeff a -> a -> a (*^) = scalarMul (^*) :: FreeModule a => a -> Coeff a -> a (^*) = flip scalarMul infixl 6 ^+^ infixl 6 ^-^ infixl 7 *^ infixl 7 ^* -------------------------------------------------------------------------------- lookupTerm :: FreeModule a => Base a -> a -> Maybe (Base a, Coeff a) lookupTerm b x = case coeff b x of 0 -> Nothing c -> Just (b,c) minTermMaybe :: FreeModule a => a -> Maybe (Base a, Coeff a) minTermMaybe x = if isZero x then Nothing else Just (minTerm x) maxTermMaybe :: FreeModule a => a -> Maybe (Base a, Coeff a) maxTermMaybe x = if isZero x then Nothing else Just (maxTerm x) --------------------------------------------------------------------------------