{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
module Dovetail.Core.Data.String.Common where
import Data.Foldable (fold)
import Data.Text (Text)
import Data.Text qualified as Text
import Data.Vector (Vector)
import Data.Vector qualified as Vector
import Dovetail
import Dovetail.Evaluate (builtIn)
env :: forall ctx. Env ctx
env :: Env ctx
env = do
let _ModuleName :: ModuleName
_ModuleName = Text -> ModuleName
ModuleName Text
"Data.String.Common"
[Env ctx] -> Env ctx
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold
[ ModuleName
-> Text
-> (Value ctx
-> Value ctx -> Value ctx -> Text -> Text -> Eval ctx (Value ctx))
-> Env ctx
forall ctx a. ToValue ctx a => ModuleName -> Text -> a -> Env ctx
builtIn @ctx @(Value ctx -> Value ctx -> Value ctx -> Text -> Text -> Eval ctx (Value ctx))
ModuleName
_ModuleName Text
"_localeCompare"
\Value ctx
lt Value ctx
eq Value ctx
gt Text
t1 Text
t2 -> Value ctx -> Eval ctx (Value ctx)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
case Text -> Text -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Text
t1 Text
t2 of
Ordering
LT -> Value ctx
lt
Ordering
EQ -> Value ctx
eq
Ordering
GT -> Value ctx
gt
, ModuleName
-> Text -> (Text -> Text -> Text -> Eval ctx Text) -> Env ctx
forall ctx a. ToValue ctx a => ModuleName -> Text -> a -> Env ctx
builtIn @ctx @(Text -> Text -> Text -> Eval ctx Text)
ModuleName
_ModuleName Text
"replace"
\Text
needle Text
replacement Text
haystack ->
Text -> Eval ctx Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure case Text -> Text -> (Text, Text)
Text.breakOn Text
needle Text
haystack of
(Text
_, Text
"") -> Text
haystack
(Text
before, Text
after) -> Text
before Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
replacement Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
after
, ModuleName
-> Text -> (Text -> Text -> Text -> Eval ctx Text) -> Env ctx
forall ctx a. ToValue ctx a => ModuleName -> Text -> a -> Env ctx
builtIn @ctx @(Text -> Text -> Text -> Eval ctx Text)
ModuleName
_ModuleName Text
"replaceAll"
\Text
needle Text
replacement Text
haystack ->
Text -> Eval ctx Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Text -> Text -> Text
Text.replace Text
needle Text
replacement Text
haystack)
, ModuleName
-> Text -> (Text -> Text -> Eval ctx (Vector Text)) -> Env ctx
forall ctx a. ToValue ctx a => ModuleName -> Text -> a -> Env ctx
builtIn @ctx @(Text -> Text -> Eval ctx (Vector Text))
ModuleName
_ModuleName Text
"split"
\Text
sep Text
s ->
Vector Text -> Eval ctx (Vector Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Text] -> Vector Text
forall a. [a] -> Vector a
Vector.fromList (Text -> Text -> [Text]
Text.splitOn Text
sep Text
s))
, ModuleName -> Text -> (Text -> Eval ctx Text) -> Env ctx
forall ctx a. ToValue ctx a => ModuleName -> Text -> a -> Env ctx
builtIn @ctx @(Text -> Eval ctx Text)
ModuleName
_ModuleName Text
"toLower"
(Text -> Eval ctx Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Eval ctx Text) -> (Text -> Text) -> Text -> Eval ctx Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
Text.toLower)
, ModuleName -> Text -> (Text -> Eval ctx Text) -> Env ctx
forall ctx a. ToValue ctx a => ModuleName -> Text -> a -> Env ctx
builtIn @ctx @(Text -> Eval ctx Text)
ModuleName
_ModuleName Text
"toUpper"
(Text -> Eval ctx Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Eval ctx Text) -> (Text -> Text) -> Text -> Eval ctx Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
Text.toUpper)
, ModuleName -> Text -> (Text -> Eval ctx Text) -> Env ctx
forall ctx a. ToValue ctx a => ModuleName -> Text -> a -> Env ctx
builtIn @ctx @(Text -> Eval ctx Text)
ModuleName
_ModuleName Text
"trim"
(Text -> Eval ctx Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Eval ctx Text) -> (Text -> Text) -> Text -> Eval ctx Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
Text.strip)
, ModuleName
-> Text -> (Text -> Vector Text -> Eval ctx Text) -> Env ctx
forall ctx a. ToValue ctx a => ModuleName -> Text -> a -> Env ctx
builtIn @ctx @(Text -> Vector Text -> Eval ctx Text)
ModuleName
_ModuleName Text
"joinWith"
\Text
sep Vector Text
ss ->
Text -> Eval ctx Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> [Text] -> Text
Text.intercalate Text
sep (Vector Text -> [Text]
forall a. Vector a -> [a]
Vector.toList Vector Text
ss))
]