ddc-core-salt-0.4.3.1: Disciplined Disciple Compiler C code generator.

Safe HaskellSafe
LanguageHaskell98

DDC.Core.Salt.Name

Contents

Description

Names used in the Disciple Core Salt language profile.

Synopsis

Documentation

data Name Source #

Names of things used in Disciple Core Salt.

Constructors

NameVar !String

A type or value variable.

NameCon !String

Constructor names.

NameExt !Name !String

An extended name.

NameObjTyCon

The abstract heap object type constructor.

NamePrimTyCon !PrimTyCon

A primitive type constructor.

NamePrimVal !PrimVal

A primitive value.

Instances

Eq Name Source # 

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name Source # 

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Pretty Name Source # 

Associated Types

data PrettyMode Name :: * #

Methods

pprDefaultMode :: PrettyMode Name #

ppr :: Name -> Doc #

pprPrec :: Int -> Name -> Doc #

pprModePrec :: PrettyMode Name -> Int -> Name -> Doc #

CompoundName Name Source # 
NFData Name Source # 

Methods

rnf :: Name -> () #

FromAnnot (Pat Name) Pat Source # 
FromAnnot (WiCon Name) WiCon Source # 
FromAnnot (Bind Name) (Bind Name) Source # 
FromAnnot (Bound Name) (Bound Name) Source # 
FromAnnot (Type Name) (Type Name) Source # 
FromAnnot (Exp a Name) Exp Source # 
FromAnnot (Lets a Name) Lets Source # 
FromAnnot (Alt a Name) Alt Source # 
FromAnnot (Cast a Name) Cast Source # 
FromAnnot (Witness a Name) Witness Source # 
FromAnnot (DaCon Name (Type Name)) (DaCon Name (Type Name)) Source # 
type GAnnot Name # 
type GAnnot Name = ()
type GBind Name # 
type GBound Name # 
type GPrim Name # 

Primitive Type Constructors

data PrimTyCon Source #

Primitive type constructors.

Constructors

PrimTyConVoid

Void# the Void type has no values.

PrimTyConBool

Bool# unboxed booleans.

PrimTyConNat

Nat# natural numbers. Enough precision to count every object in the heap, but NOT necessearily enough precision to count every byte of memory.

PrimTyConInt

Int# signed integers. Enough precision to count every object in the heap, but NOT necessearily enough precision to count every byte of memory. If N is the total number of objects that can exist in the heap, then the range of Int# is at least (-N .. +N) inclusive.

PrimTyConSize

Size# unsigned sizes. Enough precision to count every addressable bytes of memory.

PrimTyConWord Int

WordN# machine words of the given width.

PrimTyConFloat Int

FloatN# floating point numbers of the given width.

PrimTyConVec Int

VecN# a packed vector of N values. This is intended to have kind (Data -> Data), so we use concrete vector types like Vec4.

PrimTyConAddr

Addr# a relative or absolute machine address. Enough precision to count every byte of memory. Unlike pointers below, an absolute Addr# need not refer to memory owned by the current process.

PrimTyConPtr

Ptr# like Addr#, but with a region and element type annotation. In particular, a value of a type like (Ptr) must be at least 4-byte aligned and point to memory owned by the current process.

PrimTyConTextLit

TextLit# type of a text literal, which is represented as a pointer to the literal data in static memory.

PrimTyConTag

Tag# data constructor tags. Enough precision to count every possible alternative of an enumerated type.

pprPrimTyConStem :: PrimTyCon -> Doc Source #

Pretty print a primitive type constructor, without the # suffix.

readPrimTyCon :: String -> Maybe PrimTyCon Source #

Read a primitive type constructor.

Words are limited to 8, 16, 32, or 64 bits.

Floats are limited to 32 or 64 bits.

readPrimTyConStem :: String -> Maybe PrimTyCon Source #

Read a primitive type constructor, without the # suffix.

primTyConIsIntegral :: PrimTyCon -> Bool Source #

Integral constructors are the ones that we can reasonably convert from integers of the same size.

These are Bool#, Nat#, Int#, Size, WordN# and Tag#.

primTyConIsFloating :: PrimTyCon -> Bool Source #

Floating point types.

These are FloatN#.

primTyConIsUnsigned :: PrimTyCon -> Bool Source #

Unsigned types.

These are Bool# Nat# Size# WordN Tag.

primTyConIsSigned :: PrimTyCon -> Bool Source #

Signed integral constructors.

This is just Int.

primTyConWidth :: Platform -> PrimTyCon -> Maybe Integer Source #

Get the representation width of a primitive type constructor, in bits. This is how much space it takes up in an object payload.

Bools are representable with a single bit, but we unpack them into a whole word.

The constructors Void and VecN# and String have no width.

Primitive Values

data PrimVal Source #

Primitive values, meaning both operators and literals.

readPrimVal :: String -> Maybe PrimVal Source #

