{- -----------------------------------------------------------------------------
Copyright 2019-2023 Kevin P. Barry

Licensed under the Apache License, Version 2.0 (the "License");
you may not use this file except in compliance with the License.
You may obtain a copy of the License at

    http://www.apache.org/licenses/LICENSE-2.0

Unless required by applicable law or agreed to in writing, software
distributed under the License is distributed on an "AS IS" BASIS,
WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
See the License for the specific language governing permissions and
limitations under the License.
----------------------------------------------------------------------------- -}

-- Author: Kevin P. Barry [ta0kira@gmail.com]

{-# LANGUAGE Safe #-}

module Types.Builtin (
  ExpressionValue(..),
  PrimitiveType(..),
  boolRequiredValue,
  charRequiredValue,
  emptyType,
  floatRequiredValue,
  formattedRequiredValue,
  intRequiredValue,
  isIdentifierRequiredValue,
  isPointerRequiredValue,
  isOpaqueMulti,
  orderOptionalValue,
  requiredStaticTypes,
  stringRequiredValue,
) where

import qualified Data.Set as Set

import Base.GeneralType
import Base.MergeTree (reduceMergeTree)
import Base.Positional
import Types.TypeInstance


boolRequiredValue :: ValueType
boolRequiredValue :: ValueType
boolRequiredValue = CategoryName -> ValueType
requiredSingleton CategoryName
BuiltinBool
stringRequiredValue :: ValueType
stringRequiredValue :: ValueType
stringRequiredValue = CategoryName -> ValueType
requiredSingleton CategoryName
BuiltinString
charRequiredValue :: ValueType
charRequiredValue :: ValueType
charRequiredValue = CategoryName -> ValueType
requiredSingleton CategoryName
BuiltinChar
intRequiredValue :: ValueType
intRequiredValue :: ValueType
intRequiredValue = CategoryName -> ValueType
requiredSingleton CategoryName
BuiltinInt
floatRequiredValue :: ValueType
floatRequiredValue :: ValueType
floatRequiredValue = CategoryName -> ValueType
requiredSingleton CategoryName
BuiltinFloat
formattedRequiredValue :: ValueType
formattedRequiredValue :: ValueType
formattedRequiredValue = CategoryName -> ValueType
requiredSingleton CategoryName
BuiltinFormatted
orderOptionalValue :: GeneralInstance -> ValueType
orderOptionalValue :: GeneralInstance -> ValueType
orderOptionalValue GeneralInstance
t = StorageType -> GeneralInstance -> ValueType
ValueType StorageType
OptionalValue (GeneralInstance -> ValueType) -> GeneralInstance -> ValueType
forall a b. (a -> b) -> a -> b
$ TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance CategoryName
BuiltinOrder ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [GeneralInstance
t])

isPointerRequiredValue :: ValueType -> Bool
isPointerRequiredValue :: ValueType -> Bool
isPointerRequiredValue (ValueType StorageType
RequiredValue GeneralInstance
t) = Maybe TypeInstanceOrParam -> Bool
check (Maybe TypeInstanceOrParam -> Bool)
-> Maybe TypeInstanceOrParam -> Bool
forall a b. (a -> b) -> a -> b
$ GeneralInstance -> Maybe (T GeneralInstance)
extractSingle GeneralInstance
t where
  check :: Maybe TypeInstanceOrParam -> Bool
check (Just (JustTypeInstance (TypeInstance CategoryName
BuiltinPointer (Positional [GeneralInstance
_])))) = Bool
True
  check Maybe TypeInstanceOrParam
_ = Bool
False
  extractSingle :: GeneralInstance -> Maybe (T GeneralInstance)
extractSingle = ([Maybe (T GeneralInstance)] -> Maybe (T GeneralInstance))
-> ([Maybe (T GeneralInstance)] -> Maybe (T GeneralInstance))
-> (T GeneralInstance -> Maybe (T GeneralInstance))
-> GeneralInstance
-> Maybe (T GeneralInstance)
forall a b.
PreserveMerge a =>
([b] -> b) -> ([b] -> b) -> (T a -> b) -> a -> b
reduceMergeTree (Maybe (T GeneralInstance)
-> [Maybe (T GeneralInstance)] -> Maybe (T GeneralInstance)
forall a b. a -> b -> a
const Maybe (T GeneralInstance)
forall a. Maybe a
Nothing) (Maybe (T GeneralInstance)
-> [Maybe (T GeneralInstance)] -> Maybe (T GeneralInstance)
forall a b. a -> b -> a
const Maybe (T GeneralInstance)
forall a. Maybe a
Nothing) T GeneralInstance -> Maybe (T GeneralInstance)
forall a. a -> Maybe a
Just
isPointerRequiredValue ValueType
_ = Bool
False

isIdentifierRequiredValue :: ValueType -> Bool
isIdentifierRequiredValue :: ValueType -> Bool
isIdentifierRequiredValue (ValueType StorageType
RequiredValue GeneralInstance
t) = Maybe TypeInstanceOrParam -> Bool
check (Maybe TypeInstanceOrParam -> Bool)
-> Maybe TypeInstanceOrParam -> Bool
forall a b. (a -> b) -> a -> b
$ GeneralInstance -> Maybe (T GeneralInstance)
extractSingle GeneralInstance
t where
  check :: Maybe TypeInstanceOrParam -> Bool
