module Hydra.Printing where
import qualified Hydra.Basics as Basics
import qualified Hydra.Core as Core
import qualified Hydra.Lib.Literals as Literals
import qualified Hydra.Lib.Strings as Strings
import qualified Hydra.Mantle as Mantle
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S
describeFloatType :: (Core.FloatType -> String)
describeFloatType :: FloatType -> String
describeFloatType FloatType
t = ([String] -> String
Strings.cat [
(\FloatType
x -> Precision -> String
describePrecision (FloatType -> Precision
Basics.floatTypePrecision FloatType
x)) FloatType
t,
String
" floating-point numbers"])
describeIntegerType :: (Core.IntegerType -> String)
describeIntegerType :: IntegerType -> String
describeIntegerType IntegerType
t = ([String] -> String
Strings.cat [
(\IntegerType
x -> Precision -> String
describePrecision (IntegerType -> Precision
Basics.integerTypePrecision IntegerType
x)) IntegerType
t,
String
" integers"])
describeLiteralType :: (Core.LiteralType -> String)
describeLiteralType :: LiteralType -> String
describeLiteralType LiteralType
x = case LiteralType
x of
LiteralType
Core.LiteralTypeBinary -> String
"binary strings"
LiteralType
Core.LiteralTypeBoolean -> String
"boolean values"
Core.LiteralTypeFloat FloatType
v246 -> (FloatType -> String
describeFloatType FloatType
v246)
Core.LiteralTypeInteger IntegerType
v247 -> (IntegerType -> String
describeIntegerType IntegerType
v247)
LiteralType
Core.LiteralTypeString -> String
"character strings"
describePrecision :: (Mantle.Precision -> String)
describePrecision :: Precision -> String
describePrecision Precision
x = case Precision
x of
Precision
Mantle.PrecisionArbitrary -> String
"arbitrary-precision"
Mantle.PrecisionBits Int
v250 -> ([String] -> String
Strings.cat [
Int -> String
Literals.showInt32 Int
v250,
String
"-bit"])
describeType :: (Core.Type -> String)
describeType :: Type -> String
describeType Type
x = case Type
x of
Core.TypeAnnotated AnnotatedType
v251 -> ([String] -> String
Strings.cat [
String
"annotated ",
(Type -> String
describeType (AnnotatedType -> Type
Core.annotatedTypeSubject AnnotatedType
v251))])
Core.TypeApplication ApplicationType
_ -> String
"instances of an application type"
Core.TypeLiteral LiteralType
v253 -> (LiteralType -> String
describeLiteralType LiteralType
v253)
Core.TypeFunction FunctionType
v254 -> ([String] -> String
Strings.cat [
[String] -> String
Strings.cat [
[String] -> String
Strings.cat [
String
"functions from ",
(Type -> String
describeType (FunctionType -> Type
Core.functionTypeDomain FunctionType
v254))],
String
" to "],
(Type -> String
describeType (FunctionType -> Type
Core.functionTypeCodomain FunctionType
v254))])
Core.TypeLambda LambdaType
_ -> String
"polymorphic terms"
Core.TypeList Type
v256 -> ([String] -> String
Strings.cat [
String
"lists of ",
(Type -> String
describeType Type
v256)])
Core.TypeMap MapType
v257 -> ([String] -> String
Strings.cat [
[String] -> String
Strings.cat [
[String] -> String
Strings.cat [
String
"maps from ",
(Type -> String
describeType (MapType -> Type
Core.mapTypeKeys MapType
v257))],
String
" to "],
(Type -> String
describeType (MapType -> Type
Core.mapTypeValues MapType
v257))])
Core.TypeOptional Type
v258 -> ([String] -> String
Strings.cat [
String
"optional ",
(Type -> String
describeType Type
v258)])
Core.TypeProduct [Type]
_ -> String
"tuples"
Core.TypeRecord RowType
_ -> String
"records"
Core.TypeSet Type
v261 -> ([String] -> String
Strings.cat [
String
"sets of ",
(Type -> String
describeType Type
v261)])
Core.TypeSum [Type]
_ -> String
"variant tuples"
Core.TypeUnion RowType
_ -> String
"unions"
Core.TypeVariable Name
_ -> String
"instances of a named type"
Core.TypeWrap WrappedType
v265 -> ([String] -> String
Strings.cat [
String
"wrapper for ",
(Type -> String
describeType (WrappedType -> Type
Core.wrappedTypeObject WrappedType
v265))])