Read a primitive value.

pattern NamePrimOp :: PrimOp -> Name Source #

Primitive Operators

data PrimOp Source #

Primitive operators implemented directly by the machine or runtime system.

Constructors

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.

Instances

readPrimOp :: String -> Maybe PrimOp Source #

Read a primitive operator.

Primitive Arithmetic

data PrimArith Source #

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.

Constructors

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

readPrimArith :: String -> Maybe PrimArith Source #

Read a primitive operator.

Primitive Calls

data PrimCall Source #

Primitive ways of invoking a function, where control flow returns back to the caller.

Constructors

PrimCallStd Int

Perform a standard function call where the address is not statically known. All the arguments are boxed heap objects.

PrimCallTail Int

Tailcall a statically known functions, where the arguments can be boxed or unboxed.

Primitive Casts

data PrimCast Source #

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.

Constructors

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.

primCastPromoteIsValid Source #

Arguments

:: Platform

Target platform.

-> PrimTyCon

Source type.

-> PrimTyCon

Destination type.

-> Bool 

Check for a valid promotion primop.

primCastTruncateIsValid Source #

Arguments

:: Platform

Target platform.

-> PrimTyCon

Source type.

-> PrimTyCon

Destination type.

-> Bool 

Check for valid truncation primop.

Primitive Control

data PrimControl Source #

Primitive non-returning control flow.

Constructors

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.

Primitive Store

data PrimStore Source #

Raw access to the store.

Constructors

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 alloc# below, and has global side effect. Calling it twice in the same program is undefined.

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 offset.

PrimStorePeekBounded

Read a value from a pointer plus offset, with an integrated bounds check.

PrimStorePoke

Write a value to a pointer plus given offset.

PrimStorePokeBounded

Write a value to a pointer plus offset, with an integrated bounds check.

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 Vector

data PrimVec Source #

Primitive fixed-length SIMD vector operators.

Constructors

PrimVecNeg

Negate elements of a vector.

Fields

PrimVecAdd

Add elements of a vector.

Fields

PrimVecSub

Subtract elements of a vector.

Fields

PrimVecMul

Multiply elements of a vector.

Fields

PrimVecDiv

Divide elements of a vector.

Fields

PrimVecRep

Replicate a scalar into a vector.

Fields

PrimVecPack

Pack multiple scalars into a vector

Fields

PrimVecProj

Extract a single element from a vector.

PrimVecGather

Read multiple elements from memory.

Fields

PrimVecScatter

Write multiple elements to memory.

Fields

readPrimVec :: String -> Maybe PrimVec Source #

Read a primitive vector operator.

multiOfPrimVec :: PrimVec -> Maybe Int Source #

Yield the multiplicity of a vector operator.

liftPrimArithToVec :: Int -> PrimArith -> Maybe PrimVec Source #

Yield the PrimVector that corresponds to a PrimArith of the given multiplicity, if any.

lowerPrimVecToArith :: PrimVec -> Maybe PrimArith Source #

Yield the PrimArith that corresponds to a PrimVector, if any.

Primitive Literals

data PrimLit Source #

Primitive literals.

Constructors

PrimLitVoid

The void literal.

PrimLitBool !Bool

A boolean literal.

PrimLitNat !Integer

A natural number literal.

PrimLitInt !Integer

An integer number literal.

PrimLitSize !Integer

A size literal.

PrimLitWord !Integer !Int

A word literal, of the given width.

PrimLitFloat !Double !Int

A floating point literal, of the given width.

PrimLitChar !Char

A character literal.

PrimLitTextLit !Text

A text literal.

PrimLitTag !Integer

A constructor tag literal.

readPrimLit :: String -> Maybe PrimLit Source #

Read a primitive literal.

readLitInteger :: String -> Maybe Integer #

Read a signed integer.

readLitNat :: String -> Maybe Integer #

Read an integer with an explicit format specifier like 1234i.

readLitInt :: String -> Maybe Integer #

Read an integer literal with an explicit format specifier like 1234i.

readLitSize :: String -> Maybe Integer #

Read an size literal with an explicit format specifier like 1234s.

readLitWordOfBits :: String -> Maybe (Integer, Int) #

Read a word with an explicit format speficier.

readLitFloatOfBits :: String -> Maybe (Double, Int) #

Read a float literal with an explicit format specifier like 123.00f32#.

pattern NameLitBool :: Bool -> Name Source #

pattern NameLitWord :: Integer -> Int -> Name Source #

pattern NameLitFloat :: Double -> Int -> Name Source #

pattern NameLitChar :: Char -> Name Source #

pattern NameLitTextLit :: Text -> Name Source #

Name Parsing

readName :: String -> Maybe Name Source #

Read the name of a variable, constructor or literal.

takeNameVar :: Name -> Maybe String Source #

Take the string of a non-primitive name. Supports extended names.