{- -----------------------------------------------------------------------------
Copyright 2019-2021 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,
  defaultCategories,
  defaultCategoryDeps,
  emptyType,
  floatRequiredValue,
  formattedRequiredValue,
  intRequiredValue,
  isPrimitiveType,
  orderOptionalValue,
  stringRequiredValue,
) where

import qualified Data.Map as Map
import qualified Data.Set as Set

import Base.GeneralType
import Base.Positional
import Types.TypeCategory
import Types.TypeInstance


defaultCategories :: CategoryMap c
defaultCategories :: CategoryMap c
defaultCategories = CategoryMap c
forall k a. Map k a
Map.empty

defaultCategoryDeps :: Set.Set CategoryName
defaultCategoryDeps :: Set CategoryName
defaultCategoryDeps = [CategoryName] -> Set CategoryName
forall a. Ord a => [a] -> Set a
Set.fromList []

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])

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

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

isPrimitiveType :: ValueType -> Bool
isPrimitiveType :: ValueType -> Bool
isPrimitiveType ValueType
t
  | ValueType
t ValueType -> ValueType -> Bool
forall a. Eq a => a -> a -> Bool
== ValueType
boolRequiredValue  = Bool
True
  | ValueType
t ValueType -> ValueType -> Bool
forall a. Eq a => a -> a -> Bool
== ValueType
intRequiredValue   = Bool
True
  | ValueType
t ValueType -> ValueType -> Bool
forall a. Eq a => a -> a -> Bool
== ValueType
floatRequiredValue = Bool
True
  | ValueType
t ValueType -> ValueType -> Bool
forall a. Eq a => a -> a -> Bool
== ValueType
charRequiredValue  = Bool
True
  | Bool
otherwise               = Bool
False

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
showList :: [ExpressionValue] -> ShowS
$cshowList :: [ExpressionValue] -> ShowS
show :: ExpressionValue -> String
$cshow :: ExpressionValue -> String
showsPrec :: Int -> ExpressionValue -> ShowS
$cshowsPrec :: Int -> ExpressionValue -> ShowS
Show)