> {-# OPTIONS_HADDOCK show-extensions #-}
> {-|
> Module    : LTK.Decide.B
> Copyright : (c) 2022-2024 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
>                     , isBs, isLBs, isTLBs) where

> import Data.Representation.FiniteSemigroup

> import LTK.FSA
> import LTK.Algebra(SynMon)
> 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 = GeneratedAction -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isBs (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 a band.
> isBM :: (Ord n, Ord e) => SynMon n e -> Bool
> isBM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isBM = FSA ([Maybe n], [Symbol e]) e -> Bool
forall n e. (Ord n, Ord e) => FSA n e -> Bool
isB

> -- |True iff the semigroup is a band.
> --
> -- @since 1.2
> isBs :: FiniteSemigroupRep s => s -> Bool
> isBs :: forall s. FiniteSemigroupRep s => s -> Bool
isBs = s -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isBand

> -- |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 = GeneratedAction -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isLBs (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 a band.
> isLBM :: (Ord n, Ord e) => SynMon n e -> Bool
> isLBM :: forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isLBM = FSA ([Maybe n], [Symbol e]) e -> Bool
forall n e. (Ord n, Ord e) => FSA n e -> Bool
isLB

> -- |True iff the semigroup is locally a band.
> --
> -- @since 1.2
> isLBs :: FiniteSemigroupRep s => s -> Bool
> isLBs :: forall s. FiniteSemigroupRep s => s -> Bool
isLBs = (FSMult -> Bool) -> s -> Bool
forall s. FiniteSemigroupRep s => (FSMult -> Bool) -> s -> Bool
locally FSMult -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isBand

> -- |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 = FSA n e -> Bool
forall n e. (Ord n, Ord e) => FSA n e -> Bool
isLB (FSA n e -> Bool) -> (FSA n e -> FSA n e) -> FSA n e -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FSA n e -> FSA n e
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 = SynMon n e -> Bool
forall n e. (Ord n, Ord e) => SynMon n e -> Bool
isLBM (SynMon n e -> Bool)
-> (SynMon n e -> SynMon n e) -> SynMon n e -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SynMon n e -> SynMon n e
forall n e. (Ord n, Ord e) => FSA n e -> FSA n e
project

> -- |True iff the semigroup is locally a band on some tier.
> --
> -- @since 1.2
> isTLBs :: FiniteSemigroupRep s => s -> Bool
> isTLBs :: forall s. FiniteSemigroupRep s => s -> Bool
isTLBs = FSMult -> Bool
forall s. FiniteSemigroupRep s => s -> Bool
isLBs (FSMult -> Bool) -> (s -> FSMult) -> s -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> FSMult
forall s. FiniteSemigroupRep s => s -> FSMult
projectedSubsemigroup