module Spark.Core.StructuresInternal(
NodeName(..),
NodePath(..),
NodeId(..),
FieldName(..),
FieldPath(..),
catNodePath,
fieldName,
unsafeFieldName,
fieldPath,
) where
import qualified Data.Text as T
import Data.ByteString(ByteString)
import GHC.Generics (Generic)
import Data.Hashable(Hashable)
import Data.List(intercalate)
import qualified Data.Aeson as A
import Data.String(IsString(..))
import Data.Vector(Vector)
import qualified Data.Vector as V
import Spark.Core.Internal.Utilities
newtype NodeName = NodeName { unNodeName :: T.Text } deriving (Eq, Ord)
newtype NodePath = NodePath { unNodePath :: Vector NodeName } deriving (Eq)
newtype NodeId = NodeId { unNodeId :: ByteString } deriving (Eq, Ord, Generic)
newtype FieldName = FieldName { unFieldName :: T.Text } deriving (Eq)
newtype FieldPath = FieldPath { unFieldPath :: Vector FieldName } deriving (Eq)
fieldName :: T.Text -> Either String FieldName
fieldName = Right . FieldName
unsafeFieldName :: (HasCallStack) => T.Text -> FieldName
unsafeFieldName = forceRight . fieldName
fieldPath :: T.Text -> Either String FieldPath
fieldPath x = Right . FieldPath . V.singleton $ FieldName x
catNodePath :: NodePath -> T.Text
catNodePath (NodePath np) =
T.intercalate "/" (unNodeName <$> V.toList np)
instance Show NodeId where
show (NodeId bs) = let s = show bs in
if length s > 9 then
(drop 1 . take 6) s ++ ".."
else
s
instance Show NodeName where
show (NodeName nn) = T.unpack nn
instance Show NodePath where
show np = T.unpack $ T.concat ["NPath(", catNodePath np, ")" ]
instance Show FieldPath where
show (FieldPath l) =
intercalate "." (show <$> V.toList l)
instance Show FieldName where
show (FieldName fn) = T.unpack fn
instance Hashable NodeId
instance IsString FieldName where
fromString = FieldName . T.pack
instance A.ToJSON NodeName where
toJSON = A.toJSON . unNodeName
instance A.ToJSON NodePath where
toJSON = A.toJSON . unNodePath
instance A.ToJSON FieldName where
toJSON = A.toJSON . unFieldName
instance A.ToJSON FieldPath where
toJSON = A.toJSON . unFieldPath
instance Ord FieldName where
compare f1 f2 = compare (unFieldName f1) (unFieldName f2)