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

> This module implements an algorithm to decide whether a syntactic
> semigroup \(S\) is locally Piecewise Testable (LPT).  This is the
> case iff each of its idempotents \(e\) satisfies the property that
> \(eSe\) is \(\mathcal{J}\)-trivial.
>
> @since 1.0
> -}
> module LTK.Decide.LPT (isLPT, isLPTM, isLPTs) where

> import Data.Representation.FiniteSemigroup

> import LTK.FSA
> import LTK.Algebra

> -- |True iff the automaton recognizes an LPT stringset.
> isLPT :: (Ord n, Ord e) => FSA n e -> Bool
> isLPT :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isLPT = GeneratedAction -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isLPTs (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 is locally \(\mathcal{J}\)-trivial.
> isLPTM :: (Ord n, Ord e) => SynMon n e -> Bool
> isLPTM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isLPTM = FSA ([Maybe n], [Symbol e]) e -> Bool
forall n e. (Ord n, Ord e) => FSA n e -> Bool
isLPT

> -- |True iff the semigroup is locally \(\mathcal{J}\)-trivial.
> --
> -- @since 1.2
> isLPTs :: FiniteSemigroupRep s => s -> Bool
> isLPTs :: forall s. FiniteSemigroupRep s => s -> Bool
isLPTs = (FSMult -> Bool) -> s -> Bool
forall s. FiniteSemigroupRep s => (FSMult -> Bool) -> s -> Bool
locally FSMult -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isJTrivial