{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies      #-}
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
-- |
-- Module: Data.Greskell.Greskell
-- Description: Low-level Gremlin script data type
-- Maintainer: Toshio Ito <debug.ito@gmail.com>
--
--
module Data.Greskell.Greskell
    ( -- * Type
      Greskell
    , ToGreskell (..)
      -- * Conversions
    , toGremlin
    , toGremlinLazy
      -- * Literals
      --
      -- $literals
    , string
    , true
    , false
    , list
    , single
    , number
    , value
    , valueInt
    , gvalue
    , gvalueInt
      -- * Unsafe constructors
    , unsafeGreskell
    , unsafeGreskellLazy
    , unsafeFunCall
    , unsafeMethodCall
      -- * Examples
    , examples
    ) where

import           Data.Aeson             (Value)
import qualified Data.Aeson             as Aeson
import qualified Data.Aeson.Key         as Key
import qualified Data.Aeson.KeyMap      as KM
import           Data.Bifunctor         (bimap)
import           Data.Foldable          (toList)
import           Data.List              (intersperse)
import           Data.Monoid            (Monoid (..))
import           Data.Ratio             (Rational, denominator, numerator)
import           Data.Scientific        (Scientific, base10Exponent, coefficient)
import           Data.Semigroup         (Semigroup (..))
import           Data.String            (IsString (..))
import           Data.Text              (Text, pack, unpack)
import qualified Data.Text.Lazy         as TL

import           Data.Greskell.GraphSON (GValue, GValueBody (..), nonTypedGValue)

-- | Gremlin expression of type @a@.
--
-- 'Greskell' is essentially just a piece of Gremlin script with a
-- phantom type. The type @a@ represents the type of data that the
-- script is supposed to evaluate to.
--
-- 'Eq' and 'Ord' instances compare Gremlin scripts, NOT the values
-- they evaluate to.
newtype Greskell a
  = Greskell { forall a. Greskell a -> Text
unGreskell :: TL.Text }
  deriving (Greskell a -> Greskell a -> Bool
(Greskell a -> Greskell a -> Bool)
-> (Greskell a -> Greskell a -> Bool) -> Eq (Greskell a)
forall a. Greskell a -> Greskell a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Greskell a -> Greskell a -> Bool
== :: Greskell a -> Greskell a -> Bool
$c/= :: forall a. Greskell a -> Greskell a -> Bool
/= :: Greskell a -> Greskell a -> Bool
Eq, Eq (Greskell a)
Eq (Greskell a) =>
(Greskell a -> Greskell a -> Ordering)
-> (Greskell a -> Greskell a -> Bool)
-> (Greskell a -> Greskell a -> Bool)
-> (Greskell a -> Greskell a -> Bool)
-> (Greskell a -> Greskell a -> Bool)
-> (Greskell a -> Greskell a -> Greskell a)
-> (Greskell a -> Greskell a -> Greskell a)
-> Ord (Greskell a)
Greskell a -> Greskell a -> Bool
Greskell a -> Greskell a -> Ordering
Greskell a -> Greskell a -> Greskell a
forall a. Eq (Greskell a)
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 a. Greskell a -> Greskell a -> Bool
forall a. Greskell a -> Greskell a -> Ordering
forall a. Greskell a -> Greskell a -> Greskell a
$ccompare :: forall a. Greskell a -> Greskell a -> Ordering
compare :: Greskell a -> Greskell a -> Ordering
$c< :: forall a. Greskell a -> Greskell a -> Bool
< :: Greskell a -> Greskell a -> Bool
$c<= :: forall a. Greskell a -> Greskell a -> Bool
<= :: Greskell a -> Greskell a -> Bool
$c> :: forall a. Greskell a -> Greskell a -> Bool
> :: Greskell a -> Greskell a -> Bool
$c>= :: forall a. Greskell a -> Greskell a -> Bool
>= :: Greskell a -> Greskell a -> Bool
$cmax :: forall a. Greskell a -> Greskell a -> Greskell a
max :: Greskell a -> Greskell a -> Greskell a
$cmin :: forall a. Greskell a -> Greskell a -> Greskell a
min :: Greskell a -> Greskell a -> Greskell a
Ord, Int -> Greskell a -> ShowS
[Greskell a] -> ShowS
Greskell a -> [Char]
(Int -> Greskell a -> ShowS)
-> (Greskell a -> [Char])
-> ([Greskell a] -> ShowS)
-> Show (Greskell a)
forall a. Int -> Greskell a -> ShowS
forall a. [Greskell a] -> ShowS
forall a. Greskell a -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Int -> Greskell a -> ShowS
showsPrec :: Int -> Greskell a -> ShowS
$cshow :: forall a. Greskell a -> [Char]
show :: Greskell a -> [Char]
$cshowList :: forall a. [Greskell a] -> ShowS
showList :: [Greskell a] -> ShowS
Show)

-- | Same as 'string' except for the input and output type.
instance IsString a => IsString (Greskell a) where
  fromString :: [Char] -> Greskell a
fromString = Text -> Greskell a
forall a. Text -> Greskell a
Greskell (Text -> Greskell a) -> ([Char] -> Text) -> [Char] -> Greskell a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
TL.pack ([Char] -> Text) -> ShowS -> [Char] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
escapeDQuotes

-- | Unsafely convert the phantom type.
instance Functor Greskell where
  fmap :: forall a b. (a -> b) -> Greskell a -> Greskell b
fmap a -> b
_ = Text -> Greskell b
forall a. Text -> Greskell a
Greskell (Text -> Greskell b)
-> (Greskell a -> Text) -> Greskell a -> Greskell b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Greskell a -> Text
forall a. Greskell a -> Text
unGreskell

-- | Integer literals and numeric operation in Gremlin
instance Num a => Num (Greskell a) where
  + :: Greskell a -> Greskell a -> Greskell a
(+) = Text -> Greskell a -> Greskell a -> Greskell a
forall a. Text -> Greskell a -> Greskell a -> Greskell a
biOp Text
"+"
  (-) = Text -> Greskell a -> Greskell a -> Greskell a
forall a. Text -> Greskell a -> Greskell a -> Greskell a
biOp Text
"-"
  * :: Greskell a -> Greskell a -> Greskell a
(*) = Text -> Greskell a -> Greskell a -> Greskell a
forall a. Text -> Greskell a -> Greskell a -> Greskell a
biOp Text
"*"
  negate :: Greskell a -> Greskell a
negate (Greskell Text
a) = Text -> Greskell a
forall a. Text -> Greskell a
Greskell (Text
"-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
paren Text
a)
  abs :: Greskell a -> Greskell a
abs (Greskell Text
a) = Text -> Greskell a
forall a. Text -> Greskell a
Greskell (Text
"java.lang.Math.abs" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
paren Text
a)
  signum :: Greskell a -> Greskell a
signum (Greskell Text
a) = Text -> Greskell a
forall a. Text -> Greskell a
Greskell (Text
"java.lang.Long.signum" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
paren Text
a)
  fromInteger :: Integer -> Greskell a
fromInteger Integer
val = Text -> Greskell a
forall a. Text -> Greskell a
Greskell ([Char] -> Text
TL.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> [Char]
forall a. Show a => a -> [Char]
show Integer
val)

-- | Floating-point number literals and numeric operation in Gremlin
instance Fractional a => Fractional (Greskell a) where
  / :: Greskell a -> Greskell a -> Greskell a
(/) = Text -> Greskell a -> Greskell a -> Greskell a
forall a. Text -> Greskell a -> Greskell a -> Greskell a
biOp Text
"/"
  recip :: Greskell a -> Greskell a
recip (Greskell Text
a) = Text -> Greskell a
forall a. Text -> Greskell a
Greskell (Text
"1.0/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
paren Text
a)
  fromRational :: Rational -> Greskell a
fromRational Rational
rat = Text -> Greskell a
forall a. Text -> Greskell a
Greskell (Text -> Greskell a) -> Text -> Greskell a
forall a b. (a -> b) -> a -> b
$ (Rational -> Integer) -> Text
scriptOf Rational -> Integer
forall a. Ratio a -> a
numerator Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
".0/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (Rational -> Integer) -> Text
scriptOf Rational -> Integer
forall a. Ratio a -> a
denominator
    where
      scriptOf :: (Rational -> Integer) -> Text
scriptOf Rational -> Integer
accessor = [Char] -> Text
TL.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> [Char]
forall a. Show a => a -> [Char]
show (Integer -> [Char]) -> Integer -> [Char]
forall a b. (a -> b) -> a -> b
$ Rational -> Integer
accessor Rational
rat

-- | Semigroup operator '<>' on 'Greskell' assumes @String@
-- concatenation on Gremlin.
instance IsString a => Semigroup (Greskell a) where
  <> :: Greskell a -> Greskell a -> Greskell a
(<>) = Text -> Greskell a -> Greskell a -> Greskell a
forall a. Text -> Greskell a -> Greskell a -> Greskell a
biOp Text
"+"

-- | Monoidal operations on 'Greskell' assumes @String@ operations in
-- Gremlin. 'mempty' is the empty String, and 'mappend' is String
-- concatenation.
instance IsString a => Monoid (Greskell a) where
  mempty :: Greskell a
mempty = [Char] -> Greskell a
forall a. IsString a => [Char] -> a
fromString [Char]
""
  mappend :: Greskell a -> Greskell a -> Greskell a
mappend = Greskell a -> Greskell a -> Greskell a
forall a. Semigroup a => a -> a -> a
(<>)

-- | Something that can convert to 'Greskell'.
class ToGreskell a where
  type GreskellReturn a
  -- ^ type of return value by Greskell.
  toGreskell :: a -> Greskell (GreskellReturn a)

-- | It's just 'id'.
instance ToGreskell (Greskell a) where
  type GreskellReturn (Greskell a) = a
  toGreskell :: Greskell a -> Greskell (GreskellReturn (Greskell a))
toGreskell = Greskell a -> Greskell a
Greskell a -> Greskell (GreskellReturn (Greskell a))
forall a. a -> a
id


biOp :: TL.Text -> Greskell a -> Greskell a -> Greskell a
biOp :: forall a. Text -> Greskell a -> Greskell a -> Greskell a
biOp Text
operator (Greskell Text
a) (Greskell Text
b) = Text -> Greskell a
forall a. Text -> Greskell a
Greskell (Text -> Text
paren Text
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
operator Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
paren Text
b)

paren :: TL.Text -> TL.Text
paren :: Text -> Text
paren Text
t = Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"

escapeDQuotes :: String -> String
escapeDQuotes :: ShowS
escapeDQuotes [Char]
orig = (Char
'"' Char -> ShowS
forall a. a -> [a] -> [a]
: (Char -> [Char]
esc (Char -> [Char]) -> ShowS
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Char]
orig)) [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"\""
  where
    esc :: Char -> [Char]
esc Char
c = case Char
c of
      Char
'\n' -> [Char]
"\\n"
      Char
'\r' -> [Char]
"\\r"
      Char
'\t' -> [Char]
"\\t"
      Char
'\\' -> [Char]
"\\\\"
      Char
'"'  -> [Char]
"\\\""
      Char
'$'  -> [Char]
"\\$"
      Char
x    -> [Char
x]
      -- do we have to espace other characters?


-- | Unsafely create a 'Greskell' of arbitrary type. The given Gremlin
-- script is printed as-is.
unsafeGreskell :: Text -- ^ Gremlin script
               -> Greskell a
unsafeGreskell :: forall a. Text -> Greskell a
unsafeGreskell = Text -> Greskell a
forall a. Text -> Greskell a
Greskell (Text -> Greskell a) -> (Text -> Text) -> Text -> Greskell a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
TL.fromStrict

-- | Same as 'unsafeGreskell', but it takes lazy 'TL.Text'.
unsafeGreskellLazy :: TL.Text -- ^ Gremlin script
                   -> Greskell a
unsafeGreskellLazy :: forall a. Text -> Greskell a
unsafeGreskellLazy = Text -> Greskell a
forall a. Text -> Greskell a
Greskell


-- $literals
--
-- Functions to create literals in Gremlin script. Use 'fromInteger',
-- 'valueInt' or 'gvalueInt' to create integer literals. Use
-- 'fromRational' or 'number' to create floating-point data literals.

-- | Create a String literal in Gremlin script. The content is
-- automatically escaped.
string :: Text -> Greskell Text
string :: Text -> Greskell Text
string = [Char] -> Greskell Text
forall a. IsString a => [Char] -> a
fromString ([Char] -> Greskell Text)
-> (Text -> [Char]) -> Text -> Greskell Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Char]
unpack

