{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies      #-}
-- |
-- Module: Data.Greskell.Gremlin
-- Description: Gremlin (Groovy/Java) utility classes
-- Maintainer: Toshio Ito <debug.ito@gmail.com>
--
-- This modules defines types and functions for utility classes in
-- Gremlin.
module Data.Greskell.Gremlin
    ( -- * Predicate
      Predicate (..)
    , PredicateA (..)
      -- ** P class
    , P
    , PLike (..)
    , pNot
    , pEq
    , pNeq
    , pLt
    , pLte
    , pGt
    , pGte
    , pInside
    , pOutside
    , pBetween
    , pWithin
    , pWithout
      -- * Comparator
    , Comparator (..)
    , ComparatorA (..)
      -- ** Order enum
    , Order
    , oDesc
    , oAsc
    , oDecr
    , oIncr
    , oShuffle
      -- * Examples
    , examples
    ) where

import           Data.Aeson             (Value)
import           Data.Greskell.GraphSON (GraphSONTyped (..))
import           Data.Greskell.Greskell (Greskell, ToGreskell, string, toGremlin, toGremlinLazy,
                                         unsafeFunCall, unsafeGreskellLazy, unsafeMethodCall)
import           Data.Monoid            ((<>))
import           Data.Text              (Text)

-- | @java.util.function.Predicate@ interface.
--
-- A 'Predicate' @p@ is a function that takes 'PredicateArg' @p@ and
-- returns 'Bool'.
class Predicate p where
  type PredicateArg p
  -- | @.and@ method.
  pAnd :: Greskell p -> Greskell p -> Greskell p
  pAnd Greskell p
p1 Greskell p
p2 = forall a b. Greskell a -> Text -> [Text] -> Greskell b
unsafeMethodCall Greskell p
p1 Text
"and" [forall a. ToGreskell a => a -> Text
toGremlin Greskell p
p2]
  -- | @.or@ method.
  pOr :: Greskell p -> Greskell p -> Greskell p
  pOr Greskell p
o1 Greskell p
o2 = forall a b. Greskell a -> Text -> [Text] -> Greskell b
unsafeMethodCall Greskell p
o1 Text
"or" [forall a. ToGreskell a => a -> Text
toGremlin Greskell p
o2]
  -- | @.test@ method.
  pTest :: Greskell p -> Greskell (PredicateArg p) -> Greskell Bool
  pTest Greskell p
p Greskell (PredicateArg p)
arg = forall a b. Greskell a -> Text -> [Text] -> Greskell b
unsafeMethodCall Greskell p
p Text
"test" [forall a. ToGreskell a => a -> Text
toGremlin Greskell (PredicateArg p)
arg]
  -- | @.nagate@ method.
  pNegate :: Greskell p -> Greskell p
  pNegate Greskell p
p = forall a b. Greskell a -> Text -> [Text] -> Greskell b
unsafeMethodCall Greskell p
p Text
"negate" []

-- | Type for anonymous class of @Predicate@ interface.
newtype PredicateA a
  = PredicateA { forall a. PredicateA a -> a -> Bool
unPredicateA :: a -> Bool }

instance Predicate (PredicateA a) where
  type PredicateArg (PredicateA a) = a

-- | @org.apache.tinkerpop.gremlin.process.traversal.P@ class.
--
-- @P a@ keeps data of type @a@ and compares it with data of type @a@
-- given as the Predicate argument.
data P a

instance Predicate (P a) where
  type PredicateArg (P a) = a

instance GraphSONTyped (P a) where
  gsonTypeFor :: P a -> Text
gsonTypeFor P a
_ = Text
"g:P"

-- | Type that is compatible with 'P'. You can construct a value of
-- type @Greskell p@ using values of @PParameter p@.
--
-- Note that the type of constuctor arguments (i.e. @GreskellReturn (PParameter p)@)
-- should implement Java's @Comparable@ interface. This is true for most types,
-- so greskell doesn't have any explicit constraint about it.
--
-- @since 1.2.0.0
class (ToGreskell (PParameter p)) => PLike p where
  type PParameter p

-- | You can construct @Greskell (P a)@ from @Greskell a@.
instance PLike (P a) where
  type PParameter (P a) = Greskell a

-- | @P.not@ static method.
pNot :: PLike p => Greskell p -> Greskell p
pNot :: forall p. PLike p => Greskell p -> Greskell p
pNot Greskell p
a = forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
"P.not" [forall a. ToGreskell a => a -> Text
toGremlin Greskell p
a]

-- | @P.eq@ static method.
pEq :: PLike p => PParameter p -> Greskell p
pEq :: forall p. PLike p => PParameter p -> Greskell p
pEq PParameter p
arg = forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
"P.eq" [forall a. ToGreskell a => a -> Text
toGremlin PParameter p
arg]

-- | @P.neq@ static method.
pNeq :: PLike p => PParameter p -> Greskell p
pNeq :: forall p. PLike p => PParameter p -> Greskell p
pNeq PParameter p
arg = forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
"P.neq" [forall a. ToGreskell a => a -> Text
toGremlin PParameter p
arg]

-- | @P.lt@ static method.
pLt :: PLike p => PParameter p -> Greskell p
pLt :: forall p. PLike p => PParameter p -> Greskell p
pLt PParameter p
arg = forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
"P.lt" [forall a. ToGreskell a => a -> Text
toGremlin PParameter p
arg]

-- | @P.lte@ static method.
pLte :: PLike p => PParameter p -> Greskell p
pLte :: forall p. PLike p => PParameter p -> Greskell p
pLte PParameter p
arg = forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
"P.lte" [forall a. ToGreskell a => a -> Text
toGremlin PParameter p
arg]

-- | @P.gt@ static method.
pGt :: PLike p => PParameter p -> Greskell p
pGt :: forall p. PLike p => PParameter p -> Greskell p
pGt PParameter p
arg = forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
"P.gt" [forall a. ToGreskell a => a -> Text
toGremlin PParameter p
arg]

-- | @P.gte@ static method.
pGte :: PLike p => PParameter p -> Greskell p
pGte :: forall p. PLike p => PParameter p -> Greskell p
pGte PParameter p
arg = forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
"P.gte" [forall a. ToGreskell a => a -> Text
toGremlin PParameter p
arg]

-- | @P.inside@ static method.
pInside :: PLike p => PParameter p -> PParameter p -> Greskell p
pInside :: forall p. PLike p => PParameter p -> PParameter p -> Greskell p
pInside PParameter p
a PParameter p
b = forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
"P.inside" forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. ToGreskell a => a -> Text
toGremlin [PParameter p
a, PParameter p
b]

-- | @P.outside@ static method.
pOutside :: PLike p => PParameter p -> PParameter p -> Greskell p
pOutside :: forall p. PLike p => PParameter p -> PParameter p -> Greskell p
pOutside PParameter p
a PParameter p
b = forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
"P.outside" forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. ToGreskell a => a -> Text
toGremlin [PParameter p
a, PParameter p
b]

-- | @P.between@ static method.
pBetween :: PLike p => PParameter p -> PParameter p -> Greskell p
pBetween :: forall p. PLike p => PParameter p -> PParameter p -> Greskell p
pBetween PParameter p
a PParameter p
b = forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
"P.between" forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. ToGreskell a => a -> Text
toGremlin [PParameter p
a, PParameter p
b]

-- | @P.within@ static method.
pWithin :: PLike p => [PParameter p] -> Greskell p
pWithin :: forall p. PLike p => [PParameter p] -> Greskell p
pWithin = forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
"P.within" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a. ToGreskell a => a -> Text
toGremlin

-- | @P.without@ static method.
pWithout :: PLike p => [PParameter p] -> Greskell p
pWithout :: forall p. PLike p => [PParameter p] -> Greskell p
pWithout = forall a. Text -> [Text] -> Greskell a
unsafeFunCall Text
"P.without" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a. ToGreskell a => a -> Text
toGremlin

-- | @java.util.Comparator@ interface.
--
-- 'Comparator' compares two data of type 'CompareArg' @c@.
class Comparator c where
  type CompareArg c
  -- | @.compare@ method.
  cCompare :: Greskell c -> Greskell (CompareArg c) -> Greskell (CompareArg c) -> Greskell Int
  cCompare Greskell c
cmp Greskell (CompareArg c)
a Greskell (CompareArg c)
b = forall a b. Greskell a -> Text -> [Text] -> Greskell b
unsafeMethodCall Greskell c
cmp Text
"compare" forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. ToGreskell a => a -> Text
toGremlin [Greskell (CompareArg c)
a, Greskell (CompareArg c)
b]
  -- | @.reversed@ method.
  cReversed :: Greskell c -> Greskell c
  cReversed Greskell c
cmp = forall a b. Greskell a -> Text -> [Text] -> Greskell b
unsafeMethodCall Greskell c
cmp Text
"reversed" []
  -- | @.thenComparing@ method.
  cThenComparing :: Greskell c -> Greskell c -> Greskell c
  cThenComparing Greskell c
cmp1 Greskell c
cmp2 = forall a b. Greskell a -> Text -> [Text] -> Greskell b
unsafeMethodCall Greskell c
cmp1 Text
"thenComparing" [forall a. ToGreskell a => a -> Text
toGremlin Greskell c
cmp2]

-- | Type for anonymous class of @Comparator@ interface.
newtype ComparatorA a
  = ComparatorA { forall a. ComparatorA a -> a -> a -> Int
unComparatorA :: a -> a -> Int }

instance Comparator (ComparatorA a) where
  type CompareArg (ComparatorA a) = a

-- | @org.apache.tinkerpop.gremlin.process.traversal.Order@ enum.
data Order a

-- | @Order a@ compares the type @a@.
instance Comparator (Order a) where
  type CompareArg (Order a) = a

instance GraphSONTyped (Order a) where
  gsonTypeFor :: Order a -> Text
gsonTypeFor Order a
_ = Text
"g:Order"

-- | @desc@ order.
--
-- @since 2.0.2.0
oDesc :: Greskell (Order a)
oDesc :: forall a. Greskell (Order a)
oDesc = forall a. Text -> Greskell a
unsafeGreskellLazy Text
"Order.desc"

-- | @asc@ order.
--
-- @since 2.0.2.0
oAsc :: Greskell (Order a)
oAsc :: forall a. Greskell (Order a)
oAsc = forall a. Text -> Greskell a
unsafeGreskellLazy Text
"Order.asc"

-- | @decr@ order.
--
-- Note that @decr@ was removed in TinkerPop 3.5.0. Use 'oDesc' instead.
oDecr :: Greskell (Order a)
oDecr :: forall a. Greskell (Order a)
oDecr = forall a. Text -> Greskell a
unsafeGreskellLazy Text
"Order.decr"

-- | @incr@ order.
--
-- Note that @incr@ was removed in TinkerPop 3.5.0. Use 'oAsc' instead.
oIncr :: Greskell (Order a)
oIncr :: forall a. Greskell (Order a)
oIncr = forall a. Text -> Greskell a
unsafeGreskellLazy Text
"Order.incr"

-- | @shuffle@ order.
oShuffle :: Greskell (Order a)
oShuffle :: forall a. Greskell (Order a)
oShuffle = forall a. Text -> Greskell a
unsafeGreskellLazy Text
"Order.shuffle"

-- | 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 =
  [ (forall a. ToGreskell a => a -> Text
toGremlin (forall p. PLike p => Greskell p -> Greskell p
pNot forall a b. (a -> b) -> a -> b
$ forall p. PLike p => PParameter p -> Greskell p
pEq forall a b. (a -> b) -> a -> b
$ Greskell Int
10 :: Greskell (P Int)), Text
"P.not(P.eq(10))")
  , (forall a. ToGreskell a => a -> Text
toGremlin (forall p. PLike p => PParameter p -> Greskell p
pEq forall a b. (a -> b) -> a -> b
$ Text -> Greskell Text
string Text
"hoge" :: Greskell (P Text)), Text
"P.eq(\"hoge\")")
  , (forall a. ToGreskell a => a -> Text
toGremlin (forall p. PLike p => PParameter p -> PParameter p -> Greskell p
pInside Greskell Int
10 Greskell Int
20 :: Greskell (P Int)), Text
"P.inside(10,20)")
  , (forall a. ToGreskell a => a -> Text
toGremlin (forall p. PLike p => [PParameter p] -> Greskell p
pWithin [Greskell Text
"foo", Greskell Text
"bar", Greskell Text
"hoge"] :: Greskell (P Text)), Text
"P.within(\"foo\",\"bar\",\"hoge\")")
  , (forall a. ToGreskell a => a -> Text
toGremlin forall a. Greskell (Order a)
oDesc, Text
"Order.desc")
  , (forall a. ToGreskell a => a -> Text
toGremlin forall a. Greskell (Order a)
oAsc, Text
"Order.asc")
  , (forall a. ToGreskell a => a -> Text
toGremlin forall a. Greskell (Order a)
oDecr, Text
"Order.decr")
  , (forall a. ToGreskell a => a -> Text
toGremlin forall a. Greskell (Order a)
oIncr, Text
"Order.incr")
  ]