module Ondim.Extra.Standard
( standardMap,
bind,
call,
open,
with,
ifBound,
anyBound,
matchBound,
ignore,
scope,
) where
import Data.Text qualified as T
import Ondim
import Ondim.Debug
import Ondim.Extra.Exceptions (tryExp)
import Ondim.Extra.Expansions
standardMap :: NamespaceMap s
standardMap :: forall s. NamespaceMap s
standardMap = do
Text
"if" Text -> PolyExpansion s -> NamespaceMap s
forall m. HasCallStack => Text -> PolyExpansion m -> NamespaceMap m
#* Expansion s a
PolyExpansion s
forall s a. OndimNode a => Expansion s a
ifBound
Text
"any" Text -> PolyExpansion s -> NamespaceMap s
forall m. HasCallStack => Text -> PolyExpansion m -> NamespaceMap m
#* Expansion s a
PolyExpansion s
forall s a. OndimNode a => Expansion s a
anyBound
Text
"match" Text -> PolyExpansion s -> NamespaceMap s
forall m. HasCallStack => Text -> PolyExpansion m -> NamespaceMap m
#* Expansion s a
PolyExpansion s
forall s a. OndimNode a => Expansion s a
matchBound
Text
"try" Text -> PolyExpansion s -> NamespaceMap s
forall m. HasCallStack => Text -> PolyExpansion m -> NamespaceMap m
#* Expansion s a
PolyExpansion s
forall s a. OndimNode a => Expansion s a
tryExp
Text
"ignore" Text -> PolyExpansion s -> NamespaceMap s
forall m. HasCallStack => Text -> PolyExpansion m -> NamespaceMap m
#* Expansion s a
PolyExpansion s
forall s a. OndimNode a => Expansion s a
ignore
Text
"open" Text -> PolyExpansion s -> NamespaceMap s
forall m. HasCallStack => Text -> PolyExpansion m -> NamespaceMap m
#* Expansion s a
PolyExpansion s
forall s a. OndimNode a => Expansion s a
open
Text
"with" Text -> PolyExpansion s -> NamespaceMap s
forall m. HasCallStack => Text -> PolyExpansion m -> NamespaceMap m
#* Expansion s a
PolyExpansion s
forall s a. OndimNode a => Expansion s a
with
Text
"scope" Text -> PolyExpansion s -> NamespaceMap s
forall m. HasCallStack => Text -> PolyExpansion m -> NamespaceMap m
#* Expansion s a
PolyExpansion s
forall s a. OndimNode a => Expansion s a
scope
Text
"call" Text -> PolyExpansion s -> NamespaceMap s
forall m. HasCallStack => Text -> PolyExpansion m -> NamespaceMap m
#* Expansion s a
PolyExpansion s
forall s a. OndimNode a => Expansion s a
call
Text
"bind" Text -> PolyExpansion s -> NamespaceMap s
forall m. HasCallStack => Text -> PolyExpansion m -> NamespaceMap m
#* Expansion s a
forall s. HasCallStack => PolyExpansion s
PolyExpansion s
bind
ifBound :: PolyExpansion s
ifBound :: forall s a. OndimNode a => Expansion s a
ifBound a
node = do
attrs <- (Char -> Bool) -> Text -> [Text]
T.split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
',') (Text -> [Text]) -> Ondim s Text -> Ondim s [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> a -> Ondim s Text
forall t s. OndimNode t => Text -> t -> Ondim s Text
lookupSingleAttr' Text
"id" a
node
bound <- allM exists attrs
ifElse bound node
where
exists :: Text -> Ondim m Bool
exists Text
n = Maybe (NamespaceItem m) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe (NamespaceItem m) -> Bool)
-> (OndimState m -> Maybe (NamespaceItem m))
-> OndimState m
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Namespace m -> Maybe (NamespaceItem m)
forall m. Text -> Namespace m -> Maybe (NamespaceItem m)
lookup Text
n (Namespace m -> Maybe (NamespaceItem m))
-> (OndimState m -> Namespace m)
-> OndimState m
-> Maybe (NamespaceItem m)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OndimState m -> Namespace m
forall s. OndimState s -> Namespace s
expansions (OndimState m -> Bool) -> Ondim m (OndimState m) -> Ondim m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ondim m (OndimState m)
forall s. Ondim s (OndimState s)
getOndimS
anyBound :: PolyExpansion s
anyBound :: forall s a. OndimNode a => Expansion s a
anyBound a
node = do
attrs <- (Text, Text) -> Text
forall a b. (a, b) -> a
fst ((Text, Text) -> Text) -> Ondim s [(Text, Text)] -> Ondim s [Text]
forall (f :: * -> *) (g :: * -> *) a b.
(Functor f, Functor g) =>
(a -> b) -> f (g a) -> f (g b)
<<$>> a -> Ondim s [(Text, Text)]
forall s. a -> Ondim s [(Text, Text)]
forall t s. OndimNode t => t -> Ondim s [(Text, Text)]
attributes a
node
bound <- anyM exists attrs
ifElse bound node
where
exists :: Text -> Ondim m Bool
exists Text
n = Maybe (NamespaceItem m) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe (NamespaceItem m) -> Bool)
-> (OndimState m -> Maybe (NamespaceItem m))
-> OndimState m
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Namespace m -> Maybe (NamespaceItem m)
forall m. Text -> Namespace m -> Maybe (NamespaceItem m)
lookup Text
n (Namespace m -> Maybe (NamespaceItem m))
-> (OndimState m -> Namespace m)
-> OndimState m
-> Maybe (NamespaceItem m)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OndimState m -> Namespace m
forall s. OndimState s -> Namespace s
expansions (OndimState m -> Bool) -> Ondim m (OndimState m) -> Ondim m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ondim m (OndimState m)
forall s. Ondim s (OndimState s)
getOndimS
matchBound :: PolyExpansion s
matchBound :: forall s a. OndimNode a => Expansion s a
matchBound a
node = do
tag <- Text -> a -> Ondim s Text
forall t s. OndimNode t => Text -> t -> Ondim s Text
lookupSingleAttr' Text
"id" a
node
tagC <- getText tag
switchWithDefault (rightToMaybe tagC) node
ignore :: PolyExpansion s
ignore :: forall s a. OndimNode a => Expansion s a
ignore = Ondim s [a] -> a -> Ondim s [a]
forall a b. a -> b -> a
const (Ondim s [a] -> a -> Ondim s [a])
-> Ondim s [a] -> a -> Ondim s [a]
forall a b. (a -> b) -> a -> b
$ [a] -> Ondim s [a]
forall a. a -> Ondim s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
open :: PolyExpansion s
open :: forall s a. OndimNode a => Expansion s a
open a
node = do
name <- Text -> a -> Ondim s Text
forall t s. OndimNode t => Text -> t -> Ondim s Text
lookupSingleAttr' Text
"id" a
node
exps <- getNamespace name
withoutExpansions [name] $
case exps of
Right Namespace s
n -> Namespace s -> Ondim s [a] -> Ondim s [a]
forall s a. Namespace s -> Ondim s a -> Ondim s a
withNamespace Namespace s
n (Ondim s [a] -> Ondim s [a]) -> Ondim s [a] -> Ondim s [a]
forall a b. (a -> b) -> a -> b
$ Expansion s a
forall t s. OndimNode t => Expansion s t
expandChildren a
node
Left OndimFailure
e -> forall {k} (t :: k) s a.
Typeable t =>
Text -> OndimFailure -> Ondim s a
forall t s a. Typeable t => Text -> OndimFailure -> Ondim s a
throwExpFailure @() Text
name OndimFailure
e
with :: PolyExpansion s
with :: forall s a. OndimNode a => Expansion s a
with a
node = do
exps <- OndimState s -> Namespace s
forall s. OndimState s -> Namespace s
expansions (OndimState s -> Namespace s)
-> Ondim s (OndimState s) -> Ondim s (Namespace s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ondim s (OndimState s)
forall s. Ondim s (OndimState s)
getOndimS
actions <-
attributes node <&> map \(Text
k, Text
v) ->
let expansion :: Maybe (NamespaceItem s)
expansion = Text -> Namespace s -> Maybe (NamespaceItem s)
forall m. Text -> Namespace m -> Maybe (NamespaceItem m)
lookup Text
v Namespace s
exps
in [Text] -> Ondim s [a] -> Ondim s [a]
forall s a. [Text] -> Ondim s a -> Ondim s a
withoutExpansions [Text
v] (Ondim s [a] -> Ondim s [a])
-> (Ondim s [a] -> Ondim s [a]) -> Ondim s [a] -> Ondim s [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe (NamespaceItem s) -> Ondim s [a] -> Ondim s [a]
forall s a.
Text -> Maybe (NamespaceItem s) -> Ondim s a -> Ondim s a
withSomeExpansion Text
k Maybe (NamespaceItem s)
expansion
foldr ($) (expandChildren node) actions
scope :: PolyExpansion s
scope :: forall s a. OndimNode a => Expansion s a
scope a
node = do
s <- Ondim s (OndimState s)
forall s. Ondim s (OndimState s)
getOndimS
expandChildren node <* putOndimS s
call :: PolyExpansion s
call :: forall s a. OndimNode a => Expansion s a
call a
node = do
name <- Text -> a -> Ondim s Text
forall t s. OndimNode t => Text -> t -> Ondim s Text
lookupSingleAttr' Text
"id" a
node
callExpansion name node
bind :: (HasCallStack) => PolyExpansion s
bind :: forall s. HasCallStack => PolyExpansion s
bind a
node = do
attrs <- a -> Ondim s [(Text, Text)]
forall s. a -> Ondim s [(Text, Text)]
forall t s. OndimNode t => t -> Ondim s [(Text, Text)]
attributes a
node
defSite <- getCurrentSite
let strict = ((Text, Text) -> Bool) -> [(Text, Text)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Text
"strict" Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==) (Text -> Bool) -> ((Text, Text) -> Text) -> (Text, Text) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> Text
forall a b. (a, b) -> a
fst) [(Text, Text)]
attrs
thing <-
if strict
then expandChildren node
else return $ children node
name <- ensureSingleAttr "id" attrs
putSomeExpansion name . Just $ TemplateData defSite thing
pure []