> {-# OPTIONS_HADDOCK show-extensions #-}
> {-|
> Module    : LTK.Decide.GD
> Copyright : (c) 2021-2022 Dakotah Lambert
> License   : MIT

> This module implements an algorithm to decide whether a given FSA
> is Generalized Definite (GD) based on the semigroup characterization,
> or if it is Tier-Based Generalized Definite (TGD).
>
> @since 1.0
> -}
> module LTK.Decide.GD (isGD, isGDM, isTGD, isTGDM) where

> import qualified Data.Set as Set

> import LTK.FSA
> import LTK.Algebra
> import LTK.Tiers (project)

> -- |True iff the automaton recognizes a generalized definite stringset.
> isGD :: (Ord n, Ord e) => FSA n e -> Bool
> isGD :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isGD = forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isGDM forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e n.
(Ord e, Ord n) =>
FSA n e -> FSA ([Maybe n], [Symbol e]) e
syntacticMonoid

> -- |True iff the monoid satisfies \(eSe=e\) for all idempotents \(e\).
> isGDM :: (Ord n, Ord e) => SynMon n e -> Bool
> isGDM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isGDM SynMon n e
m = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((forall a. Eq a => a -> a -> Bool
== Int
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Set a -> Int
Set.size forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n e. (Ord n, Ord e) => FSA (S n e) e -> T n e -> Set (T n e)
ese SynMon n e
m) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Set a -> [a]
Set.toList forall a b. (a -> b) -> a -> b
$ forall n e. (Ord n, Ord e) => FSA (n, [Symbol e]) e -> Set (T n e)
idempotents SynMon n e
m

> -- |True iff the language is generalized definite for some tier.
> isTGD :: (Ord n, Ord e) => FSA n e -> Bool
> isTGD :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isTGD = forall n e. (Ord n, Ord e) => FSA n e -> Bool
isGD forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n e. (Ord n, Ord e) => FSA n e -> FSA n e
project

> -- |True iff the projected subsemigroup satisfies eSe=e
> isTGDM :: (Ord n, Ord e) => SynMon n e -> Bool
> isTGDM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isTGDM = forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isGDM forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n e. (Ord n, Ord e) => FSA n e -> FSA n e
project