{-# LANGUAGE DeriveFunctor #-}
module Dhall.Context (
Context
, empty
, insert
, match
, lookup
, toList
) where
import Data.Text (Text)
import Prelude hiding (lookup)
newtype Context a = Context { forall a. Context a -> [(Text, a)]
getContext :: [(Text, a)] }
deriving (forall a b. a -> Context b -> Context a
forall a b. (a -> b) -> Context a -> Context b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Context b -> Context a
$c<$ :: forall a b. a -> Context b -> Context a
fmap :: forall a b. (a -> b) -> Context a -> Context b
$cfmap :: forall a b. (a -> b) -> Context a -> Context b
Functor)
empty :: Context a
empty :: forall a. Context a
empty = forall a. [(Text, a)] -> Context a
Context []
insert :: Text -> a -> Context a -> Context a
insert :: forall a. Text -> a -> Context a -> Context a
insert Text
k a
v (Context [(Text, a)]
kvs) = forall a. [(Text, a)] -> Context a
Context ((Text
k, a
v) forall a. a -> [a] -> [a]
: [(Text, a)]
kvs)
{-# INLINABLE insert #-}
match :: Context a -> Maybe (Text, a, Context a)
match :: forall a. Context a -> Maybe (Text, a, Context a)
match (Context ((Text
k, a
v) : [(Text, a)]
kvs)) = forall a. a -> Maybe a
Just (Text
k, a
v, forall a. [(Text, a)] -> Context a
Context [(Text, a)]
kvs)
match (Context [] ) = forall a. Maybe a
Nothing
{-# INLINABLE match #-}
lookup :: Text -> Int -> Context a -> Maybe a
lookup :: forall a. Text -> Int -> Context a -> Maybe a
lookup Text
_ Int
_ (Context [] ) =
forall a. Maybe a
Nothing
lookup Text
x Int
n (Context ((Text
k, a
v):[(Text, a)]
kvs)) =
if Text
x forall a. Eq a => a -> a -> Bool
== Text
k
then if Int
n forall a. Eq a => a -> a -> Bool
== Int
0
then forall a. a -> Maybe a
Just a
v
else forall a. Text -> Int -> Context a -> Maybe a
lookup Text
x (Int
n forall a. Num a => a -> a -> a
- Int
1) (forall a. [(Text, a)] -> Context a
Context [(Text, a)]
kvs)
else forall a. Text -> Int -> Context a -> Maybe a
lookup Text
x Int
n (forall a. [(Text, a)] -> Context a
Context [(Text, a)]
kvs)
{-# INLINABLE lookup #-}
toList :: Context a -> [(Text, a)]
toList :: forall a. Context a -> [(Text, a)]
toList = forall a. Context a -> [(Text, a)]
getContext
{-# INLINABLE toList #-}