Carp/src/Reify.hs

64 lines
2.3 KiB
Haskell
Raw Permalink Normal View History

{-# LANGUAGE FlexibleInstances #-}
Enhance type reflection; get types of values, get kinds Extends Carp's support for type reflection by returning types for values as well as bindings. `type` now also returns a valid Carp expression/s-expression and so its output can be used as input to dynamic functions and macros (prior to this commit, `type` printed the type to the REPL but did not return a meaningful expression in Carp). Here are a few illustrations of the behavior: ``` (def x 1) ;; type now returns an s-expression/symbol (type x) => Int ;; It also works on values (type 1) => Int (type 2b) => Byte (type "foo") => (Ref String <StaticLifetime>) ;; It works on more complex values as well (type Maybe) => Module (type Maybe.Just) (Fn [a] (Maybe a) <StaticLifetime>) ;; reports honestly about polymorphism (type (Maybe.Nothing)) => (Maybe a) (type (Pair.init 1 2)) => (Pair Int Int) ;; What about the type of types? (type (type 2)) => Type ;; Or the type of types of types? (type (type (type 2))) => () ;; One more time! (type (type (type (type 2)))) => () ;; so, () is the fixpoint of type, and is reached after two applications (type zero) ;; the type of an interface is all of its implementations => (((Fn [] (Array a) <StaticLifetime>) (Fn [] Bool <StaticLifetime>) (Fn [] Byte <StaticLifetime>) (Fn [] Char <StaticLifetime>) (Fn [] Double <StaticLifetime>) (Fn [] Float <StaticLifetime>) (Fn [] Int <StaticLifetime>) (Fn [] Int16 <StaticLifetime>) (Fn [] Int32 <StaticLifetime>) (Fn [] Int64 <StaticLifetime>) (Fn [] Int8 <StaticLifetime>) (Fn [] Long <StaticLifetime>) (Fn [] (Maybe a) <StaticLifetime>) (Fn [] (Pair a b) <StaticLifetime>) (Fn [] (Quadruple a b c d) <StaticLifetime>) (Fn [] String <StaticLifetime>) (Fn [] (Triple a b c) <StaticLifetime>) (Fn [] Uint16 <StaticLifetime>) (Fn [] Uint32 <StaticLifetime>) (Fn [] Uint64 <StaticLifetime>) (Fn [] Uint8 <StaticLifetime>))) ``` As shown in the example above, this change also includes a cosmetic update to the representation of lifetime variables, which are surrounded in <> to distinguish them from type variables. This commit also adds a new `kind` primitive that reports on the kind of a binding or value: ``` (def x 3) (kind x) => Base (kind 2) => Base (kind Maybe.Just) => Higher (kind (Maybe.Just 2)) => Higher ``` `kind` and `type` both support interactive development in the repl, for example, a user can rely on `kind` to check the kind of a type they plan on using in an interface that demands a higher-kinded argument. Likewise, they both also support developing macros based on type information.
2020-10-03 00:48:58 +03:00
-- | Module Reify provides a typeclass and instances for turning internal compiler types and data into
-- corresponding representations in the Carp language.
module Reify where
import Info
Enhance type reflection; get types of values, get kinds Extends Carp's support for type reflection by returning types for values as well as bindings. `type` now also returns a valid Carp expression/s-expression and so its output can be used as input to dynamic functions and macros (prior to this commit, `type` printed the type to the REPL but did not return a meaningful expression in Carp). Here are a few illustrations of the behavior: ``` (def x 1) ;; type now returns an s-expression/symbol (type x) => Int ;; It also works on values (type 1) => Int (type 2b) => Byte (type "foo") => (Ref String <StaticLifetime>) ;; It works on more complex values as well (type Maybe) => Module (type Maybe.Just) (Fn [a] (Maybe a) <StaticLifetime>) ;; reports honestly about polymorphism (type (Maybe.Nothing)) => (Maybe a) (type (Pair.init 1 2)) => (Pair Int Int) ;; What about the type of types? (type (type 2)) => Type ;; Or the type of types of types? (type (type (type 2))) => () ;; One more time! (type (type (type (type 2)))) => () ;; so, () is the fixpoint of type, and is reached after two applications (type zero) ;; the type of an interface is all of its implementations => (((Fn [] (Array a) <StaticLifetime>) (Fn [] Bool <StaticLifetime>) (Fn [] Byte <StaticLifetime>) (Fn [] Char <StaticLifetime>) (Fn [] Double <StaticLifetime>) (Fn [] Float <StaticLifetime>) (Fn [] Int <StaticLifetime>) (Fn [] Int16 <StaticLifetime>) (Fn [] Int32 <StaticLifetime>) (Fn [] Int64 <StaticLifetime>) (Fn [] Int8 <StaticLifetime>) (Fn [] Long <StaticLifetime>) (Fn [] (Maybe a) <StaticLifetime>) (Fn [] (Pair a b) <StaticLifetime>) (Fn [] (Quadruple a b c d) <StaticLifetime>) (Fn [] String <StaticLifetime>) (Fn [] (Triple a b c) <StaticLifetime>) (Fn [] Uint16 <StaticLifetime>) (Fn [] Uint32 <StaticLifetime>) (Fn [] Uint64 <StaticLifetime>) (Fn [] Uint8 <StaticLifetime>))) ``` As shown in the example above, this change also includes a cosmetic update to the representation of lifetime variables, which are surrounded in <> to distinguish them from type variables. This commit also adds a new `kind` primitive that reports on the kind of a binding or value: ``` (def x 3) (kind x) => Base (kind 2) => Base (kind Maybe.Just) => Higher (kind (Maybe.Just 2)) => Higher ``` `kind` and `type` both support interactive development in the repl, for example, a user can rely on `kind` to check the kind of a type they plan on using in an interface that demands a higher-kinded argument. Likewise, they both also support developing macros based on type information.
2020-10-03 00:48:58 +03:00
import Obj
import System.FilePath
import Types
Enhance type reflection; get types of values, get kinds Extends Carp's support for type reflection by returning types for values as well as bindings. `type` now also returns a valid Carp expression/s-expression and so its output can be used as input to dynamic functions and macros (prior to this commit, `type` printed the type to the REPL but did not return a meaningful expression in Carp). Here are a few illustrations of the behavior: ``` (def x 1) ;; type now returns an s-expression/symbol (type x) => Int ;; It also works on values (type 1) => Int (type 2b) => Byte (type "foo") => (Ref String <StaticLifetime>) ;; It works on more complex values as well (type Maybe) => Module (type Maybe.Just) (Fn [a] (Maybe a) <StaticLifetime>) ;; reports honestly about polymorphism (type (Maybe.Nothing)) => (Maybe a) (type (Pair.init 1 2)) => (Pair Int Int) ;; What about the type of types? (type (type 2)) => Type ;; Or the type of types of types? (type (type (type 2))) => () ;; One more time! (type (type (type (type 2)))) => () ;; so, () is the fixpoint of type, and is reached after two applications (type zero) ;; the type of an interface is all of its implementations => (((Fn [] (Array a) <StaticLifetime>) (Fn [] Bool <StaticLifetime>) (Fn [] Byte <StaticLifetime>) (Fn [] Char <StaticLifetime>) (Fn [] Double <StaticLifetime>) (Fn [] Float <StaticLifetime>) (Fn [] Int <StaticLifetime>) (Fn [] Int16 <StaticLifetime>) (Fn [] Int32 <StaticLifetime>) (Fn [] Int64 <StaticLifetime>) (Fn [] Int8 <StaticLifetime>) (Fn [] Long <StaticLifetime>) (Fn [] (Maybe a) <StaticLifetime>) (Fn [] (Pair a b) <StaticLifetime>) (Fn [] (Quadruple a b c d) <StaticLifetime>) (Fn [] String <StaticLifetime>) (Fn [] (Triple a b c) <StaticLifetime>) (Fn [] Uint16 <StaticLifetime>) (Fn [] Uint32 <StaticLifetime>) (Fn [] Uint64 <StaticLifetime>) (Fn [] Uint8 <StaticLifetime>))) ``` As shown in the example above, this change also includes a cosmetic update to the representation of lifetime variables, which are surrounded in <> to distinguish them from type variables. This commit also adds a new `kind` primitive that reports on the kind of a binding or value: ``` (def x 3) (kind x) => Base (kind 2) => Base (kind Maybe.Just) => Higher (kind (Maybe.Just 2)) => Higher ``` `kind` and `type` both support interactive development in the repl, for example, a user can rely on `kind` to check the kind of a type they plan on using in an interface that demands a higher-kinded argument. Likewise, they both also support developing macros based on type information.
2020-10-03 00:48:58 +03:00
-- | The Reifiable class ranges over internal Carp compiler types that
Enhance type reflection; get types of values, get kinds Extends Carp's support for type reflection by returning types for values as well as bindings. `type` now also returns a valid Carp expression/s-expression and so its output can be used as input to dynamic functions and macros (prior to this commit, `type` printed the type to the REPL but did not return a meaningful expression in Carp). Here are a few illustrations of the behavior: ``` (def x 1) ;; type now returns an s-expression/symbol (type x) => Int ;; It also works on values (type 1) => Int (type 2b) => Byte (type "foo") => (Ref String <StaticLifetime>) ;; It works on more complex values as well (type Maybe) => Module (type Maybe.Just) (Fn [a] (Maybe a) <StaticLifetime>) ;; reports honestly about polymorphism (type (Maybe.Nothing)) => (Maybe a) (type (Pair.init 1 2)) => (Pair Int Int) ;; What about the type of types? (type (type 2)) => Type ;; Or the type of types of types? (type (type (type 2))) => () ;; One more time! (type (type (type (type 2)))) => () ;; so, () is the fixpoint of type, and is reached after two applications (type zero) ;; the type of an interface is all of its implementations => (((Fn [] (Array a) <StaticLifetime>) (Fn [] Bool <StaticLifetime>) (Fn [] Byte <StaticLifetime>) (Fn [] Char <StaticLifetime>) (Fn [] Double <StaticLifetime>) (Fn [] Float <StaticLifetime>) (Fn [] Int <StaticLifetime>) (Fn [] Int16 <StaticLifetime>) (Fn [] Int32 <StaticLifetime>) (Fn [] Int64 <StaticLifetime>) (Fn [] Int8 <StaticLifetime>) (Fn [] Long <StaticLifetime>) (Fn [] (Maybe a) <StaticLifetime>) (Fn [] (Pair a b) <StaticLifetime>) (Fn [] (Quadruple a b c d) <StaticLifetime>) (Fn [] String <StaticLifetime>) (Fn [] (Triple a b c) <StaticLifetime>) (Fn [] Uint16 <StaticLifetime>) (Fn [] Uint32 <StaticLifetime>) (Fn [] Uint64 <StaticLifetime>) (Fn [] Uint8 <StaticLifetime>))) ``` As shown in the example above, this change also includes a cosmetic update to the representation of lifetime variables, which are surrounded in <> to distinguish them from type variables. This commit also adds a new `kind` primitive that reports on the kind of a binding or value: ``` (def x 3) (kind x) => Base (kind 2) => Base (kind Maybe.Just) => Higher (kind (Maybe.Just 2)) => Higher ``` `kind` and `type` both support interactive development in the repl, for example, a user can rely on `kind` to check the kind of a type they plan on using in an interface that demands a higher-kinded argument. Likewise, they both also support developing macros based on type information.
2020-10-03 00:48:58 +03:00
-- may have corresponding representations in Carp itself.
class Reifiable a where
reify :: a -> XObj
symbol :: Show a => a -> XObj
symbol x = XObj (Sym (SymPath [] (show x)) Symbol) Nothing Nothing
-- Show on strings results in a symbol that includes quotes ""
-- This function is the same as symbol, for string literals.
literal :: String -> XObj
Enhance type reflection; get types of values, get kinds Extends Carp's support for type reflection by returning types for values as well as bindings. `type` now also returns a valid Carp expression/s-expression and so its output can be used as input to dynamic functions and macros (prior to this commit, `type` printed the type to the REPL but did not return a meaningful expression in Carp). Here are a few illustrations of the behavior: ``` (def x 1) ;; type now returns an s-expression/symbol (type x) => Int ;; It also works on values (type 1) => Int (type 2b) => Byte (type "foo") => (Ref String <StaticLifetime>) ;; It works on more complex values as well (type Maybe) => Module (type Maybe.Just) (Fn [a] (Maybe a) <StaticLifetime>) ;; reports honestly about polymorphism (type (Maybe.Nothing)) => (Maybe a) (type (Pair.init 1 2)) => (Pair Int Int) ;; What about the type of types? (type (type 2)) => Type ;; Or the type of types of types? (type (type (type 2))) => () ;; One more time! (type (type (type (type 2)))) => () ;; so, () is the fixpoint of type, and is reached after two applications (type zero) ;; the type of an interface is all of its implementations => (((Fn [] (Array a) <StaticLifetime>) (Fn [] Bool <StaticLifetime>) (Fn [] Byte <StaticLifetime>) (Fn [] Char <StaticLifetime>) (Fn [] Double <StaticLifetime>) (Fn [] Float <StaticLifetime>) (Fn [] Int <StaticLifetime>) (Fn [] Int16 <StaticLifetime>) (Fn [] Int32 <StaticLifetime>) (Fn [] Int64 <StaticLifetime>) (Fn [] Int8 <StaticLifetime>) (Fn [] Long <StaticLifetime>) (Fn [] (Maybe a) <StaticLifetime>) (Fn [] (Pair a b) <StaticLifetime>) (Fn [] (Quadruple a b c d) <StaticLifetime>) (Fn [] String <StaticLifetime>) (Fn [] (Triple a b c) <StaticLifetime>) (Fn [] Uint16 <StaticLifetime>) (Fn [] Uint32 <StaticLifetime>) (Fn [] Uint64 <StaticLifetime>) (Fn [] Uint8 <StaticLifetime>))) ``` As shown in the example above, this change also includes a cosmetic update to the representation of lifetime variables, which are surrounded in <> to distinguish them from type variables. This commit also adds a new `kind` primitive that reports on the kind of a binding or value: ``` (def x 3) (kind x) => Base (kind 2) => Base (kind Maybe.Just) => Higher (kind (Maybe.Just 2)) => Higher ``` `kind` and `type` both support interactive development in the repl, for example, a user can rely on `kind` to check the kind of a type they plan on using in an interface that demands a higher-kinded argument. Likewise, they both also support developing macros based on type information.
2020-10-03 00:48:58 +03:00
literal x = XObj (Sym (SymPath [] x) Symbol) Nothing Nothing
array :: (Reifiable a) => [a] -> XObj
array x = XObj (Arr (map reify x)) Nothing Nothing
lifetime :: Show a => a -> XObj
lifetime x = literal ("<" ++ show x ++ ">")
-- Types
instance Reifiable Kind where
reify k = symbol k
instance Reifiable Ty where
reify (StructTy t []) = reify t
reify (StructTy t vs) = XObj (Lst (reify t : map reify vs)) Nothing (Just TypeTy)
reify (RefTy t lt) = XObj (Lst [literal "Ref", reify t, lifetime lt]) Nothing (Just TypeTy)
reify (PointerTy t) = XObj (Lst [literal "Ptr", reify t]) Nothing (Just TypeTy)
reify (FuncTy ats rt lt) = XObj (Lst [literal "Fn", array ats, reify rt, lifetime lt]) Nothing (Just TypeTy)
reify TypeTy = XObj (Sym (SymPath [] (show TypeTy)) Symbol) Nothing (Just Universe)
reify UnitTy = XObj (Sym (SymPath [] "Unit") Symbol) Nothing (Just TypeTy)
Refactor: clean up Env module, store type environments in modules (#1207) * refactor: major environment mgmt refactor This big refactor primarily changes two things in terms of behavior: 1. Stores a SymPath on concretely named (non-generic) struct types; before we stored a string. 2. The SymPath mentioned in (1.) designates where the struct is stored in the current environment chain. Modules now carry a local type environment in addition to their local value environments. Any types defined in the module are added to this environment rather than the global type environment. To resolve a type such as `Foo.Bar` we now do the following: - Search the *global value environment* for the Foo module. - Get the type environment stored in the Foo module. - Search for Bar in the Foo module's type environment. Additionally, this commit eliminates the Lookup module entirely and refactors the Env module to handle all aspects of environment management in hopefully a more reusable fashion. I also took the opportunity to refactor primitiveDeftype in Primitives and qualifySym in Qualify, both of which were hefty functions that I found difficult to grok and needed refactoring anyway as a result of lookup changes (lookups now return an Either instead of a Maybe). Subsequent commits will clean up and clarify this work further. This does include one minor regression. Namely, an implementation of `hash` in core/Color that was maximally generic now needs type casting. * refactor: clean up recent Env changes This commit removes some redundant functions, unifies some logic, and renames some routines across the Env module in efforts to make it cleaner. Call sites have been updated accordingly. * chore: format code with ormolu * fix: update lookup tests Changes references to renamed functions in the Env module. * refactor: style + additional improvements from eriksvedang@ - Rename arrayTy -> arrayTyA in ArrayTemplates.hs to disambiguate. - Add maybeId util function. - Remove commented code. - Refactor a few functions for readability. * fix: fix type inference regression Recent commits introduced one minor regression whereby an instance of type inference in core/Color.carp no longer worked and required explicit type annotation. The problem ultimately had to do with qualification: - Prior to the recent changes, type inference worked because the call in question was qualified to Color.Id.get-tag, fixing the type. - Failing to copy over a local envs Use modules to function envs resulted in finding more than just Color.Id.get-tag for this instance. We now copy use modules over to function envs generated during qualification to ensure we resolve to Use'd definitions before more general cases. Similarly, I made a small change to primitiveUse to support contextual use calls (e.g. the `(use Id)` in Color.carp, which really means `(use Color.Id)`) * chore: Update some clarificatory comments * chore: fix inline comment
2021-05-19 20:20:48 +03:00
reify (ConcreteNameTy path) = XObj (Sym path Symbol) Nothing (Just TypeTy)
Enhance type reflection; get types of values, get kinds Extends Carp's support for type reflection by returning types for values as well as bindings. `type` now also returns a valid Carp expression/s-expression and so its output can be used as input to dynamic functions and macros (prior to this commit, `type` printed the type to the REPL but did not return a meaningful expression in Carp). Here are a few illustrations of the behavior: ``` (def x 1) ;; type now returns an s-expression/symbol (type x) => Int ;; It also works on values (type 1) => Int (type 2b) => Byte (type "foo") => (Ref String <StaticLifetime>) ;; It works on more complex values as well (type Maybe) => Module (type Maybe.Just) (Fn [a] (Maybe a) <StaticLifetime>) ;; reports honestly about polymorphism (type (Maybe.Nothing)) => (Maybe a) (type (Pair.init 1 2)) => (Pair Int Int) ;; What about the type of types? (type (type 2)) => Type ;; Or the type of types of types? (type (type (type 2))) => () ;; One more time! (type (type (type (type 2)))) => () ;; so, () is the fixpoint of type, and is reached after two applications (type zero) ;; the type of an interface is all of its implementations => (((Fn [] (Array a) <StaticLifetime>) (Fn [] Bool <StaticLifetime>) (Fn [] Byte <StaticLifetime>) (Fn [] Char <StaticLifetime>) (Fn [] Double <StaticLifetime>) (Fn [] Float <StaticLifetime>) (Fn [] Int <StaticLifetime>) (Fn [] Int16 <StaticLifetime>) (Fn [] Int32 <StaticLifetime>) (Fn [] Int64 <StaticLifetime>) (Fn [] Int8 <StaticLifetime>) (Fn [] Long <StaticLifetime>) (Fn [] (Maybe a) <StaticLifetime>) (Fn [] (Pair a b) <StaticLifetime>) (Fn [] (Quadruple a b c d) <StaticLifetime>) (Fn [] String <StaticLifetime>) (Fn [] (Triple a b c) <StaticLifetime>) (Fn [] Uint16 <StaticLifetime>) (Fn [] Uint32 <StaticLifetime>) (Fn [] Uint64 <StaticLifetime>) (Fn [] Uint8 <StaticLifetime>))) ``` As shown in the example above, this change also includes a cosmetic update to the representation of lifetime variables, which are surrounded in <> to distinguish them from type variables. This commit also adds a new `kind` primitive that reports on the kind of a binding or value: ``` (def x 3) (kind x) => Base (kind 2) => Base (kind Maybe.Just) => Higher (kind (Maybe.Just 2)) => Higher ``` `kind` and `type` both support interactive development in the repl, for example, a user can rely on `kind` to check the kind of a type they plan on using in an interface that demands a higher-kinded argument. Likewise, they both also support developing macros based on type information.
2020-10-03 00:48:58 +03:00
reify t = XObj (Sym (SymPath [] (show t)) Symbol) Nothing (Just TypeTy)
instance Reifiable String where
2020-12-22 19:44:44 +03:00
reify s = XObj (Str s) Nothing (Just StringTy)
instance Reifiable Int where
2020-12-22 19:44:44 +03:00
reify i = XObj (Num IntTy (fromIntegral i)) Nothing (Just IntTy)
getInfoAsXObj :: (Reifiable a) => (Info -> a) -> Maybe Info -> Maybe XObj
2020-12-22 19:44:44 +03:00
getInfoAsXObj f = fmap (reify . f)
getFileAsXObj :: FilePathPrintLength -> Maybe Info -> Maybe XObj
getFileAsXObj FullPath = getInfoAsXObj infoFile
getFileAsXObj ShortPath = getInfoAsXObj (takeFileName . infoFile)
getLineAsXObj :: Maybe Info -> Maybe XObj
getLineAsXObj = getInfoAsXObj infoLine
getColumnAsXObj :: Maybe Info -> Maybe XObj
getColumnAsXObj = getInfoAsXObj infoColumn