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

> This module implements an algorithm to decide whether a given FSA
> is generalized locally testable in the sense of Brzozowski and
> Fich (1984):
> https://doi.org/10.1016/0012-365X(84)90045-1
>
> @since 1.0
> -}
> module LTK.Decide.GLT (isGLT, isGLTM) where

> import qualified Data.Set as Set

> import LTK.FSA
> import LTK.Algebra

> -- |True iff the automaton recognizes a generalized locally-testable
> -- stringset.
> isGLT :: (Ord n, Ord e) => FSA n e -> Bool
> isGLT :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isGLT = forall n e. (Ord n, Ord e) => FSA (n, [Symbol e]) e -> Bool
isGLTM 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 the generalized local testabiltiy
> -- condition.
> isGLTM :: (Ord n, Ord e) => FSA (n, [Symbol e]) e -> Bool
> isGLTM :: forall n e. (Ord n, Ord e) => FSA (n, [Symbol e]) e -> Bool
isGLTM FSA (n, [Symbol e]) e
f = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Set (T n e) -> Bool
commutativeBand 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)
emee FSA (n, [Symbol e]) e
f) forall a b. (a -> b) -> a -> b
$ forall a. Set a -> [a]
Set.toList Set (T n e)
i
>     where i :: Set (T n e)
i = forall n e. (Ord n, Ord e) => FSA (n, [Symbol e]) e -> Set (T n e)
idempotents FSA (n, [Symbol e]) e
f
>           commutativeBand :: Set (T n e) -> Bool
commutativeBand = forall a. (a -> Bool) -> (a -> Bool) -> a -> Bool
both (forall n e.
(Ord n, Ord e) =>
FSA (n, [Symbol e]) e -> Set (State (n, [Symbol e])) -> Bool
isCommutative FSA (n, [Symbol e]) e
f) (forall c a. (Container c a, Eq a) => c -> c -> Bool
isSubsetOf Set (T n e)
i)