check (Just (JustTypeInstance (TypeInstance CategoryName
BuiltinIdentifier (Positional [GeneralInstance
_])))) = Bool
True
  check Maybe TypeInstanceOrParam
_ = Bool
False
  extractSingle :: GeneralInstance -> Maybe (T GeneralInstance)
extractSingle = ([Maybe (T GeneralInstance)] -> Maybe (T GeneralInstance))
-> ([Maybe (T GeneralInstance)] -> Maybe (T GeneralInstance))
-> (T GeneralInstance -> Maybe (T GeneralInstance))
-> GeneralInstance
-> Maybe (T GeneralInstance)
forall a b.
PreserveMerge a =>
([b] -> b) -> ([b] -> b) -> (T a -> b) -> a -> b
reduceMergeTree (Maybe (T GeneralInstance)
-> [Maybe (T GeneralInstance)] -> Maybe (T GeneralInstance)
forall a b. a -> b -> a
const Maybe (T GeneralInstance)
forall a. Maybe a
Nothing) (Maybe (T GeneralInstance)
-> [Maybe (T GeneralInstance)] -> Maybe (T GeneralInstance)
forall a b. a -> b -> a
const Maybe (T GeneralInstance)
forall a. Maybe a
Nothing) T GeneralInstance -> Maybe (T GeneralInstance)
forall a. a -> Maybe a
Just
isIdentifierRequiredValue ValueType
_ = Bool
False

emptyType :: ValueType
emptyType :: ValueType
emptyType = StorageType -> GeneralInstance -> ValueType
ValueType StorageType
OptionalValue GeneralInstance
forall a. Bounded a => a
minBound

data PrimitiveType =
  PrimBool |
  PrimChar |
  PrimInt |
  PrimFloat |
  PrimString |
  PrimPointer |
  PrimIdentifier
  deriving (PrimitiveType -> PrimitiveType -> Bool
(PrimitiveType -> PrimitiveType -> Bool)
-> (PrimitiveType -> PrimitiveType -> Bool) -> Eq PrimitiveType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PrimitiveType -> PrimitiveType -> Bool
== :: PrimitiveType -> PrimitiveType -> Bool
$c/= :: PrimitiveType -> PrimitiveType -> Bool
/= :: PrimitiveType -> PrimitiveType -> Bool
Eq,Int -> PrimitiveType -> ShowS
[PrimitiveType] -> ShowS
PrimitiveType -> String
(Int -> PrimitiveType -> ShowS)
-> (PrimitiveType -> String)
-> ([PrimitiveType] -> ShowS)
-> Show PrimitiveType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PrimitiveType -> ShowS
showsPrec :: Int -> PrimitiveType -> ShowS
$cshow :: PrimitiveType -> String
show :: PrimitiveType -> String
$cshowList :: [PrimitiveType] -> ShowS
showList :: [PrimitiveType] -> ShowS
Show)

data ExpressionValue =
  -- Multi argument/return tuple.
  OpaqueMulti String |
  -- Single value that needs to be wrapped. (Can convert to UnwrappedSingle.)
  WrappedSingle String |
  -- Single value that will not be wrapped. (Can convert to WrappedSingle.)
  UnwrappedSingle String |
  -- Primitive value that needs to be boxed. (Can convert to UnboxedPrimitive.)
  BoxedPrimitive PrimitiveType String |
  -- Primitive value that will not be boxed. (Can convert to BoxedPrimitive.)
  UnboxedPrimitive PrimitiveType String |
  -- Value with lazy initialization. Requires indirection to get/set.
  LazySingle ExpressionValue
  deriving (Int -> ExpressionValue -> ShowS
[ExpressionValue] -> ShowS
ExpressionValue -> String
(Int -> ExpressionValue -> ShowS)
-> (ExpressionValue -> String)
-> ([ExpressionValue] -> ShowS)
-> Show ExpressionValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExpressionValue -> ShowS
showsPrec :: Int -> ExpressionValue -> ShowS
$cshow :: ExpressionValue -> String
show :: ExpressionValue -> String
$cshowList :: [ExpressionValue] -> ShowS
showList :: [ExpressionValue] -> ShowS
Show)

isOpaqueMulti :: ExpressionValue -> Bool
isOpaqueMulti :: ExpressionValue -> Bool
isOpaqueMulti (OpaqueMulti String
_) = Bool
True
isOpaqueMulti ExpressionValue
_               = Bool
False

requiredStaticTypes :: Set.Set CategoryName
requiredStaticTypes :: Set CategoryName
requiredStaticTypes = [CategoryName] -> Set CategoryName
forall a. Ord a => [a] -> Set a
Set.fromList [
    CategoryName
BuiltinBool,
    CategoryName
BuiltinChar,
    CategoryName
BuiltinInt,
    CategoryName
BuiltinFloat,
    CategoryName
BuiltinPointer,
    CategoryName
BuiltinIdentifier
  ]