module ProjectM36.DataTypes.List where
import ProjectM36.Base
import ProjectM36.DataTypes.Maybe
import ProjectM36.DataTypes.Primitive
import qualified Data.Map as M
import qualified Data.HashSet as HS
import ProjectM36.AtomFunctionError

listAtomType :: AtomType -> AtomType
listAtomType :: AtomType -> AtomType
listAtomType AtomType
arg = TypeConstructorName -> TypeVarMap -> AtomType
ConstructedAtomType TypeConstructorName
"List" (TypeConstructorName -> AtomType -> TypeVarMap
forall k a. k -> a -> Map k a
M.singleton TypeConstructorName
"a" AtomType
arg)

listTypeConstructorMapping :: TypeConstructorMapping
listTypeConstructorMapping :: TypeConstructorMapping
listTypeConstructorMapping = [(TypeConstructorName -> [TypeConstructorName] -> TypeConstructorDef
ADTypeConstructorDef TypeConstructorName
"List" [TypeConstructorName
"a"],
                           [TypeConstructorName
-> [DataConstructorDefArg] -> DataConstructorDef
DataConstructorDef TypeConstructorName
"Empty" [],
                           TypeConstructorName
-> [DataConstructorDefArg] -> DataConstructorDef
DataConstructorDef TypeConstructorName
"Cons" [TypeConstructorName -> DataConstructorDefArg
DataConstructorDefTypeVarNameArg TypeConstructorName
"a",
                                                      TypeConstructor -> DataConstructorDefArg
DataConstructorDefTypeConstructorArg (TypeConstructorName -> [TypeConstructor] -> TypeConstructor
forall a.
TypeConstructorName -> [TypeConstructor] -> TypeConstructorBase a
ADTypeConstructor TypeConstructorName
"List" [TypeConstructorName -> TypeConstructor
forall a. TypeConstructorName -> TypeConstructorBase a
TypeVariable TypeConstructorName
"a"])]])]
                         
listLength :: Atom -> Either AtomFunctionError Int                         
listLength :: Atom -> Either AtomFunctionError Int
listLength (ConstructedAtom TypeConstructorName
"Cons" AtomType
_ (Atom
_:Atom
nextCons:[Atom]
_)) = do
  Int
c <- Atom -> Either AtomFunctionError Int
listLength Atom
nextCons
  Int -> Either AtomFunctionError Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
listLength (ConstructedAtom TypeConstructorName
"Empty" AtomType
_ [Atom]
_) = Int -> Either AtomFunctionError Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
0
listLength Atom
_ = AtomFunctionError -> Either AtomFunctionError Int
forall a b. a -> Either a b
Left AtomFunctionError
AtomFunctionTypeMismatchError

listMaybeHead :: Atom -> Either AtomFunctionError Atom
listMaybeHead :: Atom -> Either AtomFunctionError Atom
listMaybeHead (ConstructedAtom TypeConstructorName
"Cons" AtomType
_ (Atom
val:[Atom]
_)) = Atom -> Either AtomFunctionError Atom
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TypeConstructorName -> AtomType -> [Atom] -> Atom
ConstructedAtom TypeConstructorName
"Just" AtomType
aType [Atom
val])
  where
    aType :: AtomType
aType = AtomType -> AtomType
maybeAtomType (Atom -> AtomType
atomTypeForAtom Atom
val)
listMaybeHead (ConstructedAtom TypeConstructorName
"Empty" (ConstructedAtomType TypeConstructorName
_ TypeVarMap
tvMap) [Atom]
_) =
  case TypeConstructorName -> TypeVarMap -> Maybe AtomType
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup TypeConstructorName
"a" TypeVarMap
tvMap of
    Maybe AtomType
Nothing -> AtomFunctionError -> Either AtomFunctionError Atom
forall a b. a -> Either a b
Left AtomFunctionError
AtomFunctionTypeMismatchError
    Just AtomType
aType -> Atom -> Either AtomFunctionError Atom
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TypeConstructorName -> AtomType -> [Atom] -> Atom
ConstructedAtom TypeConstructorName
"Nothing" AtomType
aType [])
listMaybeHead Atom
_ = AtomFunctionError -> Either AtomFunctionError Atom
forall a b. a -> Either a b
Left AtomFunctionError
AtomFunctionTypeMismatchError

