Skip to content

Commit

Permalink
Add Low.Syntax module
Browse files Browse the repository at this point in the history
  • Loading branch information
ollef committed May 20, 2024
1 parent ad177c1 commit 12ef00e
Show file tree
Hide file tree
Showing 3 changed files with 124 additions and 0 deletions.
12 changes: 12 additions & 0 deletions src/Low/PassBy.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}

module Low.PassBy where

import Low.Representation (Representation)
import Protolude

data PassBy
= Value !Representation
| Reference
deriving (Eq, Show, Generic, Hashable)
54 changes: 54 additions & 0 deletions src/Low/Representation.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,54 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE PatternSynonyms #-}

module Low.Representation where

import Protolude hiding (repr)

data Representation = Representation
{ pointers :: !Int
, nonPointerBytes :: !Int
}
deriving (Eq, Show, Generic, Hashable)

instance Semigroup Representation where
repr1 <> repr2 =
Representation
{ pointers = repr1.pointers + repr2.pointers
, nonPointerBytes = repr1.nonPointerBytes + repr2.nonPointerBytes
}

instance Monoid Representation where
mempty = Empty

pattern Empty :: Representation
pattern Empty = Representation {pointers = 0, nonPointerBytes = 0}

leastUpperBound :: Representation -> Representation -> Representation
leastUpperBound repr1 repr2 =
Representation
{ pointers = max repr1.pointers repr2.pointers
, nonPointerBytes =
max repr1.nonPointerBytes repr2.nonPointerBytes
}

wordBytes :: Int
wordBytes = 8

int :: Representation
int = Representation {pointers = 0, nonPointerBytes = wordBytes}

type_ :: Representation
type_ = Representation {pointers = 0, nonPointerBytes = wordBytes}

pointer :: Representation
pointer = Representation {pointers = 1, nonPointerBytes = 0}

rawFunctionPointer :: Representation
rawFunctionPointer = Representation {pointers = 0, nonPointerBytes = wordBytes}

shouldPassByReference :: Representation -> Bool
shouldPassByReference repr =
repr.pointers * wordBytes + repr.nonPointerBytes > 2 * wordBytes
58 changes: 58 additions & 0 deletions src/Low/Syntax.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,58 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}

module Low.Syntax where

import Index
import Literal (Literal)
import Low.PassBy (PassBy)
import Low.Representation (Representation)
import Name (Name)
import qualified Name
import Protolude

data Term v
= Operand !(Operand v)
| Let !PassBy !Name !(Term v) !(Scope Term v)
| Seq !(Term v) !(Term v)
| Case !(Operand v) [Branch v] (Maybe (Term v))
| Call !Name.Lifted [Operand v]
| StackAllocate !(Operand v)
| HeapAllocate !Name.QualifiedConstructor !(Operand v)
| Dereference !(Operand v)
| PointerTag !(Operand v)
| Offset !(Operand v) !(Operand v)
| Copy !(Operand v) !(Operand v) !(Operand v)
| Store !(Operand v) !(Operand v) !Representation
| Load !(Operand v) !Representation
deriving (Eq, Show, Generic, Hashable)

data Operand v
= Var !(Index v)
| Global !Name.Lifted
| Literal !Literal
| Representation !Representation
| Tag !Name.QualifiedConstructor
deriving (Eq, Show, Generic, Hashable)

data Branch v
= ConstructorBranch !Name.QualifiedConstructor !(Term v)
| LiteralBranch !Literal !(Term v)
deriving (Eq, Show, Generic, Hashable)

data Function v
= Body !(Term v)
| Parameter !Name !(Scope Function v)
deriving (Eq, Show, Generic, Hashable)

type Type = Term

data Definition
= ConstantDefinition !(Term Void)
| FunctionDefinition !(Function Void)
deriving (Eq, Show, Generic, Hashable)

data Signature
= ConstantSignature !Representation
| FunctionSignature [PassBy] !PassBy
deriving (Eq, Show, Generic, Hashable)

0 comments on commit 12ef00e

Please sign in to comment.