module Language.Lexer.Tlex.Machine.Pattern (
    Pattern (..),
    enumsP,
    straightEnumSetP,
    anyoneP,
    AcceptPriority (..),
    mostPriority,
    Accept (..),
    compareAcceptsByPriority,
    StartState (..),
    startStateFromEnum,
) where

import           Language.Lexer.Tlex.Prelude

import qualified Data.EnumSet                        as EnumSet
import qualified Data.Hashable                       as Hashable
import qualified Language.Lexer.Tlex.Data.SymEnumSet as SymEnumSet


newtype StartState = StartState Int
    deriving (StartState -> StartState -> Bool
(StartState -> StartState -> Bool)
-> (StartState -> StartState -> Bool) -> Eq StartState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartState -> StartState -> Bool
$c/= :: StartState -> StartState -> Bool
== :: StartState -> StartState -> Bool
$c== :: StartState -> StartState -> Bool
Eq, Int -> StartState -> ShowS
[StartState] -> ShowS
StartState -> String
(Int -> StartState -> ShowS)
-> (StartState -> String)
-> ([StartState] -> ShowS)
-> Show StartState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartState] -> ShowS
$cshowList :: [StartState] -> ShowS
show :: StartState -> String
$cshow :: StartState -> String
showsPrec :: Int -> StartState -> ShowS
$cshowsPrec :: Int -> StartState -> ShowS
Show)
    deriving Int -> StartState
StartState -> Int
StartState -> [StartState]
StartState -> StartState
StartState -> StartState -> [StartState]
StartState -> StartState -> StartState -> [StartState]
(StartState -> StartState)
-> (StartState -> StartState)
-> (Int -> StartState)
-> (StartState -> Int)
-> (StartState -> [StartState])
-> (StartState -> StartState -> [StartState])
-> (StartState -> StartState -> [StartState])
-> (StartState -> StartState -> StartState -> [StartState])
-> Enum StartState
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: StartState -> StartState -> StartState -> [StartState]
$cenumFromThenTo :: StartState -> StartState -> StartState -> [StartState]
enumFromTo :: StartState -> StartState -> [StartState]
$cenumFromTo :: StartState -> StartState -> [StartState]
enumFromThen :: StartState -> StartState -> [StartState]
$cenumFromThen :: StartState -> StartState -> [StartState]
enumFrom :: StartState -> [StartState]
$cenumFrom :: StartState -> [StartState]
fromEnum :: StartState -> Int
$cfromEnum :: StartState -> Int
toEnum :: Int -> StartState
$ctoEnum :: Int -> StartState
pred :: StartState -> StartState
$cpred :: StartState -> StartState
succ :: StartState -> StartState
$csucc :: StartState -> StartState
Enum via Int

startStateFromEnum :: Enum s => s -> StartState
startStateFromEnum :: s -> StartState
startStateFromEnum s
x = Int -> StartState
StartState do s -> Int
forall a. Enum a => a -> Int
fromEnum s
x


newtype AcceptPriority = AcceptPriority Int
    deriving (AcceptPriority -> AcceptPriority -> Bool
(AcceptPriority -> AcceptPriority -> Bool)
-> (AcceptPriority -> AcceptPriority -> Bool) -> Eq AcceptPriority
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AcceptPriority -> AcceptPriority -> Bool
$c/= :: AcceptPriority -> AcceptPriority -> Bool
== :: AcceptPriority -> AcceptPriority -> Bool
$c== :: AcceptPriority -> AcceptPriority -> Bool
Eq, Int -> AcceptPriority -> ShowS
[AcceptPriority] -> ShowS
AcceptPriority -> String
(Int -> AcceptPriority -> ShowS)
-> (AcceptPriority -> String)
-> ([AcceptPriority] -> ShowS)
-> Show AcceptPriority
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AcceptPriority] -> ShowS
$cshowList :: [AcceptPriority] -> ShowS
show :: AcceptPriority -> String
$cshow :: AcceptPriority -> String
showsPrec :: Int -> AcceptPriority -> ShowS
$cshowsPrec :: Int -> AcceptPriority -> ShowS
Show)
    deriving Eq AcceptPriority