-- | Boolean @true@ literal.
true :: Greskell Bool
true :: Greskell Bool
true = Text -> Greskell Bool
forall a. Text -> Greskell a
unsafeGreskell Text
"true"

-- | Boolean @false@ literal.
false :: Greskell Bool
false :: Greskell Bool
false = Text -> Greskell Bool
forall a. Text -> Greskell a
unsafeGreskell Text
"false"

-- | List literal.
list :: [Greskell a] -> Greskell [a]
list :: forall a. [Greskell a] -> Greskell [a]
list [Greskell a]
gs = Text -> Greskell [a]
forall a. Text -> Greskell a
unsafeGreskellLazy (Text -> Greskell [a]) -> Text -> Greskell [a]
forall a b. (a -> b) -> a -> b
$ (Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
TL.intercalate Text
"," [Text]
gs_txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]")
  where
    gs_txt :: [Text]
gs_txt = (Greskell a -> Text) -> [Greskell a] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Greskell a -> Text
forall a. ToGreskell a => a -> Text
toGremlinLazy [Greskell a]
gs

-- | Make a list with a single object. Useful to prevent the Gremlin
-- Server from automatically iterating the result object.
single :: Greskell a -> Greskell [a]
single :: forall a. Greskell a -> Greskell [a]
single Greskell a
g = [Greskell a] -> Greskell [a]
forall a. [Greskell a] -> Greskell [a]
list [Greskell a
g]

