{-# LANGUAGE UndecidableInstances #-}
module Mello.Match
( MatchErr (..)
, LocMatchErr (..)
, MatchT
, MatchM
, runMatchT
, runMatchM
, SeqMatchT
, SeqMatchM
, annoM
, memoM
, embedM
, matchM
, listM
, lookM
, elemM
, restM
, repeatM
, remainingM
, altM
, anySymM
, symM
, anyIntM
, intM
, anySciM
, sciM
, anyStrM
, strM
, anyCharM
, charM
, anyAtomM
, quoteM
, unquoteM
, docM
, MatchSexp (..)
, fromSexpT
, fromSexp
, fromAnnoSexpT
, fromAnnoSexp
, proxyM
)
where
import Bowtie (Anno (..), Memo (..), mkMemo, unMkMemo, pattern MemoP)
import Bowtie qualified as B
import Control.Exception (Exception)
import Control.Monad (ap, unless)
import Control.Monad.Except (ExceptT, MonadError (..), runExceptT)
import Control.Monad.Identity (Identity (..))
import Control.Monad.Reader (MonadReader (..), ReaderT (..), ask, asks, local)
import Control.Monad.State (MonadState (..), StateT, runStateT)
import Control.Monad.Trans (MonadTrans (..))
import Data.Proxy (Proxy)
import Data.Scientific (Scientific)
import Data.Sequence (Seq (..))
import Data.Sequence qualified as Seq
import Data.Text (Text)
import Data.Typeable (Typeable)
import Mello.Syntax (Atom (..), AtomType (..), Brace, Doc, Sexp (..), SexpF (..), SexpType (..), Sym (..))
data MatchErr e r
= MatchErrType !SexpType
| MatchErrTypeAtom
| MatchErrTypeQuote
| MatchErrTypeUnquote
| MatchErrTypeDoc
| MatchErrNotEq !Atom
| MatchErrListElem !Int
| MatchErrListRem
| MatchErrAlt !(Seq (Text, r))
| MatchErrEmbed !e
deriving stock (MatchErr e r -> MatchErr e r -> Bool
(MatchErr e r -> MatchErr e r -> Bool)
-> (MatchErr e r -> MatchErr e r -> Bool) -> Eq (MatchErr e r)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall e r. (Eq r, Eq e) => MatchErr e r -> MatchErr e r -> Bool
$c== :: forall e r. (Eq r, Eq e) => MatchErr e r -> MatchErr e r -> Bool
== :: MatchErr e r -> MatchErr e r -> Bool
$c/= :: forall e r. (Eq r, Eq e) => MatchErr e r -> MatchErr e r -> Bool
/= :: MatchErr e r -> MatchErr e r -> Bool
Eq, Eq (MatchErr e r)
Eq (MatchErr e r) =>
(MatchErr e r -> MatchErr e r -> Ordering)
-> (MatchErr e r -> MatchErr e r -> Bool)
-> (MatchErr e r -> MatchErr e r -> Bool)
-> (MatchErr e r -> MatchErr e r -> Bool)
-> (MatchErr e r -> MatchErr e r -> Bool)
-> (MatchErr e r -> MatchErr e r -> MatchErr e r)
-> (MatchErr e r -> MatchErr e r -> MatchErr e r)
-> Ord (MatchErr e r)
MatchErr e r -> MatchErr e r -> Bool
MatchErr e r -> MatchErr e r -> Ordering
MatchErr e r -> MatchErr e r -> MatchErr e r
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
forall e r. (Ord r, Ord e) => Eq (MatchErr e r)
forall e r. (Ord r, Ord e) => MatchErr e r -> MatchErr e r -> Bool
forall e r.
(Ord r, Ord e) =>
MatchErr e r -> MatchErr e r -> Ordering
forall e r.
(Ord r, Ord e) =>
MatchErr e r -> MatchErr e r -> MatchErr e r
$ccompare :: forall e r.
(Ord r, Ord e) =>
MatchErr e r -> MatchErr e r -> Ordering
compare :: MatchErr e r -> MatchErr e r -> Ordering
$c< :: forall e r. (Ord r, Ord e) => MatchErr e r -> MatchErr e r -> Bool
< :: MatchErr e r -> MatchErr e r -> Bool
$c<= :: forall e r. (Ord r, Ord e) => MatchErr e r -> MatchErr e r -> Bool
<= :: MatchErr e r -> MatchErr e r -> Bool
$c> :: forall e r. (Ord r, Ord e) => MatchErr e r -> MatchErr e r -> Bool
> :: MatchErr e r -> MatchErr e r -> Bool
$c>= :: forall e r. (Ord r, Ord e) => MatchErr e r -> MatchErr e r -> Bool
>= :: MatchErr e r -> MatchErr e r -> Bool
$cmax :: forall e r.
(Ord r, Ord e) =>
MatchErr e r -> MatchErr e r -> MatchErr e r
max :: MatchErr e r -> MatchErr e r -> MatchErr e r
$cmin :: forall e r.
(Ord r, Ord e) =>
MatchErr e r -> MatchErr e r -> MatchErr e r
min :: MatchErr e r -> MatchErr e r -> MatchErr e r
Ord, Int -> MatchErr e r -> ShowS
[MatchErr e r] -> ShowS
MatchErr e r -> String
(Int -> MatchErr e r -> ShowS)
-> (MatchErr e r -> String)
-> ([MatchErr e r] -> ShowS)
-> Show (MatchErr e r)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall e r. (Show r, Show e) => Int -> MatchErr e r -> ShowS
forall e r. (Show r, Show e) => [MatchErr e r] -> ShowS
forall e r. (Show r, Show e) => MatchErr e r -> String
$cshowsPrec :: forall e r. (Show r, Show e) => Int -> MatchErr e r -> ShowS
showsPrec :: Int -> MatchErr e r -> ShowS
$cshow :: forall e r. (Show r, Show e) => MatchErr e r -> String
show :: MatchErr e r -> String
$cshowList :: forall e r. (Show r, Show e) => [MatchErr e r] -> ShowS
showList :: [MatchErr e r] -> ShowS
Show)
instance (Typeable e, Show e, Typeable r, Show r) => Exception (MatchErr e r)
newtype LocMatchErr e k = LocMatchErr
{ forall e k.
LocMatchErr e k -> Anno k (MatchErr e (LocMatchErr e k))
unLocMatchErr :: Anno k (MatchErr e (LocMatchErr e k))
}
deriving stock (Int -> LocMatchErr e k -> ShowS
[LocMatchErr e k] -> ShowS
LocMatchErr e k -> String
(Int -> LocMatchErr e k -> ShowS)
-> (LocMatchErr e k -> String)
-> ([LocMatchErr e k] -> ShowS)
-> Show (LocMatchErr e k)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall e k. (Show k, Show e) => Int -> LocMatchErr e k -> ShowS
forall e k. (Show k, Show e) => [LocMatchErr e k] -> ShowS
forall e k. (Show k, Show e) => LocMatchErr e k -> String
$cshowsPrec :: forall e k. (Show k, Show e) => Int -> LocMatchErr e k -> ShowS
showsPrec :: Int -> LocMatchErr e k -> ShowS
$cshow :: forall e k. (Show k, Show e) => LocMatchErr e k -> String
show :: LocMatchErr e k -> String
$cshowList :: forall e k. (Show k, Show e) => [LocMatchErr e k] -> ShowS
showList :: [LocMatchErr e k] -> ShowS
Show)
deriving newtype (LocMatchErr e k -> LocMatchErr e k -> Bool
(LocMatchErr e k -> LocMatchErr e k -> Bool)
-> (LocMatchErr e k -> LocMatchErr e k -> Bool)
-> Eq (LocMatchErr e k)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall e k.
(Eq k, Eq e) =>
LocMatchErr e k -> LocMatchErr e k -> Bool
$c== :: forall e k.
(Eq k, Eq e) =>
LocMatchErr e k -> LocMatchErr e k -> Bool
== :: LocMatchErr e k -> LocMatchErr e k -> Bool
$c/= :: forall e k.
(Eq k, Eq e) =>
LocMatchErr e k -> LocMatchErr e k -> Bool
/= :: LocMatchErr e k -> LocMatchErr e k -> Bool
Eq, Eq (LocMatchErr e k)
Eq (LocMatchErr e k) =>
(LocMatchErr e k -> LocMatchErr e k -> Ordering)
-> (LocMatchErr e k -> LocMatchErr e k -> Bool)
-> (LocMatchErr e k -> LocMatchErr e k -> Bool)
-> (LocMatchErr e k -> LocMatchErr e k -> Bool)
-> (LocMatchErr e k -> LocMatchErr e k -> Bool)
-> (LocMatchErr e k -> LocMatchErr e k -> LocMatchErr e k)
-> (LocMatchErr e k -> LocMatchErr e k -> LocMatchErr e k)
-> Ord (LocMatchErr e k)
LocMatchErr e k -> LocMatchErr e k -> Bool
LocMatchErr e k -> LocMatchErr e k -> Ordering
LocMatchErr e k -> LocMatchErr e k -> LocMatchErr e k
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
forall e k. (Ord k, Ord e) => Eq (LocMatchErr e k)
forall e k.
(Ord k, Ord e) =>
LocMatchErr e k -> LocMatchErr e k -> Bool
forall e k.
(Ord k, Ord e) =>
LocMatchErr e k -> LocMatchErr e k -> Ordering
forall e k.
(Ord k, Ord e) =>
LocMatchErr e k -> LocMatchErr e k -> LocMatchErr e k
$ccompare :: forall e k.
(Ord k, Ord e) =>
LocMatchErr e k -> LocMatchErr e k -> Ordering
compare :: LocMatchErr e k -> LocMatchErr e k -> Ordering
$c< :: forall e k.
(Ord k, Ord e) =>
LocMatchErr e k -> LocMatchErr e k -> Bool
< :: LocMatchErr e k -> LocMatchErr e k -> Bool
$c<= :: forall e k.
(Ord k, Ord e) =>
LocMatchErr e k -> LocMatchErr e k -> Bool
<= :: LocMatchErr e k -> LocMatchErr e k -> Bool
$c> :: forall e k.
(Ord k, Ord e) =>
LocMatchErr e k -> LocMatchErr e k -> Bool
> :: LocMatchErr e k -> LocMatchErr e k -> Bool
$c>= :: forall e k.
(Ord k, Ord e) =>
LocMatchErr e k -> LocMatchErr e k -> Bool
>= :: LocMatchErr e k -> LocMatchErr e k -> Bool
$cmax :: forall e k.
(Ord k, Ord e) =>
LocMatchErr e k -> LocMatchErr e k -> LocMatchErr e k
max :: LocMatchErr e k -> LocMatchErr e k -> LocMatchErr e k
$cmin :: forall e k.
(Ord k, Ord e) =>
LocMatchErr e k -> LocMatchErr e k -> LocMatchErr e k
min :: LocMatchErr e k -> LocMatchErr e k -> LocMatchErr e k
Ord)
instance (Typeable e, Show e, Typeable k, Show k) => Exception (LocMatchErr e k)
newtype MatchT e k m a = MatchT {forall e k (m :: * -> *) a.
MatchT e k m a
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
unMatchT :: ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a}
deriving newtype ((forall a b. (a -> b) -> MatchT e k m a -> MatchT e k m b)
-> (forall a b. a -> MatchT e k m b -> MatchT e k m a)
-> Functor (MatchT e k m)
forall a b. a -> MatchT e k m b -> MatchT e k m a
forall a b. (a -> b) -> MatchT e k m a -> MatchT e k m b
forall e k (m :: * -> *) a b.
Functor m =>
a -> MatchT e k m b -> MatchT e k m a
forall e k (m :: * -> *) a b.
Functor m =>
(a -> b) -> MatchT e k m a -> MatchT e k m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall e k (m :: * -> *) a b.
Functor m =>
(a -> b) -> MatchT e k m a -> MatchT e k m b
fmap :: forall a b. (a -> b) -> MatchT e k m a -> MatchT e k m b
$c<$ :: forall e k (m :: * -> *) a b.
Functor m =>
a -> MatchT e k m b -> MatchT e k m a
<$ :: forall a b. a -> MatchT e k m b -> MatchT e k m a
Functor, Functor (MatchT e k m)
Functor (MatchT e k m) =>
(forall a. a -> MatchT e k m a)
-> (forall a b.
MatchT e k m (a -> b) -> MatchT e k m a -> MatchT e k m b)
-> (forall a b c.
(a -> b -> c)
-> MatchT e k m a -> MatchT e k m b -> MatchT e k m c)
-> (forall a b. MatchT e k m a -> MatchT e k m b -> MatchT e k m b)
-> (forall a b. MatchT e k m a -> MatchT e k m b -> MatchT e k m a)
-> Applicative (MatchT e k m)
forall a. a -> MatchT e k m a
forall a b. MatchT e k m a -> MatchT e k m b -> MatchT e k m a
forall a b. MatchT e k m a -> MatchT e k m b -> MatchT e k m b
forall a b.
MatchT e k m (a -> b) -> MatchT e k m a -> MatchT e k m b
forall a b c.
(a -> b -> c) -> MatchT e k m a -> MatchT e k m b -> MatchT e k m c
forall e k (m :: * -> *). Monad m => Functor (MatchT e k m)
forall e k (m :: * -> *) a. Monad m => a -> MatchT e k m a
forall e k (m :: * -> *) a b.
Monad m =>
MatchT e k m a -> MatchT e k m b -> MatchT e k m a
forall e k (m :: * -> *) a b.
Monad m =>
MatchT e k m a -> MatchT e k m b -> MatchT e k m b
forall e k (m :: * -> *) a b.
Monad m =>
MatchT e k m (a -> b) -> MatchT e k m a -> MatchT e k m b
forall e k (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> MatchT e k m a -> MatchT e k m b -> MatchT e k m c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
$cpure :: forall e k (m :: * -> *) a. Monad m => a -> MatchT e k m a
pure :: forall a. a -> MatchT e k m a
$c<*> :: forall e k (m :: * -> *) a b.
Monad m =>
MatchT e k m (a -> b) -> MatchT e k m a -> MatchT e k m b
<*> :: forall a b.
MatchT e k m (a -> b) -> MatchT e k m a -> MatchT e k m b
$cliftA2 :: forall e k (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> MatchT e k m a -> MatchT e k m b -> MatchT e k m c
liftA2 :: forall a b c.
(a -> b -> c) -> MatchT e k m a -> MatchT e k m b -> MatchT e k m c
$c*> :: forall e k (m :: * -> *) a b.
Monad m =>
MatchT e k m a -> MatchT e k m b -> MatchT e k m b
*> :: forall a b. MatchT e k m a -> MatchT e k m b -> MatchT e k m b
$c<* :: forall e k (m :: * -> *) a b.
Monad m =>
MatchT e k m a -> MatchT e k m b -> MatchT e k m a
<* :: forall a b. MatchT e k m a -> MatchT e k m b -> MatchT e k m a
Applicative, Applicative (MatchT e k m)
Applicative (MatchT e k m) =>
(forall a b.
MatchT e k m a -> (a -> MatchT e k m b) -> MatchT e k m b)
-> (forall a b. MatchT e k m a -> MatchT e k m b -> MatchT e k m b)
-> (forall a. a -> MatchT e k m a)
-> Monad (MatchT e k m)
forall a. a -> MatchT e k m a
forall a b. MatchT e k m a -> MatchT e k m b -> MatchT e k m b
forall a b.
MatchT e k m a -> (a -> MatchT e k m b) -> MatchT e k m b
forall e k (m :: * -> *). Monad m => Applicative (MatchT e k m)
forall e k (m :: * -> *) a. Monad m => a -> MatchT e k m a
forall e k (m :: * -> *) a b.
Monad m =>
MatchT e k m a -> MatchT e k m b -> MatchT e k m b
forall e k (m :: * -> *) a b.
Monad m =>
MatchT e k m a -> (a -> MatchT e k m b) -> MatchT e k m b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
$c>>= :: forall e k (m :: * -> *) a b.
Monad m =>
MatchT e k m a -> (a -> MatchT e k m b) -> MatchT e k m b
>>= :: forall a b.
MatchT e k m a -> (a -> MatchT e k m b) -> MatchT e k m b
$c>> :: forall e k (m :: * -> *) a b.
Monad m =>
MatchT e k m a -> MatchT e k m b -> MatchT e k m b
>> :: forall a b. MatchT e k m a -> MatchT e k m b -> MatchT e k m b
$creturn :: forall e k (m :: * -> *) a. Monad m => a -> MatchT e k m a
return :: forall a. a -> MatchT e k m a
Monad)
type MatchM e k = MatchT e k Identity
instance MonadTrans (MatchT e k) where
lift :: forall (m :: * -> *) a. Monad m => m a -> MatchT e k m a
lift = ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT (ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a)
-> (m a -> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a)
-> m a
-> MatchT e k m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExceptT (LocMatchErr e k) m a
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall (m :: * -> *) a.
Monad m =>
m a -> ReaderT (Memo SexpF k) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ExceptT (LocMatchErr e k) m a
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a)
-> (m a -> ExceptT (LocMatchErr e k) m a)
-> m a
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> ExceptT (LocMatchErr e k) m a
forall (m :: * -> *) a.
Monad m =>
m a -> ExceptT (LocMatchErr e k) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift
unlift :: (Monad m) => (Memo SexpF k -> m (Either (LocMatchErr e k) a)) -> MatchT e k m a
unlift :: forall (m :: * -> *) k e a.
Monad m =>
(Memo SexpF k -> m (Either (LocMatchErr e k) a)) -> MatchT e k m a
unlift Memo SexpF k -> m (Either (LocMatchErr e k) a)
f = ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT (ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a)
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
forall a b. (a -> b) -> a -> b
$ do
Memo SexpF k
s <- ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) (Memo SexpF k)
forall r (m :: * -> *). MonadReader r m => m r
ask
Either (LocMatchErr e k) a
ea <- ExceptT (LocMatchErr e k) m (Either (LocMatchErr e k) a)
-> ReaderT
(Memo SexpF k)
(ExceptT (LocMatchErr e k) m)
(Either (LocMatchErr e k) a)
forall (m :: * -> *) a.
Monad m =>
m a -> ReaderT (Memo SexpF k) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Either (LocMatchErr e k) a)
-> ExceptT (LocMatchErr e k) m (Either (LocMatchErr e k) a)
forall (m :: * -> *) a.
Monad m =>
m a -> ExceptT (LocMatchErr e k) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Memo SexpF k -> m (Either (LocMatchErr e k) a)
f Memo SexpF k
s))
(LocMatchErr e k
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a)
-> (a -> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a)
-> Either (LocMatchErr e k) a
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either LocMatchErr e k
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall a.
LocMatchErr e k
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError a -> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall a.
a -> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Either (LocMatchErr e k) a
ea
instance (MonadReader r m) => MonadReader r (MatchT e k m) where
ask :: MatchT e k m r
ask = m r -> MatchT e k m r
forall (m :: * -> *) a. Monad m => m a -> MatchT e k m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m r
forall r (m :: * -> *). MonadReader r m => m r
ask
local :: forall a. (r -> r) -> MatchT e k m a -> MatchT e k m a
local r -> r
f MatchT e k m a
m = (Memo SexpF k -> m (Either (LocMatchErr e k) a)) -> MatchT e k m a
forall (m :: * -> *) k e a.
Monad m =>
(Memo SexpF k -> m (Either (LocMatchErr e k) a)) -> MatchT e k m a
unlift ((r -> r)
-> m (Either (LocMatchErr e k) a) -> m (Either (LocMatchErr e k) a)
forall a. (r -> r) -> m a -> m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local r -> r
f (m (Either (LocMatchErr e k) a) -> m (Either (LocMatchErr e k) a))
-> (Memo SexpF k -> m (Either (LocMatchErr e k) a))
-> Memo SexpF k
-> m (Either (LocMatchErr e k) a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
forall e k (m :: * -> *) a.
MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
runMatchT MatchT e k m a
m)
instance (MonadState s m) => MonadState s (MatchT e k m) where
get :: MatchT e k m s
get = m s -> MatchT e k m s
forall (m :: * -> *) a. Monad m => m a -> MatchT e k m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m s
forall s (m :: * -> *). MonadState s m => m s
get
put :: s -> MatchT e k m ()
put = m () -> MatchT e k m ()
forall (m :: * -> *) a. Monad m => m a -> MatchT e k m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> MatchT e k m ()) -> (s -> m ()) -> s -> MatchT e k m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> m ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put
state :: forall a. (s -> (a, s)) -> MatchT e k m a
state = m a -> MatchT e k m a
forall (m :: * -> *) a. Monad m => m a -> MatchT e k m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> MatchT e k m a)
-> ((s -> (a, s)) -> m a) -> (s -> (a, s)) -> MatchT e k m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (s -> (a, s)) -> m a
forall a. (s -> (a, s)) -> m a
forall s (m :: * -> *) a. MonadState s m => (s -> (a, s)) -> m a
state
instance (MonadError x m) => MonadError x (MatchT e k m) where
throwError :: forall a. x -> MatchT e k m a
throwError = m a -> MatchT e k m a
forall (m :: * -> *) a. Monad m => m a -> MatchT e k m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> MatchT e k m a) -> (x -> m a) -> x -> MatchT e k m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. x -> m a
forall a. x -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError
catchError :: forall a. MatchT e k m a -> (x -> MatchT e k m a) -> MatchT e k m a
catchError MatchT e k m a
m x -> MatchT e k m a
f = (Memo SexpF k -> m (Either (LocMatchErr e k) a)) -> MatchT e k m a
forall (m :: * -> *) k e a.
Monad m =>
(Memo SexpF k -> m (Either (LocMatchErr e k) a)) -> MatchT e k m a
unlift (\Memo SexpF k
s -> m (Either (LocMatchErr e k) a)
-> (x -> m (Either (LocMatchErr e k) a))
-> m (Either (LocMatchErr e k) a)
forall a. m a -> (x -> m a) -> m a
forall e (m :: * -> *) a.
MonadError e m =>
m a -> (e -> m a) -> m a
catchError (MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
forall e k (m :: * -> *) a.
MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
runMatchT MatchT e k m a
m Memo SexpF k
s) ((MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a))
-> Memo SexpF k -> MatchT e k m a -> m (Either (LocMatchErr e k) a)
forall a b c. (a -> b -> c) -> b -> a -> c
flip MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
forall e k (m :: * -> *) a.
MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
runMatchT Memo SexpF k
s (MatchT e k m a -> m (Either (LocMatchErr e k) a))
-> (x -> MatchT e k m a) -> x -> m (Either (LocMatchErr e k) a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. x -> MatchT e k m a
f))
runMatchT :: MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
runMatchT :: forall e k (m :: * -> *) a.
MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
runMatchT MatchT e k m a
m Memo SexpF k
r = ExceptT (LocMatchErr e k) m a -> m (Either (LocMatchErr e k) a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> Memo SexpF k -> ExceptT (LocMatchErr e k) m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (MatchT e k m a
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall e k (m :: * -> *) a.
MatchT e k m a
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
unMatchT MatchT e k m a
m) Memo SexpF k
r)
runMatchM :: MatchM e k a -> Memo SexpF k -> Either (LocMatchErr e k) a
runMatchM :: forall e k a.
MatchM e k a -> Memo SexpF k -> Either (LocMatchErr e k) a
runMatchM MatchM e k a
m Memo SexpF k
r = Identity (Either (LocMatchErr e k) a) -> Either (LocMatchErr e k) a
forall a. Identity a -> a
runIdentity (MatchM e k a
-> Memo SexpF k -> Identity (Either (LocMatchErr e k) a)
forall e k (m :: * -> *) a.
MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
runMatchT MatchM e k a
m Memo SexpF k
r)
data SeqMatchT e k m a where
SeqMatchPure :: a -> SeqMatchT e k m a
SeqMatchEmbed :: MatchT e k m (SeqMatchT e k m a) -> SeqMatchT e k m a
SeqMatchElem :: MatchT e k m x -> (x -> SeqMatchT e k m a) -> SeqMatchT e k m a
SeqMatchRepeat :: SeqMatchT e k m x -> (Seq x -> SeqMatchT e k m a) -> SeqMatchT e k m a
SeqMatchRemaining :: (Int -> SeqMatchT e k m a) -> SeqMatchT e k m a
type SeqMatchM e k = SeqMatchT e k Identity
instance (Functor m) => Functor (SeqMatchT e k m) where
fmap :: forall a b. (a -> b) -> SeqMatchT e k m a -> SeqMatchT e k m b
fmap a -> b
f = SeqMatchT e k m a -> SeqMatchT e k m b
go
where
go :: SeqMatchT e k m a -> SeqMatchT e k m b
go = \case
SeqMatchPure a
a -> b -> SeqMatchT e k m b
forall a e k (m :: * -> *). a -> SeqMatchT e k m a
SeqMatchPure (a -> b
f a
a)
SeqMatchEmbed MatchT e k m (SeqMatchT e k m a)
mr -> MatchT e k m (SeqMatchT e k m b) -> SeqMatchT e k m b
forall e k (m :: * -> *) a.
MatchT e k m (SeqMatchT e k m a) -> SeqMatchT e k m a
SeqMatchEmbed ((SeqMatchT e k m a -> SeqMatchT e k m b)
-> MatchT e k m (SeqMatchT e k m a)
-> MatchT e k m (SeqMatchT e k m b)
forall a b. (a -> b) -> MatchT e k m a -> MatchT e k m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SeqMatchT e k m a -> SeqMatchT e k m b
go MatchT e k m (SeqMatchT e k m a)
mr)
SeqMatchElem MatchT e k m x
mx x -> SeqMatchT e k m a
k -> MatchT e k m x -> (x -> SeqMatchT e k m b) -> SeqMatchT e k m b
forall e k (m :: * -> *) x a.
MatchT e k m x -> (x -> SeqMatchT e k m a) -> SeqMatchT e k m a
SeqMatchElem MatchT e k m x
mx (SeqMatchT e k m a -> SeqMatchT e k m b
go (SeqMatchT e k m a -> SeqMatchT e k m b)
-> (x -> SeqMatchT e k m a) -> x -> SeqMatchT e k m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. x -> SeqMatchT e k m a
k)
SeqMatchRepeat SeqMatchT e k m x
mx Seq x -> SeqMatchT e k m a
k -> SeqMatchT e k m x
-> (Seq x -> SeqMatchT e k m b) -> SeqMatchT e k m b
forall e k (m :: * -> *) x a.
SeqMatchT e k m x
-> (Seq x -> SeqMatchT e k m a) -> SeqMatchT e k m a
SeqMatchRepeat SeqMatchT e k m x
mx (SeqMatchT e k m a -> SeqMatchT e k m b
go (SeqMatchT e k m a -> SeqMatchT e k m b)
-> (Seq x -> SeqMatchT e k m a) -> Seq x -> SeqMatchT e k m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seq x -> SeqMatchT e k m a
k)
SeqMatchRemaining Int -> SeqMatchT e k m a
k -> (Int -> SeqMatchT e k m b) -> SeqMatchT e k m b
forall e k (m :: * -> *) a.
(Int -> SeqMatchT e k m a) -> SeqMatchT e k m a
SeqMatchRemaining (SeqMatchT e k m a -> SeqMatchT e k m b
go (SeqMatchT e k m a -> SeqMatchT e k m b)
-> (Int -> SeqMatchT e k m a) -> Int -> SeqMatchT e k m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> SeqMatchT e k m a
k)
instance (Monad m) => Applicative (SeqMatchT e k m) where
pure :: forall a. a -> SeqMatchT e k m a
pure = a -> SeqMatchT e k m a
forall a e k (m :: * -> *). a -> SeqMatchT e k m a
SeqMatchPure
<*> :: forall a b.
SeqMatchT e k m (a -> b) -> SeqMatchT e k m a -> SeqMatchT e k m b
(<*>) = SeqMatchT e k m (a -> b) -> SeqMatchT e k m a -> SeqMatchT e k m b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap
instance (Monad m) => Monad (SeqMatchT e k m) where
return :: forall a. a -> SeqMatchT e k m a
return = a -> SeqMatchT e k m a
forall a. a -> SeqMatchT e k m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
SeqMatchT e k m a
r0 >>= :: forall a b.
SeqMatchT e k m a -> (a -> SeqMatchT e k m b) -> SeqMatchT e k m b
>>= a -> SeqMatchT e k m b
f = SeqMatchT e k m a -> SeqMatchT e k m b
go SeqMatchT e k m a
r0
where
go :: SeqMatchT e k m a -> SeqMatchT e k m b
go = \case
SeqMatchPure a
a -> a -> SeqMatchT e k m b
f a
a
SeqMatchEmbed MatchT e k m (SeqMatchT e k m a)
mr -> MatchT e k m (SeqMatchT e k m b) -> SeqMatchT e k m b
forall e k (m :: * -> *) a.
MatchT e k m (SeqMatchT e k m a) -> SeqMatchT e k m a
SeqMatchEmbed ((SeqMatchT e k m a -> SeqMatchT e k m b)
-> MatchT e k m (SeqMatchT e k m a)
-> MatchT e k m (SeqMatchT e k m b)
forall a b. (a -> b) -> MatchT e k m a -> MatchT e k m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SeqMatchT e k m a -> SeqMatchT e k m b
go MatchT e k m (SeqMatchT e k m a)
mr)
SeqMatchElem MatchT e k m x
mx x -> SeqMatchT e k m a
k -> MatchT e k m x -> (x -> SeqMatchT e k m b) -> SeqMatchT e k m b
forall e k (m :: * -> *) x a.
MatchT e k m x -> (x -> SeqMatchT e k m a) -> SeqMatchT e k m a
SeqMatchElem MatchT e k m x
mx (SeqMatchT e k m a -> SeqMatchT e k m b
go (SeqMatchT e k m a -> SeqMatchT e k m b)
-> (x -> SeqMatchT e k m a) -> x -> SeqMatchT e k m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. x -> SeqMatchT e k m a
k)
SeqMatchRepeat SeqMatchT e k m x
mx Seq x -> SeqMatchT e k m a
k -> SeqMatchT e k m x
-> (Seq x -> SeqMatchT e k m b) -> SeqMatchT e k m b
forall e k (m :: * -> *) x a.
SeqMatchT e k m x
-> (Seq x -> SeqMatchT e k m a) -> SeqMatchT e k m a
SeqMatchRepeat SeqMatchT e k m x
mx (SeqMatchT e k m a -> SeqMatchT e k m b
go (SeqMatchT e k m a -> SeqMatchT e k m b)
-> (Seq x -> SeqMatchT e k m a) -> Seq x -> SeqMatchT e k m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seq x -> SeqMatchT e k m a
k)
SeqMatchRemaining Int -> SeqMatchT e k m a
k -> (Int -> SeqMatchT e k m b) -> SeqMatchT e k m b
forall e k (m :: * -> *) a.
(Int -> SeqMatchT e k m a) -> SeqMatchT e k m a
SeqMatchRemaining (SeqMatchT e k m a -> SeqMatchT e k m b
go (SeqMatchT e k m a -> SeqMatchT e k m b)
-> (Int -> SeqMatchT e k m a) -> Int -> SeqMatchT e k m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> SeqMatchT e k m a
k)
annoM :: (Monad m) => MatchT e k m a -> MatchT e k m (Anno k a)
annoM :: forall (m :: * -> *) e k a.
Monad m =>
MatchT e k m a -> MatchT e k m (Anno k a)
annoM MatchT e k m a
m = ReaderT
(Memo SexpF k) (ExceptT (LocMatchErr e k) m) (a -> Anno k a)
-> MatchT e k m (a -> Anno k a)
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT ((Memo SexpF k -> a -> Anno k a)
-> ReaderT
(Memo SexpF k) (ExceptT (LocMatchErr e k) m) (a -> Anno k a)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (k -> a -> Anno k a
forall k v. k -> v -> Anno k v
Anno (k -> a -> Anno k a)
-> (Memo SexpF k -> k) -> Memo SexpF k -> a -> Anno k a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Memo SexpF k -> k
forall (f :: * -> *) k. Memo f k -> k
B.memoKey)) MatchT e k m (a -> Anno k a)
-> MatchT e k m a -> MatchT e k m (Anno k a)
forall a b.
MatchT e k m (a -> b) -> MatchT e k m a -> MatchT e k m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MatchT e k m a
m
memoM :: (Monad m) => MatchT e k m (f (Memo f k)) -> MatchT e k m (Memo f k)
memoM :: forall (m :: * -> *) e k (f :: * -> *).
Monad m =>
MatchT e k m (f (Memo f k)) -> MatchT e k m (Memo f k)
memoM MatchT e k m (f (Memo f k))
m = ReaderT
(Memo SexpF k)
(ExceptT (LocMatchErr e k) m)
(f (Memo f k) -> Memo f k)
-> MatchT e k m (f (Memo f k) -> Memo f k)
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT ((Memo SexpF k -> f (Memo f k) -> Memo f k)
-> ReaderT
(Memo SexpF k)
(ExceptT (LocMatchErr e k) m)
(f (Memo f k) -> Memo f k)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (k -> f (Memo f k) -> Memo f k
forall k (f :: * -> *). k -> f (Memo f k) -> Memo f k
MemoP (k -> f (Memo f k) -> Memo f k)
-> (Memo SexpF k -> k) -> Memo SexpF k -> f (Memo f k) -> Memo f k
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Memo SexpF k -> k
forall (f :: * -> *) k. Memo f k -> k
B.memoKey)) MatchT e k m (f (Memo f k) -> Memo f k)
-> MatchT e k m (f (Memo f k)) -> MatchT e k m (Memo f k)
forall a b.
MatchT e k m (a -> b) -> MatchT e k m a -> MatchT e k m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MatchT e k m (f (Memo f k))
m
errM :: (Monad m) => MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM :: forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM MatchErr e (LocMatchErr e k)
e = do
Memo SexpF k
s <- ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) (Memo SexpF k)
-> MatchT e k m (Memo SexpF k)
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) (Memo SexpF k)
forall r (m :: * -> *). MonadReader r m => m r
ask
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT (LocMatchErr e k
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall a.
LocMatchErr e k
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Anno k (MatchErr e (LocMatchErr e k)) -> LocMatchErr e k
forall e k.
Anno k (MatchErr e (LocMatchErr e k)) -> LocMatchErr e k
LocMatchErr (k
-> MatchErr e (LocMatchErr e k)
-> Anno k (MatchErr e (LocMatchErr e k))
forall k v. k -> v -> Anno k v
Anno (Memo SexpF k -> k
forall (f :: * -> *) k. Memo f k -> k
B.memoKey Memo SexpF k
s) MatchErr e (LocMatchErr e k)
e)))
embedM :: (Monad m) => e -> MatchT e k m a
embedM :: forall (m :: * -> *) e k a. Monad m => e -> MatchT e k m a
embedM = MatchErr e (LocMatchErr e k) -> MatchT e k m a
forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM (MatchErr e (LocMatchErr e k) -> MatchT e k m a)
-> (e -> MatchErr e (LocMatchErr e k)) -> e -> MatchT e k m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> MatchErr e (LocMatchErr e k)
forall e r. e -> MatchErr e r
MatchErrEmbed
matchM :: (Monad m) => (SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a) -> MatchT e k m a
matchM :: forall (m :: * -> *) k e a.
Monad m =>
(SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a)
-> MatchT e k m a
matchM SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a
f = do
Memo SexpF k
s <- ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) (Memo SexpF k)
-> MatchT e k m (Memo SexpF k)
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) (Memo SexpF k)
forall r (m :: * -> *). MonadReader r m => m r
ask
case SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a
f (Memo SexpF k -> SexpF (Memo SexpF k)
forall (f :: * -> *) k. Memo f k -> f (Memo f k)
B.memoVal Memo SexpF k
s) of
Left MatchErr e (LocMatchErr e k)
e -> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT (LocMatchErr e k
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall a.
LocMatchErr e k
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Anno k (MatchErr e (LocMatchErr e k)) -> LocMatchErr e k
forall e k.
Anno k (MatchErr e (LocMatchErr e k)) -> LocMatchErr e k
LocMatchErr (k
-> MatchErr e (LocMatchErr e k)
-> Anno k (MatchErr e (LocMatchErr e k))
forall k v. k -> v -> Anno k v
Anno (Memo SexpF k -> k
forall (f :: * -> *) k. Memo f k -> k
B.memoKey Memo SexpF k
s) MatchErr e (LocMatchErr e k)
e)))
Right a
a -> a -> MatchT e k m a
forall a. a -> MatchT e k m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
data S k = S !Int !(Seq (Memo SexpF k))
deriving stock (S k -> S k -> Bool
(S k -> S k -> Bool) -> (S k -> S k -> Bool) -> Eq (S k)
forall k. Eq k => S k -> S k -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall k. Eq k => S k -> S k -> Bool
== :: S k -> S k -> Bool
$c/= :: forall k. Eq k => S k -> S k -> Bool
/= :: S k -> S k -> Bool
Eq, Eq (S k)
Eq (S k) =>
(S k -> S k -> Ordering)
-> (S k -> S k -> Bool)
-> (S k -> S k -> Bool)
-> (S k -> S k -> Bool)
-> (S k -> S k -> Bool)
-> (S k -> S k -> S k)
-> (S k -> S k -> S k)
-> Ord (S k)
S k -> S k -> Bool
S k -> S k -> Ordering
S k -> S k -> S k
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
forall k. Ord k => Eq (S k)
forall k. Ord k => S k -> S k -> Bool
forall k. Ord k => S k -> S k -> Ordering
forall k. Ord k => S k -> S k -> S k
$ccompare :: forall k. Ord k => S k -> S k -> Ordering
compare :: S k -> S k -> Ordering
$c< :: forall k. Ord k => S k -> S k -> Bool
< :: S k -> S k -> Bool
$c<= :: forall k. Ord k => S k -> S k -> Bool
<= :: S k -> S k -> Bool
$c> :: forall k. Ord k => S k -> S k -> Bool
> :: S k -> S k -> Bool
$c>= :: forall k. Ord k => S k -> S k -> Bool
>= :: S k -> S k -> Bool
$cmax :: forall k. Ord k => S k -> S k -> S k
max :: S k -> S k -> S k
$cmin :: forall k. Ord k => S k -> S k -> S k
min :: S k -> S k -> S k
Ord, Int -> S k -> ShowS
[S k] -> ShowS
S k -> String
(Int -> S k -> ShowS)
-> (S k -> String) -> ([S k] -> ShowS) -> Show (S k)
forall k. Show k => Int -> S k -> ShowS
forall k. Show k => [S k] -> ShowS
forall k. Show k => S k -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall k. Show k => Int -> S k -> ShowS
showsPrec :: Int -> S k -> ShowS
$cshow :: forall k. Show k => S k -> String
show :: S k -> String
$cshowList :: forall k. Show k => [S k] -> ShowS
showList :: [S k] -> ShowS
Show)
listM :: (Monad m) => Brace -> SeqMatchT e k m a -> MatchT e k m a
listM :: forall (m :: * -> *) e k a.
Monad m =>
Brace -> SeqMatchT e k m a -> MatchT e k m a
listM = Int -> Brace -> SeqMatchT e k m a -> MatchT e k m a
forall (m :: * -> *) e k a.
Monad m =>
Int -> Brace -> SeqMatchT e k m a -> MatchT e k m a
listFromM Int
0
goSeqX :: (Monad m) => SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a
goSeqX :: forall (m :: * -> *) e k a.
Monad m =>
SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a
goSeqX = \case
SeqMatchPure a
a -> a -> StateT (S k) (MatchT e k m) a
forall a. a -> StateT (S k) (MatchT e k m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
SeqMatchEmbed MatchT e k m (SeqMatchT e k m a)
mr -> MatchT e k m (SeqMatchT e k m a)
-> StateT (S k) (MatchT e k m) (SeqMatchT e k m a)
forall (m :: * -> *) a. Monad m => m a -> StateT (S k) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift MatchT e k m (SeqMatchT e k m a)
mr StateT (S k) (MatchT e k m) (SeqMatchT e k m a)
-> (SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a)
-> StateT (S k) (MatchT e k m) a
forall a b.
StateT (S k) (MatchT e k m) a
-> (a -> StateT (S k) (MatchT e k m) b)
-> StateT (S k) (MatchT e k m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a
forall (m :: * -> *) e k a.
Monad m =>
SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a
goSeqX
SeqMatchElem MatchT e k m x
mx x -> SeqMatchT e k m a
k -> do
S Int
i Seq (Memo SexpF k)
cs <- StateT (S k) (MatchT e k m) (S k)
forall s (m :: * -> *). MonadState s m => m s
get
let i' :: Int
i' = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
case Seq (Memo SexpF k)
cs of
Seq (Memo SexpF k)
Empty -> MatchT e k m a -> StateT (S k) (MatchT e k m) a
forall (m :: * -> *) a. Monad m => m a -> StateT (S k) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MatchErr e (LocMatchErr e k) -> MatchT e k m a
forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM (Int -> MatchErr e (LocMatchErr e k)
forall e r. Int -> MatchErr e r
MatchErrListElem Int
i'))
Memo SexpF k
c :<| Seq (Memo SexpF k)
cs' -> do
S k -> StateT (S k) (MatchT e k m) ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put (Int -> Seq (Memo SexpF k) -> S k
forall k. Int -> Seq (Memo SexpF k) -> S k
S Int
i' Seq (Memo SexpF k)
cs')
x
x <- MatchT e k m x -> StateT (S k) (MatchT e k m) x
forall (m :: * -> *) a. Monad m => m a -> StateT (S k) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) x
-> MatchT e k m x
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT ((Memo SexpF k -> Memo SexpF k)
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) x
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) x
forall a.
(Memo SexpF k -> Memo SexpF k)
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (Memo SexpF k -> Memo SexpF k -> Memo SexpF k
forall a b. a -> b -> a
const Memo SexpF k
c) (MatchT e k m x
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) x
forall e k (m :: * -> *) a.
MatchT e k m a
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
unMatchT MatchT e k m x
mx)))
SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a
forall (m :: * -> *) e k a.
Monad m =>
SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a
goSeqX (x -> SeqMatchT e k m a
k x
x)
SeqMatchRepeat SeqMatchT e k m x
mx Seq x -> SeqMatchT e k m a
k -> SeqMatchT e k m x
-> (Seq x -> SeqMatchT e k m a) -> StateT (S k) (MatchT e k m) a
forall (m :: * -> *) e k x a.
Monad m =>
SeqMatchT e k m x
-> (Seq x -> SeqMatchT e k m a) -> StateT (S k) (MatchT e k m) a
goRepeatX SeqMatchT e k m x
mx Seq x -> SeqMatchT e k m a
k
SeqMatchRemaining Int -> SeqMatchT e k m a
k -> do
S Int
_ Seq (Memo SexpF k)
cs <- StateT (S k) (MatchT e k m) (S k)
forall s (m :: * -> *). MonadState s m => m s
get
SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a
forall (m :: * -> *) e k a.
Monad m =>
SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a
goSeqX (Int -> SeqMatchT e k m a
k (Seq (Memo SexpF k) -> Int
forall a. Seq a -> Int
Seq.length Seq (Memo SexpF k)
cs))
goRepeatX :: (Monad m) => SeqMatchT e k m x -> (Seq x -> SeqMatchT e k m a) -> StateT (S k) (MatchT e k m) a
goRepeatX :: forall (m :: * -> *) e k x a.
Monad m =>
SeqMatchT e k m x
-> (Seq x -> SeqMatchT e k m a) -> StateT (S k) (MatchT e k m) a
goRepeatX SeqMatchT e k m x
mx Seq x -> SeqMatchT e k m a
k = Seq x -> StateT (S k) (MatchT e k m) a
go Seq x
forall a. Seq a
Empty
where
go :: Seq x -> StateT (S k) (MatchT e k m) a
go !Seq x
acc = do
S Int
_ Seq (Memo SexpF k)
cs <- StateT (S k) (MatchT e k m) (S k)
forall s (m :: * -> *). MonadState s m => m s
get
case Seq (Memo SexpF k)
cs of
Seq (Memo SexpF k)
Empty -> SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a
forall (m :: * -> *) e k a.
Monad m =>
SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a
goSeqX (Seq x -> SeqMatchT e k m a
k Seq x
acc)
Seq (Memo SexpF k)
_ -> do
x
x <- SeqMatchT e k m x -> StateT (S k) (MatchT e k m) x
forall (m :: * -> *) e k a.
Monad m =>
SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a
goSeqX SeqMatchT e k m x
mx
Seq x -> StateT (S k) (MatchT e k m) a
go (Seq x
acc Seq x -> x -> Seq x
forall a. Seq a -> a -> Seq a
:|> x
x)
listFromM :: (Monad m) => Int -> Brace -> SeqMatchT e k m a -> MatchT e k m a
listFromM :: forall (m :: * -> *) e k a.
Monad m =>
Int -> Brace -> SeqMatchT e k m a -> MatchT e k m a
listFromM Int
i0 Brace
b0 SeqMatchT e k m a
r = MatchT e k m a
goStart
where
goStart :: MatchT e k m a
goStart = do
Memo SexpF k
s <- ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) (Memo SexpF k)
-> MatchT e k m (Memo SexpF k)
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) (Memo SexpF k)
forall r (m :: * -> *). MonadReader r m => m r
ask
case Memo SexpF k -> SexpF (Memo SexpF k)
forall (f :: * -> *) k. Memo f k -> f (Memo f k)
B.memoVal Memo SexpF k
s of
SexpListF Brace
b Seq (Memo SexpF k)
cs0 | Brace
b Brace -> Brace -> Bool
forall a. Eq a => a -> a -> Bool
== Brace
b0 -> do
let s0 :: S k
s0 = Int -> Seq (Memo SexpF k) -> S k
forall k. Int -> Seq (Memo SexpF k) -> S k
S Int
i0 (Int -> Seq (Memo SexpF k) -> Seq (Memo SexpF k)
forall a. Int -> Seq a -> Seq a
Seq.drop Int
i0 Seq (Memo SexpF k)
cs0)
(a
a, S Int
_ Seq (Memo SexpF k)
cs1) <- StateT (S k) (MatchT e k m) a -> S k -> MatchT e k m (a, S k)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a
forall (m :: * -> *) e k a.
Monad m =>
SeqMatchT e k m a -> StateT (S k) (MatchT e k m) a
goSeqX SeqMatchT e k m a
r) S k
s0
case Seq (Memo SexpF k)
cs1 of
Seq (Memo SexpF k)
Empty -> a -> MatchT e k m a
forall a. a -> MatchT e k m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
Seq (Memo SexpF k)
_ -> MatchErr e (LocMatchErr e k) -> MatchT e k m a
forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM MatchErr e (LocMatchErr e k)
forall e r. MatchErr e r
MatchErrListRem
SexpF (Memo SexpF k)
_ -> MatchErr e (LocMatchErr e k) -> MatchT e k m a
forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM (SexpType -> MatchErr e (LocMatchErr e k)
forall e r. SexpType -> MatchErr e r
MatchErrType (Brace -> SexpType
SexpTypeList Brace
b0))
elemM :: MatchT e k m a -> SeqMatchT e k m a
elemM :: forall e k (m :: * -> *) a. MatchT e k m a -> SeqMatchT e k m a
elemM = (MatchT e k m a -> (a -> SeqMatchT e k m a) -> SeqMatchT e k m a
forall e k (m :: * -> *) x a.
MatchT e k m x -> (x -> SeqMatchT e k m a) -> SeqMatchT e k m a
`SeqMatchElem` a -> SeqMatchT e k m a
forall a e k (m :: * -> *). a -> SeqMatchT e k m a
SeqMatchPure)
restM :: MatchT e k m a -> SeqMatchT e k m (Seq a)
restM :: forall e k (m :: * -> *) a.
MatchT e k m a -> SeqMatchT e k m (Seq a)
restM = SeqMatchT e k m a -> SeqMatchT e k m (Seq a)
forall e k (m :: * -> *) a.
SeqMatchT e k m a -> SeqMatchT e k m (Seq a)
repeatM (SeqMatchT e k m a -> SeqMatchT e k m (Seq a))
-> (MatchT e k m a -> SeqMatchT e k m a)
-> MatchT e k m a
-> SeqMatchT e k m (Seq a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MatchT e k m a -> SeqMatchT e k m a
forall e k (m :: * -> *) a. MatchT e k m a -> SeqMatchT e k m a
elemM
repeatM :: SeqMatchT e k m a -> SeqMatchT e k m (Seq a)
repeatM :: forall e k (m :: * -> *) a.
SeqMatchT e k m a -> SeqMatchT e k m (Seq a)
repeatM = (SeqMatchT e k m a
-> (Seq a -> SeqMatchT e k m (Seq a)) -> SeqMatchT e k m (Seq a)
forall e k (m :: * -> *) x a.
SeqMatchT e k m x
-> (Seq x -> SeqMatchT e k m a) -> SeqMatchT e k m a
`SeqMatchRepeat` Seq a -> SeqMatchT e k m (Seq a)
forall a e k (m :: * -> *). a -> SeqMatchT e k m a
SeqMatchPure)
remainingM :: SeqMatchT e k m Int
remainingM :: forall e k (m :: * -> *). SeqMatchT e k m Int
remainingM = (Int -> SeqMatchT e k m Int) -> SeqMatchT e k m Int
forall e k (m :: * -> *) a.
(Int -> SeqMatchT e k m a) -> SeqMatchT e k m a
SeqMatchRemaining Int -> SeqMatchT e k m Int
forall a e k (m :: * -> *). a -> SeqMatchT e k m a
SeqMatchPure
altM :: (Monad m) => [(Text, MatchT e k m a)] -> MatchT e k m a
altM :: forall (m :: * -> *) e k a.
Monad m =>
[(Text, MatchT e k m a)] -> MatchT e k m a
altM = Seq (Text, LocMatchErr e k)
-> [(Text, MatchT e k m a)] -> MatchT e k m a
forall {m :: * -> *} {e} {k} {a}.
Monad m =>
Seq (Text, LocMatchErr e k)
-> [(Text, MatchT e k m a)] -> MatchT e k m a
go Seq (Text, LocMatchErr e k)
forall a. Seq a
Empty
where
go :: Seq (Text, LocMatchErr e k)
-> [(Text, MatchT e k m a)] -> MatchT e k m a
go !Seq (Text, LocMatchErr e k)
acc = \case
[] -> MatchErr e (LocMatchErr e k) -> MatchT e k m a
forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM (Seq (Text, LocMatchErr e k) -> MatchErr e (LocMatchErr e k)
forall e r. Seq (Text, r) -> MatchErr e r
MatchErrAlt Seq (Text, LocMatchErr e k)
acc)
(Text
l, MatchT e k m a
m) : [(Text, MatchT e k m a)]
ms -> do
Memo SexpF k
s <- ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) (Memo SexpF k)
-> MatchT e k m (Memo SexpF k)
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) (Memo SexpF k)
forall r (m :: * -> *). MonadReader r m => m r
ask
Either (LocMatchErr e k) a
res <- m (Either (LocMatchErr e k) a)
-> MatchT e k m (Either (LocMatchErr e k) a)
forall (m :: * -> *) a. Monad m => m a -> MatchT e k m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
forall e k (m :: * -> *) a.
MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
runMatchT MatchT e k m a
m Memo SexpF k
s)
case Either (LocMatchErr e k) a
res of
Right a
a -> a -> MatchT e k m a
forall a. a -> MatchT e k m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
Left LocMatchErr e k
e -> Seq (Text, LocMatchErr e k)
-> [(Text, MatchT e k m a)] -> MatchT e k m a
go (Seq (Text, LocMatchErr e k)
acc Seq (Text, LocMatchErr e k)
-> (Text, LocMatchErr e k) -> Seq (Text, LocMatchErr e k)
forall a. Seq a -> a -> Seq a
:|> (Text
l, LocMatchErr e k
e)) [(Text, MatchT e k m a)]
ms
lookM :: (Monad m) => Brace -> [(Text, MatchT e k m (), SeqMatchT e k m a)] -> MatchT e k m a
lookM :: forall (m :: * -> *) e k a.
Monad m =>
Brace
-> [(Text, MatchT e k m (), SeqMatchT e k m a)] -> MatchT e k m a
lookM Brace
b0 [(Text, MatchT e k m (), SeqMatchT e k m a)]
as0 = MatchT e k m a
goRoot
where
goRoot :: MatchT e k m a
goRoot = do
Memo SexpF k
s <- ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) (Memo SexpF k)
-> MatchT e k m (Memo SexpF k)
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) (Memo SexpF k)
forall r (m :: * -> *). MonadReader r m => m r
ask
case Memo SexpF k -> SexpF (Memo SexpF k)
forall (f :: * -> *) k. Memo f k -> f (Memo f k)
B.memoVal Memo SexpF k
s of
SexpListF Brace
b Seq (Memo SexpF k)
cs0 | Brace
b Brace -> Brace -> Bool
forall a. Eq a => a -> a -> Bool
== Brace
b0 ->
case Seq (Memo SexpF k)
cs0 of
Seq (Memo SexpF k)
Empty -> MatchErr e (LocMatchErr e k) -> MatchT e k m a
forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM (Int -> MatchErr e (LocMatchErr e k)
forall e r. Int -> MatchErr e r
MatchErrListElem Int
0)
Memo SexpF k
hd :<| Seq (Memo SexpF k)
_ -> Memo SexpF k
-> Seq (Text, LocMatchErr e k)
-> [(Text, MatchT e k m (), SeqMatchT e k m a)]
-> MatchT e k m a
goAlt Memo SexpF k
hd Seq (Text, LocMatchErr e k)
forall a. Seq a
Empty [(Text, MatchT e k m (), SeqMatchT e k m a)]
as0
SexpF (Memo SexpF k)
_ -> MatchErr e (LocMatchErr e k) -> MatchT e k m a
forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM (SexpType -> MatchErr e (LocMatchErr e k)
forall e r. SexpType -> MatchErr e r
MatchErrType (Brace -> SexpType
SexpTypeList Brace
b0))
goAlt :: Memo SexpF k
-> Seq (Text, LocMatchErr e k)
-> [(Text, MatchT e k m (), SeqMatchT e k m a)]
-> MatchT e k m a
goAlt Memo SexpF k
hd !Seq (Text, LocMatchErr e k)
acc = \case
[] -> MatchErr e (LocMatchErr e k) -> MatchT e k m a
forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM (Seq (Text, LocMatchErr e k) -> MatchErr e (LocMatchErr e k)
forall e r. Seq (Text, r) -> MatchErr e r
MatchErrAlt Seq (Text, LocMatchErr e k)
acc)
(Text
l, MatchT e k m ()
m, SeqMatchT e k m a
r) : [(Text, MatchT e k m (), SeqMatchT e k m a)]
as -> do
Either (LocMatchErr e k) ()
resHd <- m (Either (LocMatchErr e k) ())
-> MatchT e k m (Either (LocMatchErr e k) ())
forall (m :: * -> *) a. Monad m => m a -> MatchT e k m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MatchT e k m () -> Memo SexpF k -> m (Either (LocMatchErr e k) ())
forall e k (m :: * -> *) a.
MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
runMatchT MatchT e k m ()
m Memo SexpF k
hd)
case Either (LocMatchErr e k) ()
resHd of
Right ()
_ -> do
Memo SexpF k
s <- ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) (Memo SexpF k)
-> MatchT e k m (Memo SexpF k)
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) (Memo SexpF k)
forall r (m :: * -> *). MonadReader r m => m r
ask
Either (LocMatchErr e k) a
resTl <- m (Either (LocMatchErr e k) a)
-> MatchT e k m (Either (LocMatchErr e k) a)
forall (m :: * -> *) a. Monad m => m a -> MatchT e k m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
forall e k (m :: * -> *) a.
MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
runMatchT (Int -> Brace -> SeqMatchT e k m a -> MatchT e k m a
forall (m :: * -> *) e k a.
Monad m =>
Int -> Brace -> SeqMatchT e k m a -> MatchT e k m a
listFromM Int
1 Brace
b0 SeqMatchT e k m a
r) Memo SexpF k
s)
case Either (LocMatchErr e k) a
resTl of
Right a
a -> a -> MatchT e k m a
forall a. a -> MatchT e k m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
Left LocMatchErr e k
e -> Memo SexpF k
-> Seq (Text, LocMatchErr e k)
-> [(Text, MatchT e k m (), SeqMatchT e k m a)]
-> MatchT e k m a
goAlt Memo SexpF k
hd (Seq (Text, LocMatchErr e k)
acc Seq (Text, LocMatchErr e k)
-> (Text, LocMatchErr e k) -> Seq (Text, LocMatchErr e k)
forall a. Seq a -> a -> Seq a
:|> (Text
l, LocMatchErr e k
e)) [(Text, MatchT e k m (), SeqMatchT e k m a)]
as
Left LocMatchErr e k
e -> Memo SexpF k
-> Seq (Text, LocMatchErr e k)
-> [(Text, MatchT e k m (), SeqMatchT e k m a)]
-> MatchT e k m a
goAlt Memo SexpF k
hd (Seq (Text, LocMatchErr e k)
acc Seq (Text, LocMatchErr e k)
-> (Text, LocMatchErr e k) -> Seq (Text, LocMatchErr e k)
forall a. Seq a -> a -> Seq a
:|> (Text
l, LocMatchErr e k
e)) [(Text, MatchT e k m (), SeqMatchT e k m a)]
as
anySymM :: (Monad m) => MatchT e k m Sym
anySymM :: forall (m :: * -> *) e k. Monad m => MatchT e k m Sym
anySymM = (SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) Sym)
-> MatchT e k m Sym
forall (m :: * -> *) k e a.
Monad m =>
(SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a)
-> MatchT e k m a
matchM ((SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Sym)
-> MatchT e k m Sym)
-> (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Sym)
-> MatchT e k m Sym
forall a b. (a -> b) -> a -> b
$ \case
SexpAtomF (AtomSym Sym
y) -> Sym -> Either (MatchErr e (LocMatchErr e k)) Sym
forall a b. b -> Either a b
Right Sym
y
SexpF (Memo SexpF k)
_ -> MatchErr e (LocMatchErr e k)
-> Either (MatchErr e (LocMatchErr e k)) Sym
forall a b. a -> Either a b
Left (SexpType -> MatchErr e (LocMatchErr e k)
forall e r. SexpType -> MatchErr e r
MatchErrType (AtomType -> SexpType
SexpTypeAtom AtomType
AtomTypeSym))
symM :: (Monad m) => Sym -> MatchT e k m ()
symM :: forall (m :: * -> *) e k. Monad m => Sym -> MatchT e k m ()
symM Sym
x =
MatchT e k m Sym
forall (m :: * -> *) e k. Monad m => MatchT e k m Sym
anySymM MatchT e k m Sym -> (Sym -> MatchT e k m ()) -> MatchT e k m ()
forall a b.
MatchT e k m a -> (a -> MatchT e k m b) -> MatchT e k m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Sym
y ->
Bool -> MatchT e k m () -> MatchT e k m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Sym
y Sym -> Sym -> Bool
forall a. Eq a => a -> a -> Bool
== Sym
x) (MatchErr e (LocMatchErr e k) -> MatchT e k m ()
forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM (Atom -> MatchErr e (LocMatchErr e k)
forall e r. Atom -> MatchErr e r
MatchErrNotEq (Sym -> Atom
AtomSym Sym
x)))
anyIntM :: (Monad m) => MatchT e k m Integer
anyIntM :: forall (m :: * -> *) e k. Monad m => MatchT e k m Integer
anyIntM = (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Integer)
-> MatchT e k m Integer
forall (m :: * -> *) k e a.
Monad m =>
(SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a)
-> MatchT e k m a
matchM ((SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Integer)
-> MatchT e k m Integer)
-> (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Integer)
-> MatchT e k m Integer
forall a b. (a -> b) -> a -> b
$ \case
SexpAtomF (AtomInt Integer
y) -> Integer -> Either (MatchErr e (LocMatchErr e k)) Integer
forall a b. b -> Either a b
Right Integer
y
SexpF (Memo SexpF k)
_ -> MatchErr e (LocMatchErr e k)
-> Either (MatchErr e (LocMatchErr e k)) Integer
forall a b. a -> Either a b
Left (SexpType -> MatchErr e (LocMatchErr e k)
forall e r. SexpType -> MatchErr e r
MatchErrType (AtomType -> SexpType
SexpTypeAtom AtomType
AtomTypeInt))
intM :: (Monad m) => Integer -> MatchT e k m ()
intM :: forall (m :: * -> *) e k. Monad m => Integer -> MatchT e k m ()
intM Integer
x =
MatchT e k m Integer
forall (m :: * -> *) e k. Monad m => MatchT e k m Integer
anyIntM MatchT e k m Integer
-> (Integer -> MatchT e k m ()) -> MatchT e k m ()
forall a b.
MatchT e k m a -> (a -> MatchT e k m b) -> MatchT e k m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Integer
y ->
Bool -> MatchT e k m () -> MatchT e k m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Integer
y Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
x) (MatchErr e (LocMatchErr e k) -> MatchT e k m ()
forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM (Atom -> MatchErr e (LocMatchErr e k)
forall e r. Atom -> MatchErr e r
MatchErrNotEq (Integer -> Atom
AtomInt Integer
x)))
anySciM :: (Monad m) => MatchT e k m Scientific
anySciM :: forall (m :: * -> *) e k. Monad m => MatchT e k m Scientific
anySciM = (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Scientific)
-> MatchT e k m Scientific
forall (m :: * -> *) k e a.
Monad m =>
(SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a)
-> MatchT e k m a
matchM ((SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Scientific)
-> MatchT e k m Scientific)
-> (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Scientific)
-> MatchT e k m Scientific
forall a b. (a -> b) -> a -> b
$ \case
SexpAtomF (AtomSci Scientific
y) -> Scientific -> Either (MatchErr e (LocMatchErr e k)) Scientific
forall a b. b -> Either a b
Right Scientific
y
SexpF (Memo SexpF k)
_ -> MatchErr e (LocMatchErr e k)
-> Either (MatchErr e (LocMatchErr e k)) Scientific
forall a b. a -> Either a b
Left (SexpType -> MatchErr e (LocMatchErr e k)
forall e r. SexpType -> MatchErr e r
MatchErrType (AtomType -> SexpType
SexpTypeAtom AtomType
AtomTypeSci))
sciM :: (Monad m) => Scientific -> MatchT e k m ()
sciM :: forall (m :: * -> *) e k. Monad m => Scientific -> MatchT e k m ()
sciM Scientific
x =
MatchT e k m Scientific
forall (m :: * -> *) e k. Monad m => MatchT e k m Scientific
anySciM MatchT e k m Scientific
-> (Scientific -> MatchT e k m ()) -> MatchT e k m ()
forall a b.
MatchT e k m a -> (a -> MatchT e k m b) -> MatchT e k m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Scientific
y ->
Bool -> MatchT e k m () -> MatchT e k m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Scientific
y Scientific -> Scientific -> Bool
forall a. Eq a => a -> a -> Bool
== Scientific
x) (MatchErr e (LocMatchErr e k) -> MatchT e k m ()
forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM (Atom -> MatchErr e (LocMatchErr e k)
forall e r. Atom -> MatchErr e r
MatchErrNotEq (Scientific -> Atom
AtomSci Scientific
x)))
anyStrM :: (Monad m) => MatchT e k m Text
anyStrM :: forall (m :: * -> *) e k. Monad m => MatchT e k m Text
anyStrM = (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Text)
-> MatchT e k m Text
forall (m :: * -> *) k e a.
Monad m =>
(SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a)
-> MatchT e k m a
matchM ((SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Text)
-> MatchT e k m Text)
-> (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Text)
-> MatchT e k m Text
forall a b. (a -> b) -> a -> b
$ \case
SexpAtomF (AtomStr Text
y) -> Text -> Either (MatchErr e (LocMatchErr e k)) Text
forall a b. b -> Either a b
Right Text
y
SexpF (Memo SexpF k)
_ -> MatchErr e (LocMatchErr e k)
-> Either (MatchErr e (LocMatchErr e k)) Text
forall a b. a -> Either a b
Left (SexpType -> MatchErr e (LocMatchErr e k)
forall e r. SexpType -> MatchErr e r
MatchErrType (AtomType -> SexpType
SexpTypeAtom AtomType
AtomTypeStr))
strM :: (Monad m) => Text -> MatchT e k m ()
strM :: forall (m :: * -> *) e k. Monad m => Text -> MatchT e k m ()
strM Text
x =
MatchT e k m Text
forall (m :: * -> *) e k. Monad m => MatchT e k m Text
anyStrM MatchT e k m Text -> (Text -> MatchT e k m ()) -> MatchT e k m ()
forall a b.
MatchT e k m a -> (a -> MatchT e k m b) -> MatchT e k m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
y ->
Bool -> MatchT e k m () -> MatchT e k m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text
y Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
x) (MatchErr e (LocMatchErr e k) -> MatchT e k m ()
forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM (Atom -> MatchErr e (LocMatchErr e k)
forall e r. Atom -> MatchErr e r
MatchErrNotEq (Text -> Atom
AtomStr Text
x)))
anyCharM :: (Monad m) => MatchT e k m Char
anyCharM :: forall (m :: * -> *) e k. Monad m => MatchT e k m Char
anyCharM = (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Char)
-> MatchT e k m Char
forall (m :: * -> *) k e a.
Monad m =>
(SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a)
-> MatchT e k m a
matchM ((SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Char)
-> MatchT e k m Char)
-> (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Char)
-> MatchT e k m Char
forall a b. (a -> b) -> a -> b
$ \case
SexpAtomF (AtomChar Char
y) -> Char -> Either (MatchErr e (LocMatchErr e k)) Char
forall a b. b -> Either a b
Right Char
y
SexpF (Memo SexpF k)
_ -> MatchErr e (LocMatchErr e k)
-> Either (MatchErr e (LocMatchErr e k)) Char
forall a b. a -> Either a b
Left (SexpType -> MatchErr e (LocMatchErr e k)
forall e r. SexpType -> MatchErr e r
MatchErrType (AtomType -> SexpType
SexpTypeAtom AtomType
AtomTypeChar))
charM :: (Monad m) => Char -> MatchT e k m ()
charM :: forall (m :: * -> *) e k. Monad m => Char -> MatchT e k m ()
charM Char
x =
MatchT e k m Char
forall (m :: * -> *) e k. Monad m => MatchT e k m Char
anyCharM MatchT e k m Char -> (Char -> MatchT e k m ()) -> MatchT e k m ()
forall a b.
MatchT e k m a -> (a -> MatchT e k m b) -> MatchT e k m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Char
y ->
Bool -> MatchT e k m () -> MatchT e k m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Char
y Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
x) (MatchErr e (LocMatchErr e k) -> MatchT e k m ()
forall (m :: * -> *) e k a.
Monad m =>
MatchErr e (LocMatchErr e k) -> MatchT e k m a
errM (Atom -> MatchErr e (LocMatchErr e k)
forall e r. Atom -> MatchErr e r
MatchErrNotEq (Char -> Atom
AtomChar Char
x)))
anyAtomM :: (Monad m) => MatchT e k m Atom
anyAtomM :: forall (m :: * -> *) e k. Monad m => MatchT e k m Atom
anyAtomM = (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Atom)
-> MatchT e k m Atom
forall (m :: * -> *) k e a.
Monad m =>
(SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a)
-> MatchT e k m a
matchM ((SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Atom)
-> MatchT e k m Atom)
-> (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Atom)
-> MatchT e k m Atom
forall a b. (a -> b) -> a -> b
$ \case
SexpAtomF Atom
a -> Atom -> Either (MatchErr e (LocMatchErr e k)) Atom
forall a b. b -> Either a b
Right Atom
a
SexpF (Memo SexpF k)
_ -> MatchErr e (LocMatchErr e k)
-> Either (MatchErr e (LocMatchErr e k)) Atom
forall a b. a -> Either a b
Left MatchErr e (LocMatchErr e k)
forall e r. MatchErr e r
MatchErrTypeAtom
quoteM :: (Monad m) => MatchT e k m (Memo SexpF k)
quoteM :: forall (m :: * -> *) e k. Monad m => MatchT e k m (Memo SexpF k)
quoteM = (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) (Memo SexpF k))
-> MatchT e k m (Memo SexpF k)
forall (m :: * -> *) k e a.
Monad m =>
(SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a)
-> MatchT e k m a
matchM ((SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) (Memo SexpF k))
-> MatchT e k m (Memo SexpF k))
-> (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) (Memo SexpF k))
-> MatchT e k m (Memo SexpF k)
forall a b. (a -> b) -> a -> b
$ \case
SexpQuoteF Memo SexpF k
x -> Memo SexpF k
-> Either (MatchErr e (LocMatchErr e k)) (Memo SexpF k)
forall a b. b -> Either a b
Right Memo SexpF k
x
SexpF (Memo SexpF k)
_ -> MatchErr e (LocMatchErr e k)
-> Either (MatchErr e (LocMatchErr e k)) (Memo SexpF k)
forall a b. a -> Either a b
Left MatchErr e (LocMatchErr e k)
forall e r. MatchErr e r
MatchErrTypeQuote
unquoteM :: (Monad m) => MatchT e k m (Memo SexpF k)
unquoteM :: forall (m :: * -> *) e k. Monad m => MatchT e k m (Memo SexpF k)
unquoteM = (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) (Memo SexpF k))
-> MatchT e k m (Memo SexpF k)
forall (m :: * -> *) k e a.
Monad m =>
(SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a)
-> MatchT e k m a
matchM ((SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) (Memo SexpF k))
-> MatchT e k m (Memo SexpF k))
-> (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) (Memo SexpF k))
-> MatchT e k m (Memo SexpF k)
forall a b. (a -> b) -> a -> b
$ \case
SexpUnquoteF Memo SexpF k
x -> Memo SexpF k
-> Either (MatchErr e (LocMatchErr e k)) (Memo SexpF k)
forall a b. b -> Either a b
Right Memo SexpF k
x
SexpF (Memo SexpF k)
_ -> MatchErr e (LocMatchErr e k)
-> Either (MatchErr e (LocMatchErr e k)) (Memo SexpF k)
forall a b. a -> Either a b
Left MatchErr e (LocMatchErr e k)
forall e r. MatchErr e r
MatchErrTypeQuote
docM :: (Monad m) => MatchT e k m a -> MatchT e k m (Doc, a)
docM :: forall (m :: * -> *) e k a.
Monad m =>
MatchT e k m a -> MatchT e k m (Doc, a)
docM MatchT e k m a
m = do
(Doc
d, Memo SexpF k
x) <- (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) (Doc, Memo SexpF k))
-> MatchT e k m (Doc, Memo SexpF k)
forall (m :: * -> *) k e a.
Monad m =>
(SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a)
-> MatchT e k m a
matchM ((SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) (Doc, Memo SexpF k))
-> MatchT e k m (Doc, Memo SexpF k))
-> (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) (Doc, Memo SexpF k))
-> MatchT e k m (Doc, Memo SexpF k)
forall a b. (a -> b) -> a -> b
$ \case
SexpDocF Doc
d Memo SexpF k
x -> (Doc, Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) (Doc, Memo SexpF k)
forall a b. b -> Either a b
Right (Doc
d, Memo SexpF k
x)
SexpF (Memo SexpF k)
_ -> MatchErr e (LocMatchErr e k)
-> Either (MatchErr e (LocMatchErr e k)) (Doc, Memo SexpF k)
forall a b. a -> Either a b
Left MatchErr e (LocMatchErr e k)
forall e r. MatchErr e r
MatchErrTypeDoc
a
a <- ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
forall e k (m :: * -> *) a.
ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> MatchT e k m a
MatchT ((Memo SexpF k -> Memo SexpF k)
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall a.
(Memo SexpF k -> Memo SexpF k)
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (Memo SexpF k -> Memo SexpF k -> Memo SexpF k
forall a b. a -> b -> a
const Memo SexpF k
x) (MatchT e k m a
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
forall e k (m :: * -> *) a.
MatchT e k m a
-> ReaderT (Memo SexpF k) (ExceptT (LocMatchErr e k) m) a
unMatchT MatchT e k m a
m))
(Doc, a) -> MatchT e k m (Doc, a)
forall a. a -> MatchT e k m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Doc
d, a
a)
class (Monad m) => MatchSexp e k m a where
matchSexp :: MatchT e k m a
instance (Monad m) => MatchSexp e k m Sexp where
matchSexp :: MatchT e k m Sexp
matchSexp = (SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Sexp)
-> MatchT e k m Sexp
forall (m :: * -> *) k e a.
Monad m =>
(SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a)
-> MatchT e k m a
matchM (Sexp -> Either (MatchErr e (LocMatchErr e k)) Sexp
forall a b. b -> Either a b
Right (Sexp -> Either (MatchErr e (LocMatchErr e k)) Sexp)
-> (SexpF (Memo SexpF k) -> Sexp)
-> SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) Sexp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SexpF Sexp -> Sexp
Sexp (SexpF Sexp -> Sexp)
-> (SexpF (Memo SexpF k) -> SexpF Sexp)
-> SexpF (Memo SexpF k)
-> Sexp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Memo SexpF k -> Sexp) -> SexpF (Memo SexpF k) -> SexpF Sexp
forall a b. (a -> b) -> SexpF a -> SexpF b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Memo SexpF k -> Sexp
forall t (f :: * -> *) k.
(Corecursive t, Base t ~ f) =>
Memo f k -> t
unMkMemo)
instance (Monad m) => MatchSexp e k m (Memo SexpF k) where
matchSexp :: MatchT e k m (Memo SexpF k)
matchSexp = MatchT e k m (SexpF (Memo SexpF k)) -> MatchT e k m (Memo SexpF k)
forall (m :: * -> *) e k (f :: * -> *).
Monad m =>
MatchT e k m (f (Memo f k)) -> MatchT e k m (Memo f k)
memoM ((SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) (SexpF (Memo SexpF k)))
-> MatchT e k m (SexpF (Memo SexpF k))
forall (m :: * -> *) k e a.
Monad m =>
(SexpF (Memo SexpF k) -> Either (MatchErr e (LocMatchErr e k)) a)
-> MatchT e k m a
matchM SexpF (Memo SexpF k)
-> Either (MatchErr e (LocMatchErr e k)) (SexpF (Memo SexpF k))
forall a b. b -> Either a b
Right)
instance (MatchSexp e k m s) => MatchSexp e k m (Anno k s) where
matchSexp :: MatchT e k m (Anno k s)
matchSexp = MatchT e k m s -> MatchT e k m (Anno k s)
forall (m :: * -> *) e k a.
Monad m =>
MatchT e k m a -> MatchT e k m (Anno k a)
annoM MatchT e k m s
forall e k (m :: * -> *) a. MatchSexp e k m a => MatchT e k m a
matchSexp
instance (Monad m) => MatchSexp e k m Atom where
matchSexp :: MatchT e k m Atom
matchSexp = MatchT e k m Atom
forall (m :: * -> *) e k. Monad m => MatchT e k m Atom
anyAtomM
instance (Monad m) => MatchSexp e k m Sym where
matchSexp :: MatchT e k m Sym
matchSexp = MatchT e k m Sym
forall (m :: * -> *) e k. Monad m => MatchT e k m Sym
anySymM
instance (Monad m) => MatchSexp e k m Integer where
matchSexp :: MatchT e k m Integer
matchSexp = MatchT e k m Integer
forall (m :: * -> *) e k. Monad m => MatchT e k m Integer
anyIntM
instance (Monad m) => MatchSexp e k m Scientific where
matchSexp :: MatchT e k m Scientific
matchSexp = MatchT e k m Scientific
forall (m :: * -> *) e k. Monad m => MatchT e k m Scientific
anySciM
instance (Monad m) => MatchSexp e k m Text where
matchSexp :: MatchT e k m Text
matchSexp = MatchT e k m Text
forall (m :: * -> *) e k. Monad m => MatchT e k m Text
anyStrM
instance (Monad m) => MatchSexp e k m Char where
matchSexp :: MatchT e k m Char
matchSexp = MatchT e k m Char
forall (m :: * -> *) e k. Monad m => MatchT e k m Char
anyCharM
fromSexpT :: (MatchSexp e () m a) => Sexp -> m (Either (LocMatchErr e ()) a)
fromSexpT :: forall e (m :: * -> *) a.
MatchSexp e () m a =>
Sexp -> m (Either (LocMatchErr e ()) a)
fromSexpT = MatchT e () m a -> Memo SexpF () -> m (Either (LocMatchErr e ()) a)
forall e k (m :: * -> *) a.
MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
runMatchT MatchT e () m a
forall e k (m :: * -> *) a. MatchSexp e k m a => MatchT e k m a
matchSexp (Memo SexpF () -> m (Either (LocMatchErr e ()) a))
-> (Sexp -> Memo SexpF ())
-> Sexp
-> m (Either (LocMatchErr e ()) a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SexpF () -> ()) -> Sexp -> Memo SexpF ()
forall t (f :: * -> *) k.
(Recursive t, Base t ~ f) =>
(f k -> k) -> t -> Memo f k
mkMemo (() -> SexpF () -> ()
forall a b. a -> b -> a
const ())
fromSexp :: (MatchSexp e () Identity a) => Sexp -> Either (LocMatchErr e ()) a
fromSexp :: forall e a.
MatchSexp e () Identity a =>
Sexp -> Either (LocMatchErr e ()) a
fromSexp = Identity (Either (LocMatchErr e ()) a)
-> Either (LocMatchErr e ()) a
forall a. Identity a -> a
runIdentity (Identity (Either (LocMatchErr e ()) a)
-> Either (LocMatchErr e ()) a)
-> (Sexp -> Identity (Either (LocMatchErr e ()) a))
-> Sexp
-> Either (LocMatchErr e ()) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sexp -> Identity (Either (LocMatchErr e ()) a)
forall e (m :: * -> *) a.
MatchSexp e () m a =>
Sexp -> m (Either (LocMatchErr e ()) a)
fromSexpT
fromAnnoSexpT :: (MatchSexp e k m a) => Memo SexpF k -> m (Either (LocMatchErr e k) a)
fromAnnoSexpT :: forall e k (m :: * -> *) a.
MatchSexp e k m a =>
Memo SexpF k -> m (Either (LocMatchErr e k) a)
fromAnnoSexpT = MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
forall e k (m :: * -> *) a.
MatchT e k m a -> Memo SexpF k -> m (Either (LocMatchErr e k) a)
runMatchT MatchT e k m a
forall e k (m :: * -> *) a. MatchSexp e k m a => MatchT e k m a
matchSexp
fromAnnoSexp :: (MatchSexp e k Identity a) => Memo SexpF k -> Either (LocMatchErr e k) a
fromAnnoSexp :: forall e k a.
MatchSexp e k Identity a =>
Memo SexpF k -> Either (LocMatchErr e k) a
fromAnnoSexp = Identity (Either (LocMatchErr e k) a) -> Either (LocMatchErr e k) a
forall a. Identity a -> a
runIdentity (Identity (Either (LocMatchErr e k) a)
-> Either (LocMatchErr e k) a)
-> (Memo SexpF k -> Identity (Either (LocMatchErr e k) a))
-> Memo SexpF k
-> Either (LocMatchErr e k) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Memo SexpF k -> Identity (Either (LocMatchErr e k) a)
forall e k (m :: * -> *) a.
MatchSexp e k m a =>
Memo SexpF k -> m (Either (LocMatchErr e k) a)
fromAnnoSexpT
proxyM :: (MatchSexp e k m a) => Proxy a -> MatchT e k m a
proxyM :: forall e k (m :: * -> *) a.
MatchSexp e k m a =>
Proxy a -> MatchT e k m a
proxyM = MatchT e k m a -> Proxy a -> MatchT e k m a
forall a b. a -> b -> a
const MatchT e k m a
forall e k (m :: * -> *) a. MatchSexp e k m a => MatchT e k m a
matchSexp