module Hydra.Langs.Scala.Prepare (
prepareType,
) where
import Hydra.Kernel
import qualified Hydra.Dsl.Types as Types
import qualified Data.Set as S
prepareLiteralType :: LiteralType -> (LiteralType, Literal -> Literal, S.Set String)
prepareLiteralType :: LiteralType -> (LiteralType, Literal -> Literal, Set String)
prepareLiteralType LiteralType
at = case LiteralType
at of
LiteralType
LiteralTypeBinary -> LiteralType
-> String
-> String
-> (Literal -> Literal)
-> (LiteralType, Literal -> Literal, Set String)
forall a b. a -> String -> String -> b -> (a, b, Set String)
subst LiteralType
LiteralTypeString
String
"binary strings" String
"character strings"
((Literal -> Literal)
-> (LiteralType, Literal -> Literal, Set String))
-> (Literal -> Literal)
-> (LiteralType, Literal -> Literal, Set String)
forall a b. (a -> b) -> a -> b
$ \(LiteralBinary String
v) -> String -> Literal
LiteralString String
v
LiteralTypeFloat FloatType
ft -> (FloatType -> LiteralType
LiteralTypeFloat FloatType
rtyp, \(LiteralFloat FloatValue
v) -> FloatValue -> Literal
LiteralFloat (FloatValue -> Literal) -> FloatValue -> Literal
forall a b. (a -> b) -> a -> b
$ FloatValue -> FloatValue
rep FloatValue
v, Set String
msgs)
where
(FloatType
rtyp, FloatValue -> FloatValue
rep, Set String
msgs) = FloatType -> (FloatType, FloatValue -> FloatValue, Set String)
prepareFloatType FloatType
ft
LiteralTypeInteger IntegerType
it -> (IntegerType -> LiteralType
LiteralTypeInteger IntegerType
rtyp, \(LiteralInteger IntegerValue
v) -> IntegerValue -> Literal
LiteralInteger (IntegerValue -> Literal) -> IntegerValue -> Literal
forall a b. (a -> b) -> a -> b
$ IntegerValue -> IntegerValue
rep IntegerValue
v, Set String
msgs)
where
(IntegerType
rtyp, IntegerValue -> IntegerValue
rep, Set String
msgs) = IntegerType
-> (IntegerType, IntegerValue -> IntegerValue, Set String)
prepareIntegerType IntegerType
it
LiteralType
_ -> LiteralType -> (LiteralType, Literal -> Literal, Set String)
forall a b c. a -> (a, b -> b, Set c)
same LiteralType
at
prepareFloatType :: FloatType -> (FloatType, FloatValue -> FloatValue, S.Set String)
prepareFloatType :: FloatType -> (FloatType, FloatValue -> FloatValue, Set String)
prepareFloatType FloatType
ft = case FloatType
ft of
FloatType
FloatTypeBigfloat -> FloatType
-> String
-> String
-> (FloatValue -> FloatValue)
-> (FloatType, FloatValue -> FloatValue, Set String)
forall a b. a -> String -> String -> b -> (a, b, Set String)
subst FloatType
FloatTypeFloat64
String
"arbitrary-precision floating-point numbers" String
"64-bit floating-point numbers (doubles)"
((FloatValue -> FloatValue)
-> (FloatType, FloatValue -> FloatValue, Set String))
-> (FloatValue -> FloatValue)
-> (FloatType, FloatValue -> FloatValue, Set String)
forall a b. (a -> b) -> a -> b
$ \(FloatValueBigfloat Double
v) -> Double -> FloatValue
FloatValueFloat64 Double
v
FloatType
_ -> FloatType -> (FloatType, FloatValue -> FloatValue, Set String)
forall a b c. a -> (a, b -> b, Set c)
same FloatType
ft
prepareIntegerType :: IntegerType -> (IntegerType, IntegerValue -> IntegerValue, S.Set String)
prepareIntegerType :: IntegerType
-> (IntegerType, IntegerValue -> IntegerValue, Set String)
prepareIntegerType IntegerType
it = case IntegerType
it of
IntegerType
IntegerTypeBigint -> IntegerType
-> String
-> String
-> (IntegerValue -> IntegerValue)
-> (IntegerType, IntegerValue -> IntegerValue, Set String)
forall a b. a -> String -> String -> b -> (a, b, Set String)
subst IntegerType
IntegerTypeInt64
String
"arbitrary-precision integers" String
"64-bit integers"
((IntegerValue -> IntegerValue)
-> (IntegerType, IntegerValue -> IntegerValue, Set String))
-> (IntegerValue -> IntegerValue)
-> (IntegerType, IntegerValue -> IntegerValue, Set String)
forall a b. (a -> b) -> a -> b
$ \(IntegerValueBigint Integer
v) -> Int64 -> IntegerValue
IntegerValueInt64 (Int64 -> IntegerValue) -> Int64 -> IntegerValue
forall a b. (a -> b) -> a -> b
$ Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
v
IntegerType
IntegerTypeUint8 -> IntegerType
-> String
-> String
-> (IntegerValue -> IntegerValue)
-> (IntegerType, IntegerValue -> IntegerValue, Set String)
forall a b. a -> String -> String -> b -> (a, b, Set String)
subst IntegerType
IntegerTypeInt8
String
"unsigned 8-bit integers" String
"signed 8-bit integers"
((IntegerValue -> IntegerValue)
-> (IntegerType, IntegerValue -> IntegerValue, Set String))
-> (IntegerValue -> IntegerValue)
-> (IntegerType, IntegerValue -> IntegerValue, Set String)
forall a b. (a -> b) -> a -> b
$ \(IntegerValueUint8 Int16
v) -> Int8 -> IntegerValue
IntegerValueInt8 (Int8 -> IntegerValue) -> Int8 -> IntegerValue
forall a b. (a -> b) -> a -> b
$ Int16 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
v
IntegerType
IntegerTypeUint32 -> IntegerType
-> String
-> String
-> (IntegerValue -> IntegerValue)
-> (IntegerType, IntegerValue -> IntegerValue, Set String)
forall a b. a -> String -> String -> b -> (a, b, Set String)
subst IntegerType
IntegerTypeInt32
String
"unsigned 32-bit integers" String
"signed 32-bit integers"
((IntegerValue -> IntegerValue)
-> (IntegerType, IntegerValue -> IntegerValue, Set String))
-> (IntegerValue -> IntegerValue)
-> (IntegerType, IntegerValue -> IntegerValue, Set String)
forall a b. (a -> b) -> a -> b
$ \(IntegerValueUint32 Int64
v) -> Int -> IntegerValue
IntegerValueInt32 (Int -> IntegerValue) -> Int -> IntegerValue
forall a b. (a -> b) -> a -> b
$ Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
v
IntegerType
IntegerTypeUint64 -> IntegerType
-> String
-> String
-> (IntegerValue -> IntegerValue)
-> (IntegerType, IntegerValue -> IntegerValue, Set String)
forall a b. a -> String -> String -> b -> (a, b, Set String)
subst IntegerType
IntegerTypeInt64
String
"unsigned 64-bit integers" String
"signed 64-bit integers"
((IntegerValue -> IntegerValue)
-> (IntegerType, IntegerValue -> IntegerValue, Set String))
-> (IntegerValue -> IntegerValue)
-> (IntegerType, IntegerValue -> IntegerValue, Set String)
forall a b. (a -> b) -> a -> b
$ \(IntegerValueUint64 Integer
v) -> Int64 -> IntegerValue
IntegerValueInt64 (Int64 -> IntegerValue) -> Int64 -> IntegerValue
forall a b. (a -> b) -> a -> b
$ Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
v
IntegerType
_ -> IntegerType
-> (IntegerType, IntegerValue -> IntegerValue, Set String)
forall a b c. a -> (a, b -> b, Set c)
same IntegerType
it
prepareType :: Graph -> Type -> (Type, Term -> Term, S.Set String)
prepareType :: Graph -> Type -> (Type, Term -> Term, Set String)
prepareType Graph
cx Type
typ = case Type -> Type
stripType Type
typ of
TypeLiteral LiteralType
at -> (LiteralType -> Type
Types.literal LiteralType
rtyp, \(TermLiteral Literal
av) -> Literal -> Term
TermLiteral (Literal -> Term) -> Literal -> Term
forall a b. (a -> b) -> a -> b
$ Literal -> Literal
rep Literal
av, Set String
msgs)
where
(LiteralType
rtyp, Literal -> Literal
rep, Set String
msgs) = LiteralType -> (LiteralType, Literal -> Literal, Set String)
prepareLiteralType LiteralType
at
same :: a -> (a, b -> b, S.Set c)
same :: forall a b c. a -> (a, b -> b, Set c)
same a
x = (a
x, b -> b
forall a. a -> a
id, Set c
forall a. Set a
S.empty)
subst :: a -> [Char] -> [Char] -> b -> (a, b, S.Set [Char])
subst :: forall a b. a -> String -> String -> b -> (a, b, Set String)
subst a
t String
from String
to b
r = (a
t, b
r, [String] -> Set String
forall a. Ord a => [a] -> Set a
S.fromList [String
"replace " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
from String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" with " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
to])