-- | Arbitrary precision number literal, like \"123e8\".
number :: Scientific -> Greskell Scientific
number :: Scientific -> Greskell Scientific
number = Text -> Greskell Scientific
forall a. Text -> Greskell a
unsafeGreskell (Text -> Greskell Scientific)
-> (Scientific -> Text) -> Scientific -> Greskell Scientific
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
pack ([Char] -> Text) -> (Scientific -> [Char]) -> Scientific -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> [Char]
forall a. Show a => a -> [Char]
show

-- | Aeson 'Value' literal.
--
-- Note that 'Aeson.Number' does not distinguish integers from
-- floating-point numbers, so 'value' function may format an integer
-- as a floating-point number. To ensure formatting as integers, use
-- 'valueInt'.
value :: Value -> Greskell Value
value :: Value -> Greskell Value
value Value
Aeson.Null = Text -> Greskell Value
forall a. Text -> Greskell a
unsafeGreskellLazy Text
"null"
value (Aeson.Bool Bool
b) = Greskell Bool -> Greskell Value
forall a. Greskell a -> Greskell Value
unsafeToValue (if Bool
b then Greskell Bool
true else Greskell Bool
false)
value (Aeson.Number Scientific
sci) = Greskell Scientific -> Greskell Value
forall a. Greskell a -> Greskell Value
unsafeToValue (Greskell Scientific -> Greskell Value)
-> Greskell Scientific -> Greskell Value
forall a b. (a -> b) -> a -> b
$ Scientific -> Greskell Scientific
number Scientific
sci
value (Aeson.String Text
s) = Greskell Text -> Greskell Value
forall a. Greskell a -> Greskell Value
unsafeToValue (Greskell Text -> Greskell Value)
-> Greskell Text -> Greskell Value
forall a b. (a -> b) -> a -> b
$ Text -> Greskell Text
string Text
s
value (Aeson.Array Array
v) = Greskell [Value] -> Greskell Value
forall a. Greskell a -> Greskell Value
unsafeToValue (Greskell [Value] -> Greskell Value)
-> Greskell [Value] -> Greskell Value
forall a b. (a -> b) -> a -> b
$ [Greskell Value] -> Greskell [Value]
forall a. [Greskell a] -> Greskell [a]
list ([Greskell Value] -> Greskell [Value])
-> [Greskell Value] -> Greskell [Value]
forall a b. (a -> b) -> a -> b
$ (Value -> Greskell Value) -> [Value] -> [Greskell Value]
forall a b. (a -> b) -> [a] -> [b]
map Value -> Greskell Value
value ([Value] -> [Greskell Value]) -> [Value] -> [Greskell Value]
forall a b. (a -> b) -> a -> b
$ Array -> [Value]
forall a. Vector a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Array
v
value (Aeson.Object Object
obj)
  | Object -> Bool
