uvmhs-0.0.0.0
Safe HaskellSafe-Inferred
LanguageHaskell2010

UVMHS.Lib.Parser.Regex

Documentation

class Classified c t | t -> c where Source #

Methods

classify :: t -> c Source #

Instances

Instances details
Classified CharClass Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

data RegexResult o u Source #

Instances

Instances details
(Show o, Show u) => Show (RegexResult o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

showsPrec :: Int -> RegexResult o u -> ShowS #

show :: RegexResult o u -> String #

showList :: [RegexResult o u] -> ShowS #

(Eq o, Eq u) => Eq (RegexResult o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

(==) :: RegexResult o u -> RegexResult o u -> Bool #

(/=) :: RegexResult o u -> RegexResult o u -> Bool #

(Ord o, Ord u) => Ord (RegexResult o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

compare :: RegexResult o u -> RegexResult o u -> Ordering #

(<) :: RegexResult o u -> RegexResult o u -> Bool #

(<=) :: RegexResult o u -> RegexResult o u -> Bool #

(>) :: RegexResult o u -> RegexResult o u -> Bool #

(>=) :: RegexResult o u -> RegexResult o u -> Bool #

max :: RegexResult o u -> RegexResult o u -> RegexResult o u #

min :: RegexResult o u -> RegexResult o u -> RegexResult o u #

Ord u => Append (RegexResult o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

(⧺) :: RegexResult o u -> RegexResult o u -> RegexResult o u Source #

Zero u => Eps (RegexResult o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

eps :: RegexResult o u Source #

(Ord u, Zero u) => Monoid (RegexResult o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Zero u => Null (RegexResult o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

null :: RegexResult o u Source #

(Ord u, Plus u) => Seq (RegexResult o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

(▷) :: RegexResult o u -> RegexResult o u -> RegexResult o u Source #

(Ord u, Additive u) => Seqoid (RegexResult o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

(Pretty ℕ64, Pretty Formats, Pretty (𝑂 o), Pretty u) => Pretty (RegexResult o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

pretty :: RegexResult o u -> Doc Source #

newtype RegexInfo o u Source #

Constructors

RegexInfo 

Instances

Instances details
(Show o, Show u) => Show (RegexInfo o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

showsPrec :: Int -> RegexInfo o u -> ShowS #

show :: RegexInfo o u -> String #

showList :: [RegexInfo o u] -> ShowS #

(Eq o, Eq u) => Eq (RegexInfo o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

(==) :: RegexInfo o u -> RegexInfo o u -> Bool #

(/=) :: RegexInfo o u -> RegexInfo o u -> Bool #

(Ord o, Ord u) => Ord (RegexInfo o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

compare :: RegexInfo o u -> RegexInfo o u -> Ordering #

(<) :: RegexInfo o u -> RegexInfo o u -> Bool #

(<=) :: RegexInfo o u -> RegexInfo o u -> Bool #

(>) :: RegexInfo o u -> RegexInfo o u -> Bool #

(>=) :: RegexInfo o u -> RegexInfo o u -> Bool #

max :: RegexInfo o u -> RegexInfo o u -> RegexInfo o u #

min :: RegexInfo o u -> RegexInfo o u -> RegexInfo o u #

Ord u => Append (RegexInfo o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

(⧺) :: RegexInfo o u -> RegexInfo o u -> RegexInfo o u Source #

Zero u => Eps (RegexInfo o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

eps :: RegexInfo o u Source #

(Ord u, Zero u) => Monoid (RegexInfo o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Zero u => Null (RegexInfo o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

null :: RegexInfo o u Source #

(Ord u, Plus u) => Seq (RegexInfo o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

(▷) :: RegexInfo o u -> RegexInfo o u -> RegexInfo o u Source #

(Ord u, Additive u) => Seqoid (RegexInfo o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Pretty (𝑂 (RegexResult o u)) => Pretty (RegexInfo o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

pretty :: RegexInfo o u -> Doc Source #

newtype Regex c t o u Source #

Constructors

Regex 

Fields

Instances

Instances details
(Show o, Show u, Show t, Show c) => Show (Regex c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

showsPrec :: Int -> Regex c t o u -> ShowS #

show :: Regex c t o u -> String #

showList :: [Regex c t o u] -> ShowS #

(Eq o, Eq u, Eq t, Eq c) => Eq (Regex c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

(==) :: Regex c t o u -> Regex c t o u -> Bool #

(/=) :: Regex c t o u -> Regex c t o u -> Bool #

(Ord o, Ord u, Ord t, Ord c) => Ord (Regex c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

compare :: Regex c t o u -> Regex c t o u -> Ordering #

(<) :: Regex c t o u -> Regex c t o u -> Bool #

(<=) :: Regex c t o u -> Regex c t o u -> Bool #

(>) :: Regex c t o u -> Regex c t o u -> Bool #

(>=) :: Regex c t o u -> Regex c t o u -> Bool #

max :: Regex c t o u -> Regex c t o u -> Regex c t o u #

min :: Regex c t o u -> Regex c t o u -> Regex c t o u #

(Ord c, Ord t, Ord o, Ord u, Plus u) => Append (Regex c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

(⧺) :: Regex c t o u -> Regex c t o u -> Regex c t o u Source #

(Ord c, Ord t, Ord o, Ord u, Zero u) => Eps (Regex c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

eps :: Regex c t o u Source #

(Ord c, Ord t, Ord o, Ord u, Additive u) => Kleene (Regex c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

(Ord c, Ord t, Ord o, Ord u, Additive u) => Monoid (Regex c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Zero u => Null (Regex c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

null :: Regex c t o u Source #

(Ord c, Ord t, Ord o, Ord u, Additive u) => Seq (Regex c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

(▷) :: Regex c t o u -> Regex c t o u -> Regex c t o u Source #

(Ord c, Ord t, Ord o, Ord u, Additive u) => Seqoid (Regex c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

(Ord c, Ord t, Ord o, Ord u, Zero u) => Star (Regex c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

star :: Regex c t o u -> Regex c t o u Source #

data RegexU c t o u Source #

Constructors

NullR 
ResR (RegexResult o u) 
AtomR (RegexResult o u) (RegexAtom c t o u) 
SumsR (𝑃 (Regex c t o u)) 
SeqsR (𝐿 (Regex c t o u)) 
StarR (RegexResult o u) (Regex c t o u) 

Instances

Instances details
(Show o, Show u, Show t, Show c) => Show (RegexU c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

showsPrec :: Int -> RegexU c t o u -> ShowS #

show :: RegexU c t o u -> String #

showList :: [RegexU c t o u] -> ShowS #

(Eq o, Eq u, Eq t, Eq c) => Eq (RegexU c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

(==) :: RegexU c t o u -> RegexU c t o u -> Bool #

(/=) :: RegexU c t o u -> RegexU c t o u -> Bool #

(Ord o, Ord u, Ord t, Ord c) => Ord (RegexU c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

compare :: RegexU c t o u -> RegexU c t o u -> Ordering #

(<) :: RegexU c t o u -> RegexU c t o u -> Bool #

(<=) :: RegexU c t o u -> RegexU c t o u -> Bool #

(>) :: RegexU c t o u -> RegexU c t o u -> Bool #

(>=) :: RegexU c t o u -> RegexU c t o u -> Bool #

max :: RegexU c t o u -> RegexU c t o u -> RegexU c t o u #

min :: RegexU c t o u -> RegexU c t o u -> RegexU c t o u #

(Pretty (RegexResult o u), Pretty (RegexAtom c t o u), Pretty (𝑃 (Regex c t o u)), Pretty (𝐿 (Regex c t o u)), Pretty (Regex c t o u)) => Pretty (RegexU c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

pretty :: RegexU c t o u -> Doc Source #

data RegexAtom c t o u Source #

Constructors

TokRA t 
NTokRA (𝑃 t) 
ClassRA c 

Instances

Instances details
(Show t, Show c) => Show (RegexAtom c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

showsPrec :: Int -> RegexAtom c t o u -> ShowS #

show :: RegexAtom c t o u -> String #

showList :: [RegexAtom c t o u] -> ShowS #

(Eq t, Eq c) => Eq (RegexAtom c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

(==) :: RegexAtom c t o u -> RegexAtom c t o u -> Bool #

(/=) :: RegexAtom c t o u -> RegexAtom c t o u -> Bool #

(Ord t, Ord c) => Ord (RegexAtom c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

compare :: RegexAtom c t o u -> RegexAtom c t o u -> Ordering #

(<) :: RegexAtom c t o u -> RegexAtom c t o u -> Bool #

(<=) :: RegexAtom c t o u -> RegexAtom c t o u -> Bool #

(>) :: RegexAtom c t o u -> RegexAtom c t o u -> Bool #

(>=) :: RegexAtom c t o u -> RegexAtom c t o u -> Bool #

max :: RegexAtom c t o u -> RegexAtom c t o u -> RegexAtom c t o u #

min :: RegexAtom c t o u -> RegexAtom c t o u -> RegexAtom c t o u #

(Pretty t, Pretty (𝑃 t), Pretty c) => Pretty (RegexAtom c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

pretty :: RegexAtom c t o u -> Doc Source #

nullRegex :: Zero u => Regex c t o u Source #

resRegex :: (Ord c, Ord t, Ord o, Ord u, Zero u) => RegexResult o u -> Regex c t o u Source #

epsRegex :: (Ord c, Ord t, Ord o, Ord u, Zero u) => Regex c t o u Source #

retRegex :: (Ord c, Ord t, Ord o, Ord u, Zero u) => ℕ64 -> Formats -> 𝑂 o -> u -> Regex c t o u Source #

outRegex :: (Ord c, Ord t, Ord o, Ord u, Zero u) => ℕ64 -> Formats -> o -> Regex c t o u Source #

lepsRegex :: (Ord c, Ord t, Ord o, Ord u, Zero u) => ℕ64 -> Regex c t o u Source #

fepsRegex :: (Ord c, Ord t, Ord o, Ord u, Zero u) => Formats -> Regex c t o u Source #

oepsRegex :: (Ord c, Ord t, Ord o, Ord u, Zero u) => o -> Regex c t o u Source #

uepsRegex :: (Ord c, Ord t, Ord o, Ord u, Zero u) => u -> Regex c t o u Source #

atomRegex :: (Ord c, Ord t, Ord o, Ord u, Zero u) => RegexAtom c t o u -> Regex c t o u Source #

tokRegex :: (Ord c, Ord t, Ord o, Ord u, Zero u) => t -> Regex c t o u Source #

ntokRegex :: (Ord c, Ord t, Ord o, Ord u, Zero u) => 𝑃 t -> Regex c t o u Source #

classRegex :: (Ord c, Ord t, Ord o, Ord u, Zero u) => c -> Regex c t o u Source #

consEpsRegex :: (Ord c, Ord t, Ord o, Ord u, Plus u) => RegexResult o u -> Regex c t o u -> Regex c t o u Source #

consEpsRegexU :: (Ord c, Ord t, Ord o, Ord u, Plus u) => RegexResult o u -> RegexU c t o u -> RegexU c t o u Source #

snocEpsRegex :: (Ord c, Ord t, Ord o, Ord u, Plus u) => RegexResult o u -> Regex c t o u -> Regex c t o u Source #

snocEpsRegexU :: (Ord c, Ord t, Ord o, Ord u, Plus u) => RegexResult o u -> RegexU c t o u -> RegexU c t o u Source #

sumRegex :: (Ord c, Ord t, Ord o, Ord u, Plus u) => Regex c t o u -> Regex c t o u -> Regex c t o u Source #

seqRegex :: (Ord c, Ord t, Ord o, Ord u, Additive u) => Regex c t o u -> Regex c t o u -> Regex c t o u Source #

starRegex :: (Ord c, Ord t, Ord o, Ord u, Zero u) => Regex c t o u -> Regex c t o u Source #

derRegex :: (Ord c, Ord t, Classified c t, Ord o, Ord u, Additive u) => (t c) -> Regex c t o u -> Regex c t o u Source #

derRegexAtom :: (Ord c, Ord t, Classified c t, Ord o, Ord u, Additive u) => (t c) -> RegexAtom c t o u -> Regex c t o u Source #

derRegexSequence :: (Ord t, Ord c, Classified c t, Ord o, Ord u, Additive u) => (t c) -> 𝐿 (Regex c t o u) -> Regex c t o u Source #

regexLits :: Ord t => Regex c t o u -> 𝑃 t Source #

regexLitsAtom :: Ord t => RegexAtom c t o u -> 𝑃 t Source #

regexStateDeadL :: forall (c :: Type) (t :: Type) (o :: Type) (u :: Type). (⟢) (RegexState c t o u) ((⇰) ℕ64 𝔹) Source #

regexStateResultsL :: forall (c :: Type) (t :: Type) (o :: Type) (u :: Type). (⟢) (RegexState c t o u) ((⇰) ℕ64 (𝑂 (RegexResult o u))) Source #

regexStateTransitionsL :: forall (c :: Type) (t :: Type) (o :: Type) (u :: Type). (⟢) (RegexState c t o u) ((⇰) ((∨) t c) ((⇰) ℕ64 ℕ64)) Source #

regexStateMapL :: forall (c :: Type) (t :: Type) (o :: Type) (u :: Type). (⟢) (RegexState c t o u) ((⇰) (Regex c t o u) ℕ64) Source #

regexStateNextIDL :: forall (c :: Type) (t :: Type) (o :: Type) (u :: Type). (⟢) (RegexState c t o u) ℕ64 Source #

data DFA c t o u Source #

Constructors

DFA 

Instances

Instances details
(Pretty (𝑃 t), Pretty ℕ64, Pretty ((t c) 𝕍 ℕ64), Pretty (𝕍 (𝑂 (RegexResult o u))), Pretty (𝕍 𝔹)) => Pretty (DFA c t o u) Source # 
Instance details

Defined in UVMHS.Lib.Parser.Regex

Methods

pretty :: DFA c t o u -> Doc Source #

compileRegex :: forall c t o u. (Pretty t, Pretty o, Pretty u, Ord c, Ord t, Classified c t, All c, Ord o, Ord u, Additive u) => Regex c t o u -> DFA c t o u Source #

data Lexer c t o u w Source #

Constructors

Lexer 

Fields

tokenize :: forall c t o u w. (Show u, Ord c, Ord t, Pretty t, Classified c t, Eq o, Eq u, Plus u) => Lexer c t o u w -> 𝕊 -> 𝕍 (ParserToken t) -> Doc 𝕍 (PreParserToken w) Source #

tokenizeFIO :: forall c t o u w w'. (Show u, Ord c, Ord t, Pretty t, Classified c t, Eq o, Eq u, Plus u) => Lexer c t o u w -> 𝕊 -> (𝕍 (PreParserToken w) -> 𝕍 (PreParserToken w')) -> 𝕍 (ParserToken t) -> IO (𝕍 (ParserToken w')) Source #

tokenizeIO :: forall c t o u w. (Show u, Ord c, Ord t, Pretty t, Classified c t, Eq o, Eq u, Plus u) => Lexer c t o u w -> 𝕊 -> 𝕍 (ParserToken t) -> IO (𝕍 (ParserToken w)) Source #

tokenizeFIOMain :: forall c t o u w w'. (Show u, Ord c, Ord t, Pretty t, Classified c t, Eq o, Eq u, Plus u, Pretty w') => Lexer c t o u w -> 𝕊 -> (𝕍 (PreParserToken w) -> 𝕍 (PreParserToken w')) -> 𝕍 (ParserToken t) -> IO () Source #

tokenizeIOMain :: forall c t o u w. (Show u, Ord c, Ord t, Pretty t, Classified c t, Eq o, Eq u, Plus u, Pretty w) => Lexer c t o u w -> 𝕊 -> 𝕍 (ParserToken t) -> IO () Source #

lWord :: (Zero u, Ord o, Ord u, Additive u) => 𝕊 -> Regex CharClass o u Source #

lSpace :: (Zero u, Ord o, Ord u, Additive u) => Regex CharClass o u Source #

lNl :: (Zero u, Ord o, Ord u, Additive u) => Regex CharClass o u Source #

lName :: (Zero u, Ord u, Ord o, Additive u) => Regex CharClass o u Source #

lNat :: (Zero u, Ord u, Ord o, Additive u) => Regex CharClass o u Source #

lInt :: (Zero u, Ord o, Ord u, Additive u) => Regex CharClass o u Source #

lDbl :: (Zero u, Ord o, Ord u, Additive u) => Regex CharClass o u Source #

blockifyTokens :: forall t. 𝐿 (AddBT Loc) -> (t -> 𝔹) -> (t -> 𝔹) -> (IndentCommand -> t) -> 𝕍 (PreParserToken t) -> 𝕍 (PreParserToken t) Source #