{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Group.Free
( FreeGroup
, fromDList
, toDList
, normalize
, FreeGroupL
, consL
, fromList
, toList
, normalizeL
) where
import Control.Monad (ap)
import Data.DList (DList)
import qualified Data.DList as DList
import Data.Bifunctor (bimap)
import Data.Group (Group (..))
#if __GLASGOW_HASKELL__ < 808
import Data.Semigroup (Semigroup (..))
#endif
import Data.Algebra.Free
( AlgebraType
, AlgebraType0
, FreeAlgebra (..)
)
newtype FreeGroup a = FreeGroup {
runFreeGroup :: DList (Either a a)
}
deriving (Eq, Ord, Show)
instance Functor FreeGroup where
fmap f (FreeGroup as) = FreeGroup $ bimap f f <$> as
instance Applicative FreeGroup where
pure = return
(<*>) = ap
instance Monad FreeGroup where
return a = FreeGroup $ DList.singleton (Right a)
FreeGroup as >>= f = FreeGroup $ as >>= runFreeGroup . either f f
normalize
:: Eq a
=> DList (Either a a)
-> DList (Either a a)
normalize = DList.fromList . normalizeL . DList.toList
fromDList :: Eq a => DList (Either a a) -> FreeGroup a
fromDList = freeGroupFromList . DList.toList
freeGroupFromList :: Eq a => [Either a a] -> FreeGroup a
freeGroupFromList = FreeGroup . DList.fromList . normalizeL
toDList :: FreeGroup a -> DList (Either a a)
toDList = runFreeGroup
instance Eq a => Semigroup (FreeGroup a) where
FreeGroup as <> FreeGroup bs = FreeGroup $ normalize (as `DList.append` bs)
instance Eq a => Monoid (FreeGroup a) where
mempty = FreeGroup DList.empty
#if __GLASGOW_HASKELL__ <= 802
mappend = (<>)
#endif
instance Eq a => Group (FreeGroup a) where
invert (FreeGroup as) = FreeGroup $ foldl (\acu a -> either Right Left a `DList.cons` acu) DList.empty as
type instance AlgebraType0 FreeGroup a = Eq a
type instance AlgebraType FreeGroup g = (Eq g, Group g)
instance FreeAlgebra FreeGroup where
returnFree a = FreeGroup (DList.singleton (Right a))
foldMapFree _ (FreeGroup DList.Nil) = mempty
foldMapFree f (FreeGroup as) =
let a' = DList.head as
as' = DList.tail as
in either (invert . f) f a' `mappend` foldMapFree f (FreeGroup as')
newtype FreeGroupL a = FreeGroupL { runFreeGroupL :: [Either a a] }
deriving (Show, Eq, Ord)
normalizeL
:: Eq a
=> [Either a a]
-> [Either a a]
normalizeL = foldr consL_ []
consL :: Eq a => Either a a -> FreeGroupL a -> FreeGroupL a
consL a (FreeGroupL as) = FreeGroupL (consL_ a as)
consL_ :: Eq a => Either a a -> [Either a a] -> [Either a a]
consL_ a [] = [a]
consL_ a as@(b:bs) = case (a, b) of
(Left x, Right y) | x == y -> bs
(Right x, Left y) | x == y -> bs
_ -> a : as
fromList :: Eq a => [Either a a] -> FreeGroupL a
fromList = FreeGroupL . normalizeL
toList :: FreeGroupL a -> [Either a a]
toList = runFreeGroupL
instance Eq a => Semigroup (FreeGroupL a) where
FreeGroupL as <> FreeGroupL bs = FreeGroupL $ foldr consL_ bs as
instance Eq a => Monoid (FreeGroupL a) where
mempty = FreeGroupL []
#if __GLASGOW_HASKELL__ <= 802
mappend = (<>)
#endif
instance Eq a => Group (FreeGroupL a) where
invert (FreeGroupL as) = FreeGroupL $ foldl (\acu a -> either Right Left a : acu) [] as
type instance AlgebraType0 FreeGroupL a = Eq a
type instance AlgebraType FreeGroupL g = (Eq g, Group g)
instance FreeAlgebra FreeGroupL where
returnFree a = FreeGroupL [Right a]
foldMapFree _ (FreeGroupL []) = mempty
foldMapFree f (FreeGroupL (a : as)) =
either (invert . f) f a `mappend` foldMapFree f (FreeGroupL as)