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

> This module implements an algorithm to decide whether a given FSA
> is in B, the subclass of FO2[<] where all elements are idempotent
> but the operation is not necessarily commutative.  Thus, this is
> a superclass of CB.  The local and tier-local extensions are also
> provided.
>
> @since 1.0
> -}
> module LTK.Decide.B (isB, isBM, isLB, isLBM, isTLB, isTLBM) where

> import qualified Data.Set as Set

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

> -- |True iff the automaton recognizes a band stringset.
> isB :: (Ord n, Ord e) => FSA n e -> Bool
> isB :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isB = forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isBM 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 is a band.
> isBM :: (Ord n, Ord e) => SynMon n e -> Bool
> isBM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isBM SynMon n e
m = forall a. Ord a => Set a -> Set a -> Set a
Set.union (forall n e. FSA n e -> Set (State n)
initials 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) forall a. Eq a => a -> a -> Bool
== forall e n. (Ord e, Ord n) => FSA n e -> Set (State n)
states SynMon n e
m

> -- |True iff the recognized stringset is locally a band.
> isLB :: (Ord n, Ord e) => FSA n e -> Bool
> isLB :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isLB = forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isLBM 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 is locally a band.
> isLBM :: (Ord n, Ord e) => SynMon n e -> Bool
> isLBM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isLBM SynMon n e
m = forall (s :: * -> *) a. Collapsible s => (a -> Bool) -> s a -> Bool
allS T [Maybe n] e -> Bool
f (forall e n. (Ord e, Ord n) => FSA n e -> Set (State n)
states SynMon n e
m)
>     where f :: T [Maybe n] e -> Bool
f T [Maybe n] e
x = forall a. Set a -> Bool
Set.null (forall n e. (Ord n, Ord e) => FSA (S n e) e -> T n e -> Set (T n e)
ese SynMon n e
m T [Maybe n] e
x forall a. Ord a => Set a -> Set a -> Set a
`Set.difference` Set (T [Maybe n] e)
i)
>           i :: Set (T [Maybe n] e)
i = forall a. Ord a => Set a -> Set a -> Set a
Set.union (forall n e. FSA n e -> Set (State n)
initials 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)

> -- |True iff the recognized stringset is locally a band on some tier.
> isTLB :: (Ord n, Ord e) => FSA n e -> Bool
> isTLB :: forall n e. (Ord n, Ord e) => FSA n e -> Bool
isTLB = forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isLBM 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n e. (Ord n, Ord e) => FSA n e -> FSA n e
project

> -- |True iff the monoid is locally a band on some tier.
> isTLBM :: (Ord n, Ord e) => SynMon n e -> Bool
> isTLBM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isTLBM = forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isLBM forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n e. (Ord n, Ord e) => FSA n e -> FSA n e
project