> {-# OPTIONS_HADDOCK show-extensions #-}
> {-|
> Module    : LTK.Decide.LAcom
> Copyright : (c) 2019-2024 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, isLAcoms) where

> import Data.Representation.FiniteSemigroup

> import LTK.FSA
> import LTK.Algebra(SynMon)

> -- |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 = GeneratedAction -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isLAcoms (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 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 = FSA ([Maybe n], [Symbol e]) e -> Bool
forall n e. (Ord n, Ord e) => FSA n e -> Bool
isLAcom

> -- |True iff the semigroup recognizes a LAcom stringset.
> --
> -- @since 1.2
> isLAcoms :: FiniteSemigroupRep s => s -> Bool
> isLAcoms :: forall s. FiniteSemigroupRep s => s -> Bool
isLAcoms = (FSMult -> Bool) -> s -> Bool
forall s. FiniteSemigroupRep s => (FSMult -> Bool) -> s -> Bool
locally ((FSMult -> Bool) -> (FSMult -> Bool) -> FSMult -> Bool
forall a. (a -> Bool) -> (a -> Bool) -> a -> Bool
both FSMult -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isAperiodic FSMult -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isCommutative)