-- GeNeRaTeD fOr: ../../CBS/Funcons/Values/Primitive values/unit-type.aterm {-# LANGUAGE OverloadedStrings #-} module Funcons.Core.Values.PrimitiveValues.UnitType where import Funcons.EDSL entities = [] types = typeEnvFromList [("unit-type",DataTypeMembers [] [DataTypeConstructor "null" (TTuple [])])] funcons = libFromList [("is-null",StrictFuncon stepIs_null),("unit-type",NullaryFuncon stepUnit_type),("null",NullaryFuncon stepNull)] -- | -- /is-null/ tests an arbitrary value to determine if it is equal to /null/ . is_null_ fargs = FApp "is-null" (FTuple fargs) stepIs_null fargs = evalRules [rewrite1,rewrite2] [] where rewrite1 = do let env = emptyEnv env <- vsMatch fargs [PADT "null" []] env rewriteTo (FName "true") rewrite2 = do let env = emptyEnv env <- vsMatch fargs [VPMetaVar "V"] env env <- sideCondition (SCNotInSort (TVar "V") (TName "unit-type")) env rewriteTo (FName "false") stepNull = rewritten (ADTVal "null" []) stepUnit_type = rewriteType "unit-type" []