forall v. KeyMap v -> Bool
KM.null Object
obj = Text -> Greskell Value
forall a. Text -> Greskell a
unsafeGreskellLazy Text
"[:]"
  | Bool
otherwise = Text -> Greskell Value
forall a. Text -> Greskell a
unsafeGreskellLazy (Text -> Greskell Value) -> Text -> Greskell Value
forall a b. (a -> b) -> a -> b
$ [(Key, Value)] -> Text
toGroovyMap ([(Key, Value)] -> Text) -> [(Key, Value)] -> Text
forall a b. (a -> b) -> a -> b
$ Object -> [(Key, Value)]
forall v. KeyMap v -> [(Key, v)]
KM.toList Object
obj
  where
    toGroovyMap :: [(Key, Value)] -> Text
toGroovyMap [(Key, Value)]
pairs = Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
TL.intercalate Text
"," (((Key, Value) -> Text) -> [(Key, Value)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Key, Value) -> Text
toPairText [(Key, Value)]
pairs) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]"
    toPairText :: (Key, Value) -> Text
toPairText (Key
key, Value
val) = (Greskell Text -> Text
forall a. ToGreskell a => a -> Text
toGremlinLazy (Greskell Text -> Text) -> Greskell Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Greskell Text
string (Text -> Greskell Text) -> Text -> Greskell Text
forall a b. (a -> b) -> a -> b
$ Key -> Text
Key.toText Key
key) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (Greskell Value -> Text
forall a. ToGreskell a => a -> Text
toGremlinLazy (Greskell Value -> Text) -> Greskell Value -> Text
forall a b. (a -> b) -> a -> b
$ Value -> Greskell Value
value Value
val)

