Git Product home page Git Product logo

llvm-hs-typed's Introduction

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 #-}

module Example where

-- AST
import GHC.TypeLits
import LLVM.Prelude
import LLVM.AST.Tagged
import LLVM.AST.Constant
import LLVM.AST.Tagged.Global
import LLVM.AST.Tagged.Constant
import LLVM.AST.Tagged.Tag
import LLVM.AST.TypeLevel.Type

import qualified LLVM.AST as AST
import qualified LLVM.AST.Global as AST

c0 :: Constant ::: IntegerType' 32
c0 = int 42

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

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

defAdd :: Global
defAdd = function nm (params, False) [body, body]
  where
    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

module_ :: AST.Module
module_ = defaultModule
  { moduleName = "basic"
  , moduleDefinitions = [GlobalDefinition defAdd]
  }

Typed IRBuilder

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE OverloadedStrings #-}

module Example2 where

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

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

import Data.Coerce

simple :: AST.Module
simple = Builder.buildModule "exampleModule" $ do
    func
  where
  func :: Builder.ModuleBuilder (AST.Operand ::: IntegerType' 32)
  func =
    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

llvm-hs-typed's People

Contributors

nomeata avatar sdiehl avatar yanok avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

llvm-hs-typed's Issues

Floating point type

Maybe this is a discussion that should be had in llvm-hs-pure

The LLVM language reference specifies the following floating point types:

Type Description
half 16-bit floating point value
float 32-bit floating point value
double 64-bit floating point value
fp128 128-bit floating point value (112-bit mantissa)
x86_fp80 80-bit floating point value (X87)
ppc_fp128 128-bit floating point value (two 64-bits)

Why does the llvm-hs AST have this complicated

  | FloatingPointType { typeBits :: Word32, floatingPointFormat :: FloatingPointFormat }

constructor? The values (SomeFloat in LLVM.AST.Float) follow the LLVM spec more closely…

And, more specific to this repository: Shall we stick to the type that llvm-hs uses, or shall we use something like this:

data FloatingPointType = HalfType | FloatType | DoubleType | FP128Type | QuadrupleType | X86_FP80Type | PPC_FP128Type
…
  | FloatingPointType { floatingPointType = FloatingPointType }

Dependency Graph

With regards to adding to a pretty printer for the typed AST there are two options:

  • Make llvm-hs-pretty a dependency of llvm-hs-typed and then derive the pretty instances for the type tag constructors.
  • Make llvm-hs-typeda dependency ofllvm-hs-pretty` and derive instances for the tag constructors next to the main class definitions.

I don't think anybody but me uses this library yet, but just trying to plan if we want to coalesce projects someday.

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.