module Hydra.Basics where
import qualified Hydra.Core as Core
import qualified Hydra.Graph as Graph
import qualified Hydra.Lib.Equality as Equality
import qualified Hydra.Lib.Lists as Lists
import qualified Hydra.Lib.Logic as Logic
import qualified Hydra.Lib.Maps as Maps
import qualified Hydra.Lib.Strings as Strings
import qualified Hydra.Mantle as Mantle
import qualified Hydra.Module as Module
import qualified Hydra.Strip as Strip
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S
eliminationVariant :: (Core.Elimination -> Mantle.EliminationVariant)
eliminationVariant :: Elimination -> EliminationVariant
eliminationVariant Elimination
x = case Elimination
x of
Core.EliminationList Term
_ -> EliminationVariant
Mantle.EliminationVariantList
Core.EliminationOptional OptionalCases
_ -> EliminationVariant
Mantle.EliminationVariantOptional
Core.EliminationProduct TupleProjection
_ -> EliminationVariant
Mantle.EliminationVariantProduct
Core.EliminationRecord Projection
_ -> EliminationVariant
Mantle.EliminationVariantRecord
Core.EliminationUnion CaseStatement
_ -> EliminationVariant
Mantle.EliminationVariantUnion
Core.EliminationWrap Name
_ -> EliminationVariant
Mantle.EliminationVariantWrap
eliminationVariants :: [Mantle.EliminationVariant]
eliminationVariants :: [EliminationVariant]
eliminationVariants = [
EliminationVariant
Mantle.EliminationVariantList,
EliminationVariant
Mantle.EliminationVariantWrap,
EliminationVariant
Mantle.EliminationVariantOptional,
EliminationVariant
Mantle.EliminationVariantProduct,
EliminationVariant
Mantle.EliminationVariantRecord,
EliminationVariant
Mantle.EliminationVariantUnion]
floatTypePrecision :: (Core.FloatType -> Mantle.Precision)
floatTypePrecision :: FloatType -> Precision
floatTypePrecision FloatType
x = case FloatType
x of
FloatType
Core.FloatTypeBigfloat -> Precision
Mantle.PrecisionArbitrary
FloatType
Core.FloatTypeFloat32 -> (Int -> Precision
Mantle.PrecisionBits Int
32)
FloatType
Core.FloatTypeFloat64 -> (Int -> Precision
Mantle.PrecisionBits Int
64)
floatTypes :: [Core.FloatType]
floatTypes :: [FloatType]
floatTypes = [
FloatType
Core.FloatTypeBigfloat,
FloatType
Core.FloatTypeFloat32,
FloatType
Core.FloatTypeFloat64]
floatValueType :: (Core.FloatValue -> Core.FloatType)
floatValueType :: FloatValue -> FloatType
floatValueType FloatValue
x = case FloatValue
x of
Core.FloatValueBigfloat Double
_ -> FloatType
Core.FloatTypeBigfloat
Core.FloatValueFloat32 Float
_ -> FloatType
Core.FloatTypeFloat32
Core.FloatValueFloat64 Double
_ -> FloatType
Core.FloatTypeFloat64
functionVariant :: (Core.Function -> Mantle.FunctionVariant)
functionVariant :: Function -> FunctionVariant
functionVariant Function
x = case Function
x of
Core.FunctionElimination Elimination
_ -> FunctionVariant
Mantle.FunctionVariantElimination
Core.FunctionLambda Lambda
_ -> FunctionVariant
Mantle.FunctionVariantLambda
Core.FunctionPrimitive Name
_ -> FunctionVariant
Mantle.FunctionVariantPrimitive
functionVariants :: [Mantle.FunctionVariant]
functionVariants :: [FunctionVariant]
functionVariants = [
FunctionVariant
Mantle.FunctionVariantElimination,
FunctionVariant
Mantle.FunctionVariantLambda,
FunctionVariant
Mantle.FunctionVariantPrimitive]
id_ :: (a -> a)
id_ :: forall a. a -> a
id_ a
x = a
x
integerTypeIsSigned :: (Core.IntegerType -> Bool)
integerTypeIsSigned :: IntegerType -> Bool
integerTypeIsSigned IntegerType
x = case IntegerType
x of
IntegerType
Core.IntegerTypeBigint -> Bool
True
IntegerType
Core.IntegerTypeInt8 -> Bool
True
IntegerType
Core.IntegerTypeInt16 -> Bool
True
IntegerType
Core.IntegerTypeInt32 -> Bool
True
IntegerType
Core.IntegerTypeInt64 -> Bool
True
IntegerType
Core.IntegerTypeUint8 -> Bool
False
IntegerType
Core.IntegerTypeUint16 -> Bool
False
IntegerType
Core.IntegerTypeUint32 -> Bool
False
IntegerType
Core.IntegerTypeUint64 -> Bool
False
integerTypePrecision :: (Core.IntegerType -> Mantle.Precision)
integerTypePrecision :: IntegerType -> Precision
integerTypePrecision IntegerType
x = case IntegerType
x of
IntegerType
Core.IntegerTypeBigint -> Precision
Mantle.PrecisionArbitrary
IntegerType
Core.IntegerTypeInt8 -> (Int -> Precision
Mantle.PrecisionBits Int
8)
IntegerType
Core.IntegerTypeInt16 -> (Int -> Precision
Mantle.PrecisionBits Int
16)
IntegerType
Core.IntegerTypeInt32 -> (Int -> Precision
Mantle.PrecisionBits Int
32)
IntegerType
Core.IntegerTypeInt64 -> (Int -> Precision
Mantle.PrecisionBits Int
64)
IntegerType
Core.IntegerTypeUint8 -> (Int -> Precision
Mantle.PrecisionBits Int
8)
IntegerType
Core.IntegerTypeUint16 -> (Int -> Precision
Mantle.PrecisionBits Int
16)
IntegerType
Core.IntegerTypeUint32 -> (Int -> Precision
Mantle.PrecisionBits Int
32)
IntegerType
Core.IntegerTypeUint64 -> (Int -> Precision
Mantle.PrecisionBits Int
64)
integerTypes :: [Core.IntegerType]
integerTypes :: [IntegerType]
integerTypes = [
IntegerType
Core.IntegerTypeBigint,
IntegerType
Core.IntegerTypeInt8,
IntegerType
Core.IntegerTypeInt16,
IntegerType
Core.IntegerTypeInt32,
IntegerType
Core.IntegerTypeInt64,
IntegerType
Core.IntegerTypeUint8,
IntegerType
Core.IntegerTypeUint16,
IntegerType
Core.IntegerTypeUint32,
IntegerType
Core.IntegerTypeUint64]
integerValueType :: (Core.IntegerValue -> Core.IntegerType)
integerValueType :: IntegerValue -> IntegerType
integerValueType IntegerValue
x = case IntegerValue
x of
Core.IntegerValueBigint Integer
_ -> IntegerType
Core.IntegerTypeBigint
Core.IntegerValueInt8 Int8
_ -> IntegerType
Core.IntegerTypeInt8
Core.IntegerValueInt16 Int16
_ -> IntegerType
Core.IntegerTypeInt16
Core.IntegerValueInt32 Int
_ -> IntegerType
Core.IntegerTypeInt32
Core.IntegerValueInt64 Int64
_ -> IntegerType
Core.IntegerTypeInt64
Core.IntegerValueUint8 Int16
_ -> IntegerType
Core.IntegerTypeUint8
Core.IntegerValueUint16 Int
_ -> IntegerType
Core.IntegerTypeUint16
Core.IntegerValueUint32 Int64
_ -> IntegerType
Core.IntegerTypeUint32
Core.IntegerValueUint64 Integer
_ -> IntegerType
Core.IntegerTypeUint64
literalType :: (Core.Literal -> Core.LiteralType)
literalType :: Literal -> LiteralType
literalType Literal
x = case Literal
x of
Core.LiteralBinary String
_ -> LiteralType
Core.LiteralTypeBinary
Core.LiteralBoolean Bool
_ -> LiteralType
Core.LiteralTypeBoolean
Core.LiteralFloat FloatValue
v228 -> ((\FloatType
x2 -> FloatType -> LiteralType
Core.LiteralTypeFloat FloatType
x2) (FloatValue -> FloatType
floatValueType FloatValue
v228))
Core.LiteralInteger IntegerValue
v229 -> ((\IntegerType
x2 -> IntegerType -> LiteralType
Core.LiteralTypeInteger IntegerType
x2) (IntegerValue -> IntegerType
integerValueType IntegerValue
v229))
Core.LiteralString String
_ -> LiteralType
Core.LiteralTypeString
literalTypeVariant :: (Core.LiteralType -> Mantle.LiteralVariant)
literalTypeVariant :: LiteralType -> LiteralVariant
literalTypeVariant LiteralType
x = case LiteralType
x of
LiteralType
Core.LiteralTypeBinary -> LiteralVariant
Mantle.LiteralVariantBinary
LiteralType
Core.LiteralTypeBoolean -> LiteralVariant
Mantle.LiteralVariantBoolean
Core.LiteralTypeFloat FloatType
_ -> LiteralVariant
Mantle.LiteralVariantFloat
Core.LiteralTypeInteger IntegerType
_ -> LiteralVariant
Mantle.LiteralVariantInteger
LiteralType
Core.LiteralTypeString -> LiteralVariant
Mantle.LiteralVariantString
literalVariant :: (Core.Literal -> Mantle.LiteralVariant)
literalVariant :: Literal -> LiteralVariant
literalVariant Literal
x = (LiteralType -> LiteralVariant
literalTypeVariant (Literal -> LiteralType
literalType Literal
x))
literalVariants :: [Mantle.LiteralVariant]
literalVariants :: [LiteralVariant]
literalVariants = [
LiteralVariant
Mantle.LiteralVariantBinary,
LiteralVariant
Mantle.LiteralVariantBoolean,
LiteralVariant
Mantle.LiteralVariantFloat,
LiteralVariant
Mantle.LiteralVariantInteger,
LiteralVariant
Mantle.LiteralVariantString]
termVariant :: (Core.Term -> Mantle.TermVariant)
termVariant :: Term -> TermVariant
termVariant Term
x = case Term
x of
Core.TermAnnotated AnnotatedTerm
_ -> TermVariant
Mantle.TermVariantAnnotated
Core.TermApplication Application
_ -> TermVariant
Mantle.TermVariantApplication
Core.TermFunction Function
_ -> TermVariant
Mantle.TermVariantFunction
Core.TermLet Let
_ -> TermVariant
Mantle.TermVariantLet
Core.TermList [Term]
_ -> TermVariant
Mantle.TermVariantList
Core.TermLiteral Literal
_ -> TermVariant
Mantle.TermVariantLiteral
Core.TermMap Map Term Term
_ -> TermVariant
Mantle.TermVariantMap
Core.TermOptional Maybe Term
_ -> TermVariant
Mantle.TermVariantOptional
Core.TermProduct [Term]
_ -> TermVariant
Mantle.TermVariantProduct
Core.TermRecord Record
_ -> TermVariant
Mantle.TermVariantRecord
Core.TermSet Set Term
_ -> TermVariant
Mantle.TermVariantSet
Core.TermSum Sum
_ -> TermVariant
Mantle.TermVariantSum
Core.TermTypeAbstraction TypeAbstraction
_ -> TermVariant
Mantle.TermVariantTypeAbstraction
Core.TermTypeApplication TypedTerm
_ -> TermVariant
Mantle.TermVariantTypeApplication
Core.TermTyped TypedTerm
_ -> TermVariant
Mantle.TermVariantTyped
Core.TermUnion Injection
_ -> TermVariant
Mantle.TermVariantUnion
Core.TermVariable Name
_ -> TermVariant
Mantle.TermVariantVariable
Core.TermWrap WrappedTerm
_ -> TermVariant
Mantle.TermVariantWrap
termVariants :: [Mantle.TermVariant]
termVariants :: [TermVariant]
termVariants = [
TermVariant
Mantle.TermVariantAnnotated,
TermVariant
Mantle.TermVariantApplication,
TermVariant
Mantle.TermVariantLiteral,
TermVariant
Mantle.TermVariantFunction,
TermVariant
Mantle.TermVariantList,
TermVariant
Mantle.TermVariantMap,
TermVariant
Mantle.TermVariantOptional,
TermVariant
Mantle.TermVariantProduct,
TermVariant
Mantle.TermVariantRecord,
TermVariant
Mantle.TermVariantSet,
TermVariant
Mantle.TermVariantSum,
TermVariant
Mantle.TermVariantTypeAbstraction,
TermVariant
Mantle.TermVariantTypeApplication,
TermVariant
Mantle.TermVariantTyped,
TermVariant
Mantle.TermVariantUnion,
TermVariant
Mantle.TermVariantVariable,
TermVariant
Mantle.TermVariantWrap]
typeVariant :: (Core.Type -> Mantle.TypeVariant)
typeVariant :: Type -> TypeVariant
typeVariant Type
x = case Type
x of
Core.TypeAnnotated AnnotatedType
_ -> TypeVariant
Mantle.TypeVariantAnnotated
Core.TypeApplication ApplicationType
_ -> TypeVariant
Mantle.TypeVariantApplication
Core.TypeFunction FunctionType
_ -> TypeVariant
Mantle.TypeVariantFunction
Core.TypeLambda LambdaType
_ -> TypeVariant
Mantle.TypeVariantLambda
Core.TypeList Type
_ -> TypeVariant
Mantle.TypeVariantList
Core.TypeLiteral LiteralType
_ -> TypeVariant
Mantle.TypeVariantLiteral
Core.TypeMap MapType
_ -> TypeVariant
Mantle.TypeVariantMap
Core.TypeOptional Type
_ -> TypeVariant
Mantle.TypeVariantOptional
Core.TypeProduct [Type]
_ -> TypeVariant
Mantle.TypeVariantProduct
Core.TypeRecord RowType
_ -> TypeVariant
Mantle.TypeVariantRecord
Core.TypeSet Type
_ -> TypeVariant
Mantle.TypeVariantSet
Core.TypeSum [Type]
_ -> TypeVariant
Mantle.TypeVariantSum
Core.TypeUnion RowType
_ -> TypeVariant
Mantle.TypeVariantUnion
Core.TypeVariable Name
_ -> TypeVariant
Mantle.TypeVariantVariable
Core.TypeWrap WrappedType
_ -> TypeVariant
Mantle.TypeVariantWrap
typeVariants :: [Mantle.TypeVariant]
typeVariants :: [TypeVariant]
typeVariants = [
TypeVariant
Mantle.TypeVariantAnnotated,
TypeVariant
Mantle.TypeVariantApplication,
TypeVariant
Mantle.TypeVariantFunction,
TypeVariant
Mantle.TypeVariantLambda,
TypeVariant
Mantle.TypeVariantList,
TypeVariant
Mantle.TypeVariantLiteral,
TypeVariant
Mantle.TypeVariantMap,
TypeVariant
Mantle.TypeVariantWrap,
TypeVariant
Mantle.TypeVariantOptional,
TypeVariant
Mantle.TypeVariantProduct,
TypeVariant
Mantle.TypeVariantRecord,
TypeVariant
Mantle.TypeVariantSet,
TypeVariant
Mantle.TypeVariantSum,
TypeVariant
Mantle.TypeVariantUnion,
TypeVariant
Mantle.TypeVariantVariable]
capitalize :: (String -> String)
capitalize :: String -> String
capitalize = ((String -> String) -> String -> String
mapFirstLetter String -> String
Strings.toUpper)
decapitalize :: (String -> String)
decapitalize :: String -> String
decapitalize = ((String -> String) -> String -> String
mapFirstLetter String -> String
Strings.toLower)
mapFirstLetter :: ((String -> String) -> String -> String)
mapFirstLetter :: (String -> String) -> String -> String
mapFirstLetter String -> String
mapping String
s =
let firstLetter :: String
firstLetter = (String -> String
mapping ([Int] -> String
Strings.fromList (Int -> [Int]
forall a. a -> [a]
Lists.pure ([Int] -> Int
forall a. [a] -> a
Lists.head [Int]
list))))
list :: [Int]
list = (String -> [Int]
Strings.toList String
s)
in (String -> String -> Bool -> String
forall a. a -> a -> Bool -> a
Logic.ifElse String
s (String -> String -> String
Strings.cat2 String
firstLetter ([Int] -> String
Strings.fromList ([Int] -> [Int]
forall a. [a] -> [a]
Lists.tail [Int]
list))) (String -> Bool
Strings.isEmpty String
s))
fieldMap :: ([Core.Field] -> Map Core.Name Core.Term)
fieldMap :: [Field] -> Map Name Term
fieldMap [Field]
fields = ([(Name, Term)] -> Map Name Term
forall k v. Ord k => [(k, v)] -> Map k v
Maps.fromList ((Field -> (Name, Term)) -> [Field] -> [(Name, Term)]
forall a b. (a -> b) -> [a] -> [b]
Lists.map Field -> (Name, Term)
toPair [Field]
fields))
where
toPair :: Field -> (Name, Term)
toPair = (\Field
f -> (Field -> Name
Core.fieldName Field
f, (Field -> Term
Core.fieldTerm Field
f)))
fieldTypeMap :: ([Core.FieldType] -> Map Core.Name Core.Type)
fieldTypeMap :: [FieldType] -> Map Name Type
fieldTypeMap [FieldType]
fields = ([(Name, Type)] -> Map Name Type
forall k v. Ord k => [(k, v)] -> Map k v
Maps.fromList ((FieldType -> (Name, Type)) -> [FieldType] -> [(Name, Type)]
forall a b. (a -> b) -> [a] -> [b]
Lists.map FieldType -> (Name, Type)
toPair [FieldType]
fields))
where
toPair :: FieldType -> (Name, Type)
toPair = (\FieldType
f -> (FieldType -> Name
Core.fieldTypeName FieldType
f, (FieldType -> Type
Core.fieldTypeType FieldType
f)))
isEncodedType :: (Core.Term -> Bool)
isEncodedType :: Term -> Bool
isEncodedType Term
t = ((\Term
x -> case Term
x of
Core.TermApplication Application
v269 -> (Term -> Bool
isEncodedType (Application -> Term
Core.applicationFunction Application
v269))
Core.TermUnion Injection
v270 -> (String -> String -> Bool
Equality.equalString String
"hydra/core.Type" (Name -> String
Core.unName (Injection -> Name
Core.injectionTypeName Injection
v270)))
Term
_ -> Bool
False) (Term -> Term
Strip.stripTerm Term
t))
isType :: (Core.Type -> Bool)
isType :: Type -> Bool
isType Type
t = ((\Type
x -> case Type
x of
Core.TypeApplication ApplicationType
v271 -> (Type -> Bool
isType (ApplicationType -> Type
Core.applicationTypeFunction ApplicationType
v271))
Core.TypeLambda LambdaType
v272 -> (Type -> Bool
isType (LambdaType -> Type
Core.lambdaTypeBody LambdaType
v272))
Core.TypeUnion RowType
v273 -> (String -> String -> Bool
Equality.equalString String
"hydra/core.Type" (Name -> String
Core.unName (RowType -> Name
Core.rowTypeTypeName RowType
v273)))
Type
_ -> Bool
False) (Type -> Type
Strip.stripType Type
t))
isUnitTerm :: (Core.Term -> Bool)
isUnitTerm :: Term -> Bool
isUnitTerm Term
t = (Term -> Term -> Bool
Equality.equalTerm (Term -> Term
Strip.fullyStripTerm Term
t) (Record -> Term
Core.TermRecord (Core.Record {
recordTypeName :: Name
Core.recordTypeName = (String -> Name
Core.Name String
"hydra/core.Unit"),
recordFields :: [Field]
Core.recordFields = []})))
isUnitType :: (Core.Type -> Bool)
isUnitType :: Type -> Bool
isUnitType Type
t = (Type -> Type -> Bool
Equality.equalType (Type -> Type
Strip.stripType Type
t) (RowType -> Type
Core.TypeRecord (Core.RowType {
rowTypeTypeName :: Name
Core.rowTypeTypeName = (String -> Name
Core.Name String
"hydra/core.Unit"),
rowTypeFields :: [FieldType]
Core.rowTypeFields = []})))
elementsToGraph :: (Graph.Graph -> Maybe Graph.Graph -> [Graph.Element] -> Graph.Graph)
elementsToGraph :: Graph -> Maybe Graph -> [Element] -> Graph
elementsToGraph Graph
parent Maybe Graph
schema [Element]
elements =
let toPair :: Element -> (Name, Element)
toPair = (\Element
el -> (Element -> Name
Graph.elementName Element
el, Element
el))
in Graph.Graph {
graphElements :: Map Name Element
Graph.graphElements = ([(Name, Element)] -> Map Name Element
forall k v. Ord k => [(k, v)] -> Map k v
Maps.fromList ((Element -> (Name, Element)) -> [Element] -> [(Name, Element)]
forall a b. (a -> b) -> [a] -> [b]
Lists.map Element -> (Name, Element)
toPair [Element]
elements)),
graphEnvironment :: Map Name (Maybe Term)
Graph.graphEnvironment = (Graph -> Map Name (Maybe Term)
Graph.graphEnvironment Graph
parent),
graphTypes :: Map Name TypeScheme
Graph.graphTypes = (Graph -> Map Name TypeScheme
Graph.graphTypes Graph
parent),
graphBody :: Term
Graph.graphBody = (Graph -> Term
Graph.graphBody Graph
parent),
graphPrimitives :: Map Name Primitive
Graph.graphPrimitives = (Graph -> Map Name Primitive
Graph.graphPrimitives Graph
parent),
graphSchema :: Maybe Graph
Graph.graphSchema = Maybe Graph
schema}
localNameOfEager :: (Core.Name -> String)
localNameOfEager :: Name -> String
localNameOfEager Name
x = (QualifiedName -> String
Module.qualifiedNameLocal (Name -> QualifiedName
qualifyNameEager Name
x))
localNameOfLazy :: (Core.Name -> String)
localNameOfLazy :: Name -> String
localNameOfLazy Name
x = (QualifiedName -> String
Module.qualifiedNameLocal (Name -> QualifiedName
qualifyNameLazy Name
x))
namespaceOfEager :: (Core.Name -> Maybe Module.Namespace)
namespaceOfEager :: Name -> Maybe Namespace
namespaceOfEager Name
x = (QualifiedName -> Maybe Namespace
Module.qualifiedNameNamespace (Name -> QualifiedName
qualifyNameEager Name
x))
namespaceOfLazy :: (Core.Name -> Maybe Module.Namespace)
namespaceOfLazy :: Name -> Maybe Namespace
namespaceOfLazy Name
x = (QualifiedName -> Maybe Namespace
Module.qualifiedNameNamespace (Name -> QualifiedName
qualifyNameLazy Name
x))
namespaceToFilePath :: (Bool -> Module.FileExtension -> Module.Namespace -> String)
namespaceToFilePath :: Bool -> FileExtension -> Namespace -> String
namespaceToFilePath Bool
caps FileExtension
ext Namespace
ns =
let parts :: [String]
parts = ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
Lists.map ((String -> String)
-> (String -> String) -> Bool -> String -> String
forall a. a -> a -> Bool -> a
Logic.ifElse String -> String
capitalize String -> String
forall a. a -> a
id_ Bool
caps) (String -> String -> [String]
Strings.splitOn String
"/" (Namespace -> String
Module.unNamespace Namespace
ns)))
in ([String] -> String
Strings.cat [
[String] -> String
Strings.cat [
String -> [String] -> String
Strings.intercalate String
"/" [String]
parts,
String
"."],
(FileExtension -> String
Module.unFileExtension FileExtension
ext)])
qualifyNameEager :: (Core.Name -> Module.QualifiedName)
qualifyNameEager :: Name -> QualifiedName
qualifyNameEager Name
name =
let parts :: [String]
parts = (String -> String -> [String]
Strings.splitOn String
"." (Name -> String
Core.unName Name
name))
in (QualifiedName -> QualifiedName -> Bool -> QualifiedName
forall a. a -> a -> Bool -> a
Logic.ifElse (Module.QualifiedName {
qualifiedNameNamespace :: Maybe Namespace
Module.qualifiedNameNamespace = Maybe Namespace
forall a. Maybe a
Nothing,
qualifiedNameLocal :: String
Module.qualifiedNameLocal = (Name -> String
Core.unName Name
name)}) (Module.QualifiedName {
qualifiedNameNamespace :: Maybe Namespace
Module.qualifiedNameNamespace = (Namespace -> Maybe Namespace
forall a. a -> Maybe a
Just (String -> Namespace
Module.Namespace ([String] -> String
forall a. [a] -> a
Lists.head [String]
parts))),
qualifiedNameLocal :: String
Module.qualifiedNameLocal = (String -> [String] -> String
Strings.intercalate String
"." ([String] -> [String]
forall a. [a] -> [a]
Lists.tail [String]
parts))}) (Int -> Int -> Bool
Equality.equalInt32 Int
1 ([String] -> Int
forall a. [a] -> Int
Lists.length [String]
parts)))
qualifyNameLazy :: (Core.Name -> Module.QualifiedName)
qualifyNameLazy :: Name -> QualifiedName
qualifyNameLazy Name
name =
let parts :: [String]
parts = ([String] -> [String]
forall a. [a] -> [a]
Lists.reverse (String -> String -> [String]
Strings.splitOn String
"." (Name -> String
Core.unName Name
name)))
in (QualifiedName -> QualifiedName -> Bool -> QualifiedName
forall a. a -> a -> Bool -> a
Logic.ifElse (Module.QualifiedName {
qualifiedNameNamespace :: Maybe Namespace
Module.qualifiedNameNamespace = Maybe Namespace
forall a. Maybe a
Nothing,
qualifiedNameLocal :: String
Module.qualifiedNameLocal = (Name -> String
Core.unName Name
name)}) (Module.QualifiedName {
qualifiedNameNamespace :: Maybe Namespace
Module.qualifiedNameNamespace = (Namespace -> Maybe Namespace
forall a. a -> Maybe a
Just (String -> Namespace
Module.Namespace (String -> [String] -> String
Strings.intercalate String
"." ([String] -> [String]
forall a. [a] -> [a]
Lists.reverse ([String] -> [String]
forall a. [a] -> [a]
Lists.tail [String]
parts))))),
qualifiedNameLocal :: String
Module.qualifiedNameLocal = ([String] -> String
forall a. [a] -> a
Lists.head [String]
parts)}) (Int -> Int -> Bool
Equality.equalInt32 Int
1 ([String] -> Int
forall a. [a] -> Int
Lists.length [String]
parts)))