Eq AcceptPriority
-> (AcceptPriority -> AcceptPriority -> Ordering)
-> (AcceptPriority -> AcceptPriority -> Bool)
-> (AcceptPriority -> AcceptPriority -> Bool)
-> (AcceptPriority -> AcceptPriority -> Bool)
-> (AcceptPriority -> AcceptPriority -> Bool)
-> (AcceptPriority -> AcceptPriority -> AcceptPriority)
-> (AcceptPriority -> AcceptPriority -> AcceptPriority)
-> Ord AcceptPriority
AcceptPriority -> AcceptPriority -> Bool
AcceptPriority -> AcceptPriority -> Ordering
AcceptPriority -> AcceptPriority -> AcceptPriority
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AcceptPriority -> AcceptPriority -> AcceptPriority
$cmin :: AcceptPriority -> AcceptPriority -> AcceptPriority
max :: AcceptPriority -> AcceptPriority -> AcceptPriority
$cmax :: AcceptPriority -> AcceptPriority -> AcceptPriority
>= :: AcceptPriority -> AcceptPriority -> Bool
$c>= :: AcceptPriority -> AcceptPriority -> Bool
> :: AcceptPriority -> AcceptPriority -> Bool
$c> :: AcceptPriority -> AcceptPriority -> Bool
<= :: AcceptPriority -> AcceptPriority -> Bool
$c<= :: AcceptPriority -> AcceptPriority -> Bool
< :: AcceptPriority -> AcceptPriority -> Bool
$c< :: AcceptPriority -> AcceptPriority -> Bool
compare :: AcceptPriority -> AcceptPriority -> Ordering
$ccompare :: AcceptPriority -> AcceptPriority -> Ordering
$cp1Ord :: Eq AcceptPriority
Ord via Down Int
    deriving (Int -> AcceptPriority -> Int
AcceptPriority -> Int
(Int -> AcceptPriority -> Int)
-> (AcceptPriority -> Int) -> Hashable AcceptPriority
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: AcceptPriority -> Int
$chash :: AcceptPriority -> Int
hashWithSalt :: Int -> AcceptPriority -> Int
$chashWithSalt :: Int -> AcceptPriority -> Int
Hashable.Hashable, Int -> AcceptPriority
AcceptPriority -> Int
AcceptPriority -> [AcceptPriority]
AcceptPriority -> AcceptPriority
AcceptPriority -> AcceptPriority -> [AcceptPriority]
AcceptPriority
-> AcceptPriority -> AcceptPriority -> [AcceptPriority]
(AcceptPriority -> AcceptPriority)
-> (AcceptPriority -> AcceptPriority)
-> (Int -> AcceptPriority)
-> (AcceptPriority -> Int)
-> (AcceptPriority -> [AcceptPriority])
-> (AcceptPriority -> AcceptPriority -> [AcceptPriority])
-> (AcceptPriority -> AcceptPriority -> [AcceptPriority])
-> (AcceptPriority
    -> AcceptPriority -> AcceptPriority -> [AcceptPriority])
-> Enum AcceptPriority
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: AcceptPriority
-> AcceptPriority -> AcceptPriority -> [AcceptPriority]
$cenumFromThenTo :: AcceptPriority
-> AcceptPriority -> AcceptPriority -> [AcceptPriority]
enumFromTo :: AcceptPriority -> AcceptPriority -> [AcceptPriority]
$cenumFromTo :: AcceptPriority -> AcceptPriority -> [AcceptPriority]
enumFromThen :: AcceptPriority -> AcceptPriority -> [AcceptPriority]
$cenumFromThen :: AcceptPriority -> AcceptPriority -> [AcceptPriority]
enumFrom :: AcceptPriority -> [AcceptPriority]
$cenumFrom :: AcceptPriority -> [AcceptPriority]
fromEnum :: AcceptPriority -> Int
$cfromEnum :: AcceptPriority -> Int
toEnum :: Int -> AcceptPriority
$ctoEnum :: Int -> AcceptPriority
pred :: AcceptPriority -> AcceptPriority
$cpred :: AcceptPriority -> AcceptPriority
succ :: AcceptPriority -> AcceptPriority
$csucc :: AcceptPriority -> AcceptPriority
Enum) via Int

mostPriority :: AcceptPriority
mostPriority :: AcceptPriority
mostPriority = Int -> AcceptPriority
AcceptPriority Int
0

