> {-# OPTIONS_HADDOCK show-extensions #-}
> {-|
> Module    : LTK.Decide.GD
> Copyright : (c) 2021-2024 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, isGDs, isTGD, isTGDM, isTGDs) where

> import Data.Representation.FiniteSemigroup

> import LTK.FSA
> import LTK.Algebra(SynMon)
> 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 = GeneratedAction -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isGDs (GeneratedAction -> Bool)
-> (FSA n e -> GeneratedAction) -> FSA n e -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FSA n e -> GeneratedAction
forall n e. (Ord n, Ord e) => FSA n e -> GeneratedAction
syntacticSemigroup

> -- |True iff the monoid satisfies \(eSe=e\) for all idempotents \(e\),
> -- except the identity if it is not instantiated.
> isGDM :: (Ord n, Ord e) => SynMon n e -> Bool
> isGDM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isGDM = FSA ([Maybe n], [Symbol e]) e -> Bool
forall n e. (Ord n, Ord e) => FSA n e -> Bool
isGD

> -- |True iff the semigroup satisfies \(eSe=e\)
> -- for all idempotents \(e\).
> --
> -- @since 1.2
> isGDs :: FiniteSemigroupRep s => s -> Bool
> isGDs :: forall s. FiniteSemigroupRep s => s -> Bool
isGDs = (FSMult -> Bool) -> s -> Bool
forall s. FiniteSemigroupRep s => (FSMult -> Bool) -> s -> Bool
locally FSMult -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isTrivial

> -- |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 = FSA n e -> Bool
forall n e. (Ord n, Ord e) => FSA n e -> Bool
isGD (FSA n e -> Bool) -> (FSA n e -> FSA n e) -> FSA n e -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FSA n e -> FSA n e
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 = SynMon n e -> Bool
forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isGDM (SynMon n e -> Bool)
-> (SynMon n e -> SynMon n e) -> SynMon n e -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SynMon n e -> SynMon n e
forall n e. (Ord n, Ord e) => FSA n e -> FSA n e
project

> -- |True iff the projected subsemigroup satisfies eSe=e
> --
> -- @since 1.2
> isTGDs :: FiniteSemigroupRep s => s -> Bool
> isTGDs :: forall s. FiniteSemigroupRep s => s -> Bool
isTGDs = FSMult -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isGDs (FSMult -> Bool) -> (s -> FSMult) -> s -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> FSMult
forall s. FiniteSemigroupRep s => s -> FSMult
projectedSubsemigroup