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

> This module implements an algorithm to decide whether a given FSA
> is Locally Testable (LT) based on the semigroup characterization
> of Brzozowski and Simon from their 1973 work
> "Characterizations of locally testable events".
>
> @since 0.2
> -}
> module LTK.Decide.LT (isLT, isLTM) where

> import qualified Data.Set as Set

> import LTK.FSA
> import LTK.Algebra

> -- |True iff the automaton recognizes an LT stringset.
> isLT :: (Ord n, Ord e) => FSA n e -> Bool
> isLT :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isLT = forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isLTM 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

A semigroup (S) [e.g. the syntactic semigroup] is locally testable iff
for all idempotent e, the generated subsemigroup eSe is an idempotent
commutative monoid.

> -- |True iff the given monoid is locally a semilattice.
> --
> -- @since 1.0
> isLTM :: (Ord n, Ord e) => SynMon n e -> Bool
> isLTM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isLTM SynMon n e
s = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (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 SynMon n e
s) (forall c a. (Container c a, Eq a) => c -> c -> Bool
isSubsetOf Set (State ([Maybe n], [Symbol e]))
i) 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
s)
>           forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Set a -> [a]
Set.toList forall a b. (a -> b) -> a -> b
$ Set (State ([Maybe n], [Symbol e]))
i
>     where i :: Set (State ([Maybe n], [Symbol e]))
i = forall n e. (Ord n, Ord e) => FSA (n, [Symbol e]) e -> Set (T n e)
idempotents SynMon n e
s