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

> This module implements an algorithm to decide whether a given FSA
> is Definite (Def) or Reverse Definite (RDef) based on the classic
> semigroup characterizations summarized by Brzozowski and Fich in
> their 1984 work "On Generalized Locally Testable Languages".
>
> @since 1.0
> -}
> module LTK.Decide.Definite
>     ( -- *Plain
>       isDef
>     , isDefM
>     , isRDef
>     , isRDefM
>       -- *Tier-Based
>     , isTDef
>     , isTDefM
>     , isTRDef
>     , isTRDefM
>     ) where

> import qualified Data.Set as Set

> import LTK.FSA
> import LTK.Algebra
> import LTK.Tiers (project)

> -- |True iff the automaton recognizes a definite stringset,
> -- characterized by a set of permitted suffixes.
> isDef :: (Ord n, Ord e) => FSA n e -> Bool
> isDef :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isDef = forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isDefM 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 \(Se=e\) for idempotents \(e\).
> isDefM :: (Ord n, Ord e) => SynMon n e -> Bool
> isDefM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isDefM SynMon n e
s = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((forall a. Eq a => a -> a -> Bool
==Int
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Set a -> Int
Set.size forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n e.
(Ord n, Ord e) =>
FSA (n, [Symbol e]) e
-> State (n, [Symbol e]) -> Set (State (n, [Symbol e]))
primitiveIdealL 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
$ forall n e. (Ord n, Ord e) => FSA (n, [Symbol e]) e -> Set (T n e)
idempotents SynMon n e
s

> -- |True iff the automaton recognizes a reverse definite stringset,
> -- characterized by a set of permitted prefixes.
> isRDef :: (Ord n, Ord e) => FSA n e -> Bool
> isRDef :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isRDef = forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isRDefM 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 \(eS=e\) for idempotents \(e\).
> isRDefM :: (Ord n, Ord e) => SynMon n e -> Bool
> isRDefM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isRDefM SynMon n e
s = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((forall a. Eq a => a -> a -> Bool
==Int
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Set a -> Int
Set.size forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n e. (Ord n, Ord e) => FSA n e -> State n -> Set (State n)
primitiveIdealR 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
$ forall n e. (Ord n, Ord e) => FSA (n, [Symbol e]) e -> Set (T n e)
idempotents SynMon n e
s

> -- |Definite on some tier.
> isTDef :: (Ord n, Ord e) => FSA n e -> Bool
> isTDef :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isTDef = forall n e. (Ord n, Ord e) => FSA n e -> Bool
isDef forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n e. (Ord n, Ord e) => FSA n e -> FSA n e
project

> -- |Definite on the projected subsemigroup.
> isTDefM :: (Ord n, Ord e) => SynMon n e -> Bool
> isTDefM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isTDefM = forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isDefM forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n e. (Ord n, Ord e) => FSA n e -> FSA n e
project

> -- |Reverse definite on some tier.
> isTRDef :: (Ord n, Ord e) => FSA n e -> Bool
> isTRDef :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isTRDef = forall n e. (Ord n, Ord e) => FSA n e -> Bool
isRDef forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n e. (Ord n, Ord e) => FSA n e -> FSA n e
project

> -- |Reverse definite on the projected subsemigroup.
> isTRDefM :: (Ord n, Ord e) => SynMon n e -> Bool
> isTRDefM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isTRDefM = forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isRDefM forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n e. (Ord n, Ord e) => FSA n e -> FSA n e
project