-- | Integer literal as 'Value' type.
--
-- @since 0.1.2.0
valueInt :: Integral a => a -> Greskell Value
valueInt :: forall a. Integral a => a -> Greskell Value
valueInt a
n = (Integer -> Value) -> Greskell Integer -> Greskell Value
forall a b. (a -> b) -> Greskell a -> Greskell b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> Value
toValue (Greskell Integer -> Greskell Value)
-> Greskell Integer -> Greskell Value
forall a b. (a -> b) -> a -> b
$ a -> Greskell Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
n
  where
    toValue :: Integer -> Value
    toValue :: Integer -> Value
toValue = Value -> Integer -> Value
forall a b. a -> b -> a
const Value
Aeson.Null

-- | 'Value' literal as 'GValue' type.
--
-- @since 0.1.2.0
gvalue :: Value -> Greskell GValue
gvalue :: Value -> Greskell GValue
gvalue = (Value -> GValue) -> Greskell Value -> Greskell GValue
forall a b. (a -> b) -> Greskell a -> Greskell b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> GValue
forall {p}. p -> GValue
phantomToGValue (Greskell Value -> Greskell GValue)
-> (Value -> Greskell Value) -> Value -> Greskell GValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Greskell Value
value
  where
    phantomToGValue :: p -> GValue
phantomToGValue p
_ = GValueBody -> GValue
nonTypedGValue (GValueBody -> GValue) -> GValueBody -> GValue
forall a b. (a -> b) -> a -> b
$ GValueBody
GNull

-- | Integer literal as 'GValue' type.
--
-- @since 0.1.2.0
gvalueInt :: Integral a => a -> Greskell GValue
gvalueInt :: forall a. Integral a => a -> Greskell GValue
gvalueInt a
n = (Integer -> GValue) -> Greskell Integer -> Greskell GValue
forall a b. (a -> b) -> Greskell a -> Greskell b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> GValue
toGValue (Greskell Integer -> Greskell GValue)
-> Greskell Integer -> Greskell GValue
forall a b. (a -> b) -> a -> b
$ a -> Greskell Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
n
  where
    toGValue :: Integer -> GValue
    toGValue :: Integer -> GValue