listAtomFunctions :: AtomFunctions
listAtomFunctions :: AtomFunctions
listAtomFunctions = [Function ([Atom] -> Either AtomFunctionError Atom)]
-> AtomFunctions
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HS.fromList [
  Function :: forall a.
TypeConstructorName -> [AtomType] -> FunctionBody a -> Function a
Function {
     funcName :: TypeConstructorName
funcName = TypeConstructorName
"length",
     funcType :: [AtomType]
funcType = [AtomType -> AtomType
listAtomType (TypeConstructorName -> AtomType
TypeVariableType TypeConstructorName
"a"), AtomType
IntAtomType],
     funcBody :: FunctionBody ([Atom] -> Either AtomFunctionError Atom)
funcBody = ([Atom] -> Either AtomFunctionError Atom)
-> FunctionBody ([Atom] -> Either AtomFunctionError Atom)
forall a. a -> FunctionBody a
FunctionBuiltInBody (([Atom] -> Either AtomFunctionError Atom)
 -> FunctionBody ([Atom] -> Either AtomFunctionError Atom))
-> ([Atom] -> Either AtomFunctionError Atom)
-> FunctionBody ([Atom] -> Either AtomFunctionError Atom)
forall a b. (a -> b) -> a -> b
$
       \case
               (Atom
listAtom:[Atom]
_) ->
                 Int -> Atom
IntAtom (Int -> Atom) -> (Int -> Int) -> Int -> Atom
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Atom)
-> Either AtomFunctionError Int -> Either AtomFunctionError Atom
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Atom -> Either AtomFunctionError Int
listLength Atom
listAtom
               [Atom]
_ -> AtomFunctionError -> Either AtomFunctionError Atom
forall a b. a -> Either a b
Left AtomFunctionError
AtomFunctionTypeMismatchError
     },
  Function :: forall a.
TypeConstructorName -> [AtomType] -> FunctionBody a -> Function a
Function {
    funcName :: TypeConstructorName
funcName = TypeConstructorName
"maybeHead",
    funcType :: [AtomType]
funcType = [AtomType -> AtomType
listAtomType (TypeConstructorName -> AtomType
TypeVariableType TypeConstructorName
"a"), AtomType -> AtomType
maybeAtomType (TypeConstructorName -> AtomType
TypeVariableType TypeConstructorName
"a")],
    funcBody :: FunctionBody ([Atom] -> Either AtomFunctionError Atom)
funcBody = ([Atom] -> Either AtomFunctionError Atom)
-> FunctionBody ([Atom] -> Either AtomFunctionError Atom)
forall a. a -> FunctionBody a
FunctionBuiltInBody (([Atom] -> Either AtomFunctionError Atom)
 -> FunctionBody ([Atom] -> Either AtomFunctionError Atom))
-> ([Atom] -> Either AtomFunctionError Atom)
-> FunctionBody ([Atom] -> Either AtomFunctionError Atom)
forall a b. (a -> b) -> a -> b
$
               \case
                 (Atom
listAtom:[Atom]
_) -> Atom -> Either AtomFunctionError Atom
listMaybeHead Atom
listAtom
                 [Atom]
_ -> AtomFunctionError -> Either AtomFunctionError Atom
forall a b. a -> Either a b
Left AtomFunctionError
AtomFunctionTypeMismatchError
    }
  ]
                    
--just a private utility function
listCons :: AtomType -> [Atom] -> Atom
listCons :: AtomType -> [Atom] -> Atom
listCons AtomType
typ [] = TypeConstructorName -> AtomType -> [Atom] -> Atom
ConstructedAtom TypeConstructorName
"Empty" (AtomType -> AtomType
listAtomType AtomType
typ) []
listCons AtomType
typ (Atom
a:[Atom]
as) = TypeConstructorName -> AtomType -> [Atom] -> Atom
ConstructedAtom TypeConstructorName
"Cons" (AtomType -> AtomType
listAtomType AtomType
typ) [Atom
a, AtomType -> [Atom] -> Atom
listCons AtomType
typ [Atom]
as]