module Interpreter.Lib.String where import qualified Data.ByteString as BS import Data.Coerce import Data.Text as T import Data.Text.Encoding import Data.Vector as V import Interpreter.Common builtInDecodeUTF8Bytes :: BuiltInFnWithDoc '[ '("bytes", BS.ByteString)] builtInDecodeUTF8Bytes ((coerce -> b) :> EmptyArgs) = pure $ Just $ StringValue $ decodeUtf8 b builtInEncodeUTF8Bytes :: BuiltInFnWithDoc '[ '("string", Text)] builtInEncodeUTF8Bytes ((coerce -> b) :> EmptyArgs) = pure $ Just $ BytesValue $ encodeUtf8 b builtInConcat :: BuiltInFnWithDoc '[ '("string1", Text), '("string2", Text)] builtInConcat ((coerce -> b) :> (coerce -> d) :> EmptyArgs) = pure $ Just $ StringValue $ T.concat [b, d] builtInJoin :: BuiltInFnWithDoc '[ '("joiner", Text), '("parts", [Text])] builtInJoin ((coerce -> b) :> (coerce -> d) :> EmptyArgs) = pure $ Just $ StringValue $ T.intercalate b d builtInSplit :: BuiltInFnWithDoc '[ '("divider", Text), '("text", Text)] builtInSplit ((coerce -> b) :> (coerce -> d) :> EmptyArgs) = pure $ Just $ ArrayValue $ V.fromList $ StringValue <$> T.splitOn b d builtInTrim :: BuiltInFnWithDoc '[ '("text", Text)] builtInTrim ((coerce -> d) :> EmptyArgs) = pure $ Just $ StringValue $ T.strip d builtInToLower :: BuiltInFnWithDoc '[ '("text", Text)] builtInToLower ((coerce -> d) :> EmptyArgs) = pure $ Just $ StringValue $ T.toLower d builtInToUpper :: BuiltInFnWithDoc '[ '("text", Text)] builtInToUpper ((coerce -> d) :> EmptyArgs) = pure $ Just $ StringValue $ T.toUpper d builtInReplace :: BuiltInFnWithDoc '[ '("needle", Text), '("replacement", Text), '("haystack", Text) ] builtInReplace ((coerce -> needle) :> (coerce -> replacement) :> (coerce -> haystack) :> EmptyArgs) = pure $ Just $ StringValue $ T.replace needle replacement haystack builtInToString :: BuiltInFnWithDoc '[ '("value", Value)] builtInToString ((coerce -> b) :> EmptyArgs) = pure $ Just $ StringValue $ toStringVal b builtInAmountFormat :: BuiltInFnWithDoc '[ '("separator", Text), '("positions", [Int]), '("value", Value)] builtInAmountFormat ((coerce -> (sep :: Text)) :> (coerce -> (positions :: [Int])) :> (coerce -> (v :: Value)) :> EmptyArgs) = pure $ Just $ StringValue $ amountFormat sep positions (toStringVal v)