data Accept a = Accept
    { Accept a -> AcceptPriority
accPriority       :: AcceptPriority
    , Accept a -> a
accSemanticAction :: a
    }
    deriving (Accept a -> Accept a -> Bool
(Accept a -> Accept a -> Bool)
-> (Accept a -> Accept a -> Bool) -> Eq (Accept a)
forall a. Eq a => Accept a -> Accept a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Accept a -> Accept a -> Bool
$c/= :: forall a. Eq a => Accept a -> Accept a -> Bool
== :: Accept a -> Accept a -> Bool
$c== :: forall a. Eq a => Accept a -> Accept a -> Bool
Eq, Int -> Accept a -> ShowS
[Accept a] -> ShowS
Accept a -> String
(Int -> Accept a -> ShowS)
-> (Accept a -> String) -> ([Accept a] -> ShowS) -> Show (Accept a)
forall a. Show a => Int -> Accept a -> ShowS
forall a. Show a => [Accept a] -> ShowS
forall a. Show a => Accept a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Accept a] -> ShowS
$cshowList :: forall a. Show a => [Accept a] -> ShowS
show :: Accept a -> String
$cshow :: forall a. Show a => Accept a -> String
showsPrec :: Int -> Accept a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Accept a -> ShowS
Show, a -> Accept b -> Accept a
(a -> b) -> Accept a -> Accept b
(forall a b. (a -> b) -> Accept a -> Accept b)
-> (forall a b. a -> Accept b -> Accept a) -> Functor Accept
forall a b. a -> Accept b -> Accept a
forall a b. (a -> b) -> Accept a -> Accept b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Accept b -> Accept a
$c<$ :: forall a b. a -> Accept b -> Accept a
fmap :: (a -> b) -> Accept a -> Accept b
$cfmap :: forall a b. (a -> b) -> Accept a -> Accept b
Functor)

compareAcceptsByPriority :: Accept a -> Accept a -> Ordering
compareAcceptsByPriority :: Accept a -> Accept a -> Ordering
compareAcceptsByPriority Accept{ $sel:accPriority:Accept :: forall a. Accept a -> AcceptPriority
accPriority = AcceptPriority
p1 } Accept{ $sel:accPriority:Accept :: forall a. Accept a -> AcceptPriority
accPriority = AcceptPriority
p2 } = AcceptPriority
p1 AcceptPriority -> AcceptPriority -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` AcceptPriority
p2

data Pattern e
    = Epsilon
    | Pattern e :^: Pattern e
    | Pattern e :|: Pattern e
    | Many (Pattern e)
    | Range (SymEnumSet.SymEnumSet e)
    deriving (Pattern e -> Pattern e -> Bool
(Pattern e -> Pattern e -> Bool)
-> (Pattern e -> Pattern e -> Bool) -> Eq (Pattern e)
forall e. Pattern e -> Pattern e -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Pattern e -> Pattern e -> Bool
$c/= :: forall e. Pattern e -> Pattern e -> Bool
== :: Pattern e -> Pattern e -> Bool
$c== :: forall e. Pattern e -> Pattern e -> Bool
Eq, Int -> Pattern e -> ShowS
[Pattern e] -> ShowS
Pattern e -> String
(Int -> Pattern e -> ShowS)
-> (Pattern e -> String)
-> ([Pattern e] -> ShowS)
-> Show (Pattern e)
forall e. (Enum e, Show e) => Int -> Pattern e -> ShowS
forall e. (Enum e, Show e) => [Pattern e] -> ShowS
forall e. (Enum e, Show e) => Pattern e -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Pattern e] -> ShowS
$cshowList :: forall e. (Enum e, Show e) => [Pattern e] -> ShowS
show :: Pattern e -> String
$cshow :: forall e. (Enum e, Show e) => Pattern e -> String
showsPrec :: Int -> Pattern e -> ShowS
$cshowsPrec :: forall e. (Enum e, Show e) => Int -> Pattern e -> ShowS
Show)

instance Enum e => Semigroup (Pattern e) where
    <> :: Pattern e -> Pattern e -> Pattern e
(<>) = Pattern e -> Pattern e -> Pattern e
forall e. Pattern e -> Pattern e -> Pattern e
(:^:)

instance Enum e => Monoid (Pattern e) where
    mempty :: Pattern e
mempty = Pattern e
forall e. Pattern e
Epsilon

enumsP :: Enum e => [e] -> Pattern e
enumsP :: [e] -> Pattern e
enumsP [e]
l = EnumSet e -> Pattern e
forall e. Enum e => EnumSet e -> Pattern e
straightEnumSetP do [e] -> EnumSet e
forall k. Enum k => [k] -> EnumSet k
EnumSet.fromList [e]
l

straightEnumSetP :: Enum e => EnumSet.EnumSet e -> Pattern e
straightEnumSetP :: EnumSet e -> Pattern e
straightEnumSetP EnumSet e
s = SymEnumSet e -> Pattern e
forall e. SymEnumSet e -> Pattern e
Range do Bool -> EnumSet e -> SymEnumSet e
forall a. Enum a => Bool -> EnumSet a -> SymEnumSet a
SymEnumSet.fromEnumSet Bool
True EnumSet e
s

anyoneP :: Enum e => Pattern e
anyoneP :: Pattern e
anyoneP = SymEnumSet e -> Pattern e
forall e. SymEnumSet e -> Pattern e
Range SymEnumSet e
forall a. Enum a => SymEnumSet a
SymEnumSet.full