Safe Haskell | None |
---|
Disciple Core Salt.
This is what happens to C
when you leave it out in the sun for too long.
Salt is a fragment of System-F2 that contains just those features that can be easily mapped onto C or LLVM code. It has functions, case expressions and primops, but no partial application, data types, or nested functions. All operations on algebraic data need to have been expanded to primitive store operations.
Salt exposes raw store and control primops, so its possible for functions written directly in Salt to corrupt the heap (if they are wrong).
- profile :: Profile Name
- seaOfSaltModule :: Show a => Bool -> Platform -> Module a Name -> Either (Error a) Doc
- data Error a
- = ErrorUndefined { }
- | ErrorBindNone
- | ErrorImportInvalid { }
- | ErrorTypeInvalid { }
- | ErrorNoTopLevelLetrec {
- errorModule :: Module a Name
- | ErrorFunctionInvalid { }
- | ErrorParameterInvalid { }
- | ErrorBodyInvalid { }
- | ErrorBodyMustPassControl { }
- | ErrorStmtInvalid { }
- | ErrorAltInvalid { }
- | ErrorRValueInvalid { }
- | ErrorArgInvalid { }
- | ErrorPrimCallInvalid {
- errorPrimOp :: PrimOp
- errorArgs :: [Exp a Name]
- data Name
- = NameVar String
- | NameCon String
- | NameObjTyCon
- | NamePrimTyCon PrimTyCon
- | NamePrimOp PrimOp
- | NameLitVoid
- | NameLitBool Bool
- | NameLitNat Integer
- | NameLitInt Integer
- | NameLitTag Integer
- | NameLitWord Integer Int
- data PrimTyCon
- = PrimTyConVoid
- | PrimTyConBool
- | PrimTyConNat
- | PrimTyConInt
- | PrimTyConWord Int
- | PrimTyConFloat Int
- | PrimTyConVec Int
- | PrimTyConAddr
- | PrimTyConPtr
- | PrimTyConTag
- | PrimTyConString
- data PrimOp
- data PrimCast
- primCastPromoteIsValid :: Platform -> PrimTyCon -> PrimTyCon -> Bool
- primCastTruncateIsValid :: Platform -> PrimTyCon -> PrimTyCon -> Bool
- data PrimCall = PrimCallTail Int
- data PrimControl
- data PrimStore
- = PrimStoreSize
- | PrimStoreSize2
- | PrimStoreCreate
- | PrimStoreCheck
- | PrimStoreRecover
- | PrimStoreAlloc
- | PrimStoreRead
- | PrimStoreWrite
- | PrimStorePlusAddr
- | PrimStoreMinusAddr
- | PrimStorePeek
- | PrimStorePoke
- | PrimStorePlusPtr
- | PrimStoreMinusPtr
- | PrimStoreMakePtr
- | PrimStoreTakePtr
- | PrimStoreCastPtr
- data PrimArith
- = PrimArithNeg
- | PrimArithAdd
- | PrimArithSub
- | PrimArithMul
- | PrimArithDiv
- | PrimArithMod
- | PrimArithRem
- | PrimArithEq
- | PrimArithNeq
- | PrimArithGt
- | PrimArithGe
- | PrimArithLt
- | PrimArithLe
- | PrimArithAnd
- | PrimArithOr
- | PrimArithShl
- | PrimArithShr
- | PrimArithBAnd
- | PrimArithBOr
- | PrimArithBXOr
- readName :: String -> Maybe Name
- lexModuleString :: String -> Int -> String -> [Token (Tok Name)]
- lexExpString :: String -> Int -> String -> [Token (Tok Name)]
Language profile
Conversion
:: Show a | |
=> Bool | Whether to emit top-level include macros. Emitting makes the code easier to read during testing. |
-> Platform | Target platform specification |
-> Module a Name | Module to convert. |
-> Either (Error a) Doc |
Convert a Disciple Core Salt module to C-source text.
Things that can go wrong when converting a Disciple Core Salt module to C source text.
ErrorUndefined | Variable is not in scope. |
ErrorBindNone | Binder has BNone form, binds no variable. |
ErrorImportInvalid | Invalid import. |
ErrorTypeInvalid | A local variable has an invalid type. |
ErrorNoTopLevelLetrec | Modules must contain a top-level letrec. |
| |
ErrorFunctionInvalid | An invalid function definition. |
ErrorParameterInvalid | An invalid function parameter. |
ErrorBodyInvalid | An invalid function body. |
ErrorBodyMustPassControl | A function body that does not explicitly pass control. |
ErrorStmtInvalid | An invalid statement. |
ErrorAltInvalid | An invalid alternative. |
ErrorRValueInvalid | An invalid RValue. |
ErrorArgInvalid | An invalid function argument. |
ErrorPrimCallInvalid | An invalid primitive call |
|
Names
Names of things used in Disciple Core Salt.
NameVar String | A type or value variable. |
NameCon String | Constructor names. |
NameObjTyCon | The abstract heap object type constructor. |
NamePrimTyCon PrimTyCon | A primitive type constructor. |
NamePrimOp PrimOp | A primitive operator. |
NameLitVoid | The void literal. |
NameLitBool Bool | A boolean literal. |
NameLitNat Integer | A natural number literal. |
NameLitInt Integer | An integer number literal. |
NameLitTag Integer | A constructor tag literal. |
NameLitWord Integer Int | A |
Primitive type constructors.
PrimTyConVoid |
|
PrimTyConBool |
|
PrimTyConNat |
|
PrimTyConInt |
|
PrimTyConWord Int |
|
PrimTyConFloat Int |
|
PrimTyConVec Int |
|
PrimTyConAddr |
|
PrimTyConPtr |
|
PrimTyConTag |
|
PrimTyConString |
These are primitive until we can define our own unboxed types. |
Primitive operators implemented directly by the machine or runtime system.
PrimArith PrimArith | Arithmetic, logic, comparison and bit-wise operators. |
PrimCast PrimCast | Casting between numeric types. |
PrimStore PrimStore | Raw store access. |
PrimCall PrimCall | Special function calling conventions. |
PrimControl PrimControl | Non-functional control flow. |
Primitive cast between two types.
The exact set of available casts is determined by the target platform.
For example, you can only promote a Nat#
to a Word32#
on a 32-bit
system. On a 64-bit system the Nat#
type is 64-bits wide, so casting it
to a Word32#
would be a truncation.
PrimCastConvert | Convert a value to a new representation with the same precision. |
PrimCastPromote | Promote a value to one of similar or larger width, without loss of precision. |
PrimCastTruncate | Truncate a value to a new width, possibly losing precision. |
Check for a valid promotion primop.
Check for valid truncation primop.
Primitive ways of invoking a function, where control flow returns back to the caller.
PrimCallTail Int | Tailcall a function |
data PrimControl Source
Primitive non-returning control flow.
PrimControlFail | Ungraceful failure -- just abort the program. This is called on internal errors in the runtime system. There is no further debugging info provided, so you'll need to look at the stack trace to debug it. |
PrimControlReturn | Return from the enclosing function with the given value. |
Eq PrimControl | |
Ord PrimControl | |
Show PrimControl | |
Pretty PrimControl | |
NFData PrimControl |
Raw access to the store.
PrimStoreSize | Number of bytes needed to store a value of a primitive type. |
PrimStoreSize2 | Log2 of number of bytes need to store a value of a primitive type. |
PrimStoreCreate | Create a heap of the given size.
This must be called before |
PrimStoreCheck | Check whether there are at least this many bytes still available on the heap. |
PrimStoreRecover | Force a garbage collection to recover at least this many bytes. |
PrimStoreAlloc | Allocate some space on the heap. There must be enough space available, else undefined. |
PrimStoreRead | Read a value from the store at the given address and offset. |
PrimStoreWrite | Write a value to the store at the given address and offset. |
PrimStorePlusAddr | Add an offset in bytes to an address. |
PrimStoreMinusAddr | Subtract an offset in bytes from an address. |
PrimStorePeek | Read a value from a pointer plus the given offset. |
PrimStorePoke | Write a value to a pointer plus the given offset. |
PrimStorePlusPtr | Add an offset in bytes to a pointer. |
PrimStoreMinusPtr | Subtract an offset in bytes from a pointer. |
PrimStoreMakePtr | Convert an raw address to a pointer. |
PrimStoreTakePtr | Convert a pointer to a raw address. |
PrimStoreCastPtr | Cast between pointer types. |
Primitive arithmetic, logic, and comparison opretors. We expect the backend/machine to be able to implement these directly.
For the Shift Right operator, the type that it is used at determines whether it is an arithmetic (with sign-extension) or logical (no sign-extension) shift.
PrimArithNeg | Negation |
PrimArithAdd | Addition |
PrimArithSub | Subtraction |
PrimArithMul | Multiplication |
PrimArithDiv | Division |
PrimArithMod | Modulus |
PrimArithRem | Remainder |
PrimArithEq | Equality |
PrimArithNeq | Negated Equality |
PrimArithGt | Greater Than |
PrimArithGe | Greater Than or Equal |
PrimArithLt | Less Than |
PrimArithLe | Less Than or Equal |
PrimArithAnd | Boolean And |
PrimArithOr | Boolean Or |
PrimArithShl | Shift Left |
PrimArithShr | Shift Right |
PrimArithBAnd | Bit-wise And |
PrimArithBOr | Bit-wise Or |
PrimArithBXOr | Bit-wise eXclusive Or |
Name parsing
Program lexing
:: String | Source file name. |
-> Int | Starting line number. |
-> String | String to parse. |
-> [Token (Tok Name)] |
Lex a string to tokens, using primitive names.