llvm-hs/llvm-hs-typed

Name: llvm-hs-typed

Owner: llvm-hs

Description: Type Safe LLVM IR ( Experimental )

Created: 2017-04-24 16:17:33.0

Updated: 2018-02-27 01:47:25.0

Pushed: 2018-02-09 09:19:33.0

Homepage:

Size: 81

Language: Haskell

GitHub Committers

UserMost Recent Commit# Commits

Other Committers

UserEmailMost Recent Commit# Commits

README

llvm-hs-typed

Build Status

An experimental branch of llvm-hs-pure AST that enforces the semantics of correct AST construction using the Haskell type system to prevent malformed ASTs.

Usage
Typed AST
LANGUAGE DataKinds #-}
LANGUAGE PolyKinds #-}
LANGUAGE TypeFamilies #-}
LANGUAGE TypeOperators #-}
LANGUAGE ExplicitForAll #-}
LANGUAGE TypeApplications #-}
LANGUAGE FlexibleInstances #-}
LANGUAGE OverloadedStrings #-}
LANGUAGE ScopedTypeVariables #-}
LANGUAGE AllowAmbiguousTypes #-}
LANGUAGE UndecidableInstances #-}
LANGUAGE MultiParamTypeClasses #-}

le Example where

ST
rt GHC.TypeLits
rt LLVM.Prelude
rt LLVM.AST.Tagged
rt LLVM.AST.Constant
rt LLVM.AST.Tagged.Global
rt LLVM.AST.Tagged.Constant
rt LLVM.AST.Tagged.Tag
rt LLVM.AST.TypeLevel.Type

rt qualified LLVM.AST as AST
rt qualified LLVM.AST.Global as AST

: Constant ::: IntegerType' 32
 int 42

d :: forall (t :: Type'). ShortByteString -> Name ::: t
d s = assertLLVMType $ AST.Name s

 ArgTys = [(IntegerType' 32), (IntegerType' 32)]
 RetTy = IntegerType' 32

dd :: Global
dd = function nm (params, False) [body, body]
ere
nm :: Name ::: (PointerType' (FunctionType' (IntegerType' 32) ArgTys) ('AddrSpace' 0))
nm = named "add"

-- Types of subexpression are inferred from toplevel LLVM function signature

{-p1 :: Parameter ::: (IntegerType' 32)-}
p1 = parameter (named "a") []

{-p2 :: Parameter ::: (IntegerType' 32)-}
p2 = parameter (named "b") []

{-body :: BasicBlock ::: IntegerType' 32-}
body = basicBlock "entry" [] (ret (constantOperand c0) [])

{-params :: Parameter :::* ArgTys-}
params = p1 :* p2 :* tnil

le_ :: AST.Module
le_ = defaultModule
moduleName = "basic"
moduleDefinitions = [GlobalDefinition defAdd]

Typed IRBuilder
LANGUAGE DataKinds #-}
LANGUAGE PolyKinds #-}
LANGUAGE RecursiveDo #-}
LANGUAGE TypeOperators #-}
LANGUAGE OverloadedStrings #-}

le Example2 where

rt GHC.TypeLits
rt LLVM.Prelude
rt LLVM.AST.Constant
rt LLVM.AST.Tagged.Global
rt LLVM.AST.Tagged.Tag
rt LLVM.AST.TypeLevel.Type
rt qualified LLVM.AST as AST
rt qualified LLVM.AST.Type as AST
rt qualified LLVM.AST.Global as AST
rt qualified LLVM.AST.Tagged as AST

rt LLVM.AST.Tagged.IRBuilder as TBuilder
rt qualified LLVM.IRBuilder as Builder

rt Data.Coerce

le :: AST.Module
le = Builder.buildModule "exampleModule" $ do
func
ere
nc :: Builder.ModuleBuilder (AST.Operand ::: IntegerType' 32)
nc =
TBuilder.function "add" [(AST.i32, "a"), (AST.i32, "b")] $ \[a, b] -> do
  entry <- block `named` "entry"; do
    c <- add (coerce a) (coerce b)
    ret c
License

Copyright (c) 2017, Joachim Breitner


This work is supported by the National Institutes of Health's National Center for Advancing Translational Sciences, Grant Number U24TR002306. This work is solely the responsibility of the creators and does not necessarily represent the official views of the National Institutes of Health.