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

> This module implements an algorithm to decide whether a given FSA
> is Piecewise Testable (PT) based on the semigroup characterization
> of Simon from his 1975 work "Piecewise testable events".
>
> @since 0.2
> -}
> module LTK.Decide.PT (isPT, isPTM, isPTs) where

> import Data.Representation.FiniteSemigroup

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

> -- |True iff the automaton recognizes a PT stringset.
> isPT :: (Ord n, Ord e) => FSA n e -> Bool
> isPT :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isPT = GeneratedAction -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isPTs (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 \(\mathcal{J}\)-trivial
> --
> -- @since 1.0
> isPTM :: (Ord n, Ord e) => SynMon n e -> Bool
> isPTM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isPTM = (FSA ([Maybe n], [Symbol e]) e
 -> Set (Set (State ([Maybe n], [Symbol e]))))
-> FSA ([Maybe n], [Symbol e]) e -> Bool
forall n e. (FSA n e -> Set (Set (State n))) -> FSA n e -> Bool
trivialUnder FSA ([Maybe n], [Symbol e]) e
-> Set (Set (State ([Maybe n], [Symbol e])))
forall e n.
(Ord e, Ord n) =>
FSA ([Maybe n], [Symbol e]) e
-> Set (Set (State ([Maybe n], [Symbol e])))
jEquivalence

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