toGValue = GValue -> Integer -> GValue
forall a b. a -> b -> a
const (GValue -> Integer -> GValue) -> GValue -> Integer -> GValue
forall a b. (a -> b) -> a -> b
$ GValueBody -> GValue
nonTypedGValue (GValueBody -> GValue) -> GValueBody -> GValue
forall a b. (a -> b) -> a -> b
$ GValueBody
GNull

unsafeToValue :: Greskell a -> Greskell Value
unsafeToValue :: forall a. Greskell a -> Greskell Value
unsafeToValue = (a -> Value) -> Greskell a -> Greskell Value
forall a b. (a -> b) -> Greskell a -> Greskell b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Value -> a -> Value
forall a b. a -> b -> a
const Value
Aeson.Null)

-- | Create a readable Gremlin script from 'Greskell'.
toGremlin :: ToGreskell a => a -> Text
toGremlin :: forall a. ToGreskell a => a -> Text
toGremlin = Text -> Text
TL.toStrict (Text -> Text) -> (a -> Text) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Greskell (GreskellReturn a) -> Text
forall a. Greskell a -> Text
unGreskell (Greskell (GreskellReturn a) -> Text)
-> (a -> Greskell (GreskellReturn a)) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Greskell (GreskellReturn a)
forall a. ToGreskell a => a -> Greskell (GreskellReturn a)
toGreskell

-- | Same as 'toGremlin' except that this returns lazy 'TL.Text'.
toGremlinLazy :: ToGreskell a => a -> TL.Text
toGremlinLazy :: forall a. ToGreskell a => a -> Text
toGremlinLazy = Greskell (GreskellReturn a) -> Text
forall a. Greskell a -> Text
unGreskell (Greskell (GreskellReturn a) -> Text)
-> (a -> Greskell (GreskellReturn a)) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Greskell (GreskellReturn a)
forall a. ToGreskell a => a -> Greskell (GreskellReturn a)
toGreskell

unsafeFunCallText :: Text -> [Text] -> Text
unsafeFunCallText :: Text -> [Text] -> Text
unsafeFunCallText Text
fun_name [Text]
args = Text
fun_name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
args_g Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
  where
    args_g :: Text
args_g = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
intersperse Text
"," [Text]
args

-- | Unsafely create a 'Greskell' that calls the given function with
-- the given arguments.
unsafeFunCall :: Text -- ^ function name
              -> [Text] -- ^ arguments
              -> Greskell a -- ^ return value of the function call
unsafeFunCall :: forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
fun_name [Text]
args = Text -> Greskell a
forall a. Text -> Greskell a
unsafeGreskell (Text -> Greskell a) -> Text -> Greskell a
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> Text
unsafeFunCallText Text
fun_name [Text]
args

-- | Unsafely create a 'Greskell' that calls the given object method
-- call with the given target and arguments.
unsafeMethodCall :: Greskell a -- ^ target object
                 -> Text -- ^ method name
                 -> [Text] -- ^ arguments
                 -> Greskell b -- ^ return value of the method call
unsafeMethodCall :: forall a b. Greskell a -> Text -> [Text] -> Greskell b
unsafeMethodCall Greskell a
target Text
name [Text]
args = Text -> Greskell b
forall a. Text -> Greskell a
unsafeGreskell (Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Greskell a -> Text
forall a. ToGreskell a => a -> Text
toGremlin Greskell a
target Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
unsafeFunCallText Text
name [Text]
args)

