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

> This module implements an algorithm to decide whether a given FSA
> has a syntactic semigroup which is Locally Commutative and Aperiodic,
> a near superclass of the Locally Threshold Testable languages.
>
> @since 1.1
> -}
> module LTK.Decide.LAcom (isLAcom, isLAcomM) where

> import LTK.Decide.SF (isSFM)
> import LTK.Decide.Acom (comTest)
> import LTK.FSA
> import LTK.Algebra

> -- |True iff the automaton recognizes a LAcom stringset.
> isLAcom :: (Ord n, Ord e) => FSA n e -> Bool
> isLAcom :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isLAcom = forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isLAcomM 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 recognizes a LAcom stringset.
> isLAcomM :: (Ord n, Ord e) => SynMon n e -> Bool
> isLAcomM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isLAcomM = forall a. (a -> Bool) -> (a -> Bool) -> a -> Bool
both forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isSFM forall n e. (Ord n, Ord e) => SynMon n e -> Bool
eseCom
>     where eseCom :: SynMon n e -> Bool
eseCom SynMon n e
m = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (forall n e.
(Ord n, Ord e) =>
SynMon n e -> Set (State (S [Maybe n] e)) -> Bool
comTest SynMon n e
m 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 n e. (Ord n, Ord e) => FSA (n, [Symbol e]) e -> Set (T n e)
idempotents SynMon n e
m)