-- | Examples of using this module. See the source. The 'fst' of the output is the testee, while the
-- 'snd' is the expectation.
examples :: [(Text, Text)]
examples :: [(Text, Text)]
examples =
  [ (Greskell Any -> Text
forall a. ToGreskell a => a -> Text
toGremlin (Greskell Any -> Text) -> Greskell Any -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Greskell Any
forall a. Text -> Greskell a
unsafeGreskell Text
"x + 100", Text
"x + 100")
  , (Greskell Text -> Text
forall a. ToGreskell a => a -> Text
toGremlin (Greskell Text -> Text) -> Greskell Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Greskell Text
string Text
"foo bar", Text
"\"foo bar\"")
  , (Greskell Text -> Text
forall a. ToGreskell a => a -> Text
toGremlin (Greskell Text -> Text) -> Greskell Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Greskell Text
string Text
"escape newline\n escape dollar $", Text
"\"escape newline\\n escape dollar \\$\"")
  , (Greskell Bool -> Text
forall a. ToGreskell a => a -> Text
toGremlin Greskell Bool
true, Text
"true")
  , (Greskell Bool -> Text
forall a. ToGreskell a => a -> Text
toGremlin Greskell Bool
false, Text
"false")
  , (Greskell [Int] -> Text
forall a. ToGreskell a => a -> Text
toGremlin (Greskell [Int] -> Text) -> Greskell [Int] -> Text
forall a b. (a -> b) -> a -> b
$ [Greskell Int] -> Greskell [Int]
forall a. [Greskell a] -> Greskell [a]
list ([Greskell Int
100, Greskell Int
200, Greskell Int
300] :: [Greskell Int]), Text
"[100,200,300]")
  , (Greskell [Text] -> Text
forall a. ToGreskell a => a -> Text
toGremlin (Greskell [Text] -> Text) -> Greskell [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Greskell Text -> Greskell [Text]
forall a. Greskell a -> Greskell [a]
single (Greskell Text
"hoge" :: Greskell Text), Text
"[\"hoge\"]")
  , (Greskell Scientific -> Text
forall a. ToGreskell a => a -> Text
toGremlin (Greskell Scientific -> Text) -> Greskell Scientific -> Text
forall a b. (a -> b) -> a -> b
$ Scientific -> Greskell Scientific
number Scientific
123e8, Text
"1.23e10")
  , (Greskell Value -> Text
forall a. ToGreskell a => a -> Text
toGremlin (Greskell Value -> Text) -> Greskell Value -> Text
forall a b. (a -> b) -> a -> b
$ Value -> Greskell Value
value Value
Aeson.Null, Text
"null")
  , (Greskell Value -> Text
forall a. ToGreskell a => a -> Text
toGremlin (Greskell Value -> Text) -> Greskell Value -> Text
forall a b. (a -> b) -> a -> b
$ Value -> Greskell Value
value (Value -> Greskell Value) -> Value -> Greskell Value
forall a b. (a -> b) -> a -> b
$ [Int] -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON ([Int] -> Value) -> [Int] -> Value
forall a b. (a -> b) -> a -> b
$ ([Int
10, Int
20, Int
30] :: [Int]), Text
"[10.0,20.0,30.0]")
  , (Greskell Value -> Text
forall a. ToGreskell a => a -> Text
toGremlin (Greskell Value -> Text) -> Greskell Value -> Text
forall a b. (a -> b) -> a -> b
$ Value -> Greskell Value
value (Value -> Greskell Value) -> Value -> Greskell Value
forall a b. (a -> b) -> a -> b
$ Object -> Value
Aeson.Object Object
forall a. Monoid a => a
mempty, Text
"[:]")
  , (Greskell Value -> Text
forall a. ToGreskell a => a -> Text
toGremlin (Greskell Value -> Text) -> Greskell Value -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Greskell Value
forall a. Integral a => a -> Greskell Value
valueInt (Int
100 :: Int), Text
"100")
  , (Greskell GValue -> Text
forall a. ToGreskell a => a -> Text
toGremlin (Greskell GValue -> Text) -> Greskell GValue -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Greskell GValue
forall a. Integral a => a -> Greskell GValue
gvalueInt (Int
256 :: Int), Text
"256")
  , (Greskell Any -> Text
forall a. ToGreskell a => a -> Text
toGremlin (Greskell Any -> Text) -> Greskell Any -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> Greskell Any
forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
"add" [Text
"10", Text
"20"], Text
"add(10,20)")
  , (Greskell Any -> Text
forall a. ToGreskell a => a -> Text
toGremlin (Greskell Any -> Text) -> Greskell Any -> Text
forall a b. (a -> b) -> a -> b
$ Greskell Text -> Text -> [Text] -> Greskell Any
forall a b. Greskell a -> Text -> [Text] -> Greskell b
unsafeMethodCall (Greskell Text
"foobar" :: Greskell Text) Text
"length" [], Text
"(\"foobar\").length()")
  ]