Skip to content

Commit

Permalink
WIP: fixpoint types
Browse files Browse the repository at this point in the history
  • Loading branch information
iphydf committed Dec 27, 2021
1 parent e887128 commit 19e45c1
Show file tree
Hide file tree
Showing 14 changed files with 811 additions and 714 deletions.
5 changes: 5 additions & 0 deletions BUILD.bazel
Expand Up @@ -46,6 +46,8 @@ haskell_library(
hazel_library("aeson"),
hazel_library("array"),
hazel_library("base"),
hazel_library("data-fix"),
hazel_library("transformers-compat"),
],
)

Expand All @@ -65,6 +67,7 @@ haskell_library(
":parser",
hazel_library("array"),
hazel_library("base"),
hazel_library("data-fix"),
hazel_library("text"),
],
)
Expand All @@ -91,6 +94,7 @@ haskell_library(
hazel_library("base"),
hazel_library("bytestring"),
hazel_library("containers"),
hazel_library("data-fix"),
hazel_library("filepath"),
hazel_library("groom"),
hazel_library("mtl"),
Expand All @@ -105,6 +109,7 @@ hspec_test(
":hs-cimple",
hazel_library("ansi-wl-pprint"),
hazel_library("base"),
hazel_library("data-fix"),
hazel_library("hspec"),
hazel_library("text"),
],
Expand Down
3 changes: 3 additions & 0 deletions cimple.cabal
Expand Up @@ -48,10 +48,12 @@ library
, array
, bytestring
, containers
, data-fix
, filepath
, groom
, mtl
, text
, transformers-compat

executable cimplefmt
default-language: Haskell2010
Expand Down Expand Up @@ -121,5 +123,6 @@ test-suite testsuite
base < 5
, ansi-wl-pprint
, cimple
, data-fix
, hspec
, text
2 changes: 1 addition & 1 deletion src/Language/Cimple.hs
Expand Up @@ -13,7 +13,7 @@ import Language.Cimple.Parser as X
import Language.Cimple.Tokens as X
import Language.Cimple.TraverseAst as X

type AstActions a = X.IdentityActions (State a) () Text
type AstActions a = X.IdentityActions (State a) Text

defaultActions :: AstActions state
defaultActions = X.identityActions
184 changes: 96 additions & 88 deletions src/Language/Cimple/AST.hs
@@ -1,125 +1,133 @@
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StrictData #-}
module Language.Cimple.AST
( AssignOp (..)
, BinaryOp (..)
, UnaryOp (..)
, LiteralType (..)
, Node (..)
, Node, NodeF (..)
, Scope (..)
, CommentStyle (..)
) where

import Data.Aeson (FromJSON, ToJSON)
import GHC.Generics (Generic)
import Data.Aeson (FromJSON, ToJSON)
import Data.Fix (Fix)
import Data.Functor.Classes (Eq1, Read1, Show1)
import Data.Functor.Classes.Generic (FunctorClassesDefault (..))
import GHC.Generics (Generic, Generic1)

data Node attr lexeme
= Attr attr (Node attr lexeme)
data NodeF lexeme a
-- Preprocessor
| PreprocInclude lexeme
= PreprocInclude lexeme
| PreprocDefine lexeme
| PreprocDefineConst lexeme (Node attr lexeme)
| PreprocDefineMacro lexeme [Node attr lexeme] (Node attr lexeme)
| PreprocIf (Node attr lexeme) [Node attr lexeme] (Node attr lexeme)
| PreprocIfdef lexeme [Node attr lexeme] (Node attr lexeme)
| PreprocIfndef lexeme [Node attr lexeme] (Node attr lexeme)
| PreprocElse [Node attr lexeme]
| PreprocElif (Node attr lexeme) [Node attr lexeme] (Node attr lexeme)
| PreprocDefineConst lexeme a
| PreprocDefineMacro lexeme [a] a
| PreprocIf a [a] a
| PreprocIfdef lexeme [a] a
| PreprocIfndef lexeme [a] a
| PreprocElse [a]
| PreprocElif a [a] a
| PreprocUndef lexeme
| PreprocDefined lexeme
| PreprocScopedDefine (Node attr lexeme) [Node attr lexeme] (Node attr lexeme)
| MacroBodyStmt (Node attr lexeme)
| MacroBodyFunCall (Node attr lexeme)
| PreprocScopedDefine a [a] a
| MacroBodyStmt a
| MacroBodyFunCall a
| MacroParam lexeme
| StaticAssert (Node attr lexeme) lexeme
| StaticAssert a lexeme
-- Comments
| LicenseDecl lexeme [Node attr lexeme]
| LicenseDecl lexeme [a]
| CopyrightDecl lexeme (Maybe lexeme) [lexeme]
| Comment CommentStyle lexeme [lexeme] lexeme
| CommentBlock lexeme
| Commented (Node attr lexeme) (Node attr lexeme)
| Commented a a
-- Namespace-like blocks
| ExternC [Node attr lexeme]
| Class Scope lexeme [Node attr lexeme] [Node attr lexeme]
| Namespace Scope lexeme [Node attr lexeme]
| ExternC [a]
| Class Scope lexeme [a] [a]
| Namespace Scope lexeme [a]
-- Statements
| CompoundStmt [Node attr lexeme]
| CompoundStmt [a]
| Break
| Goto lexeme
| Continue
| Return (Maybe (Node attr lexeme))
| SwitchStmt (Node attr lexeme) [Node attr lexeme]
| IfStmt (Node attr lexeme) (Node attr lexeme) (Maybe (Node attr lexeme))
| ForStmt (Node attr lexeme) (Node attr lexeme) (Node attr lexeme) (Node attr lexeme)
| WhileStmt (Node attr lexeme) (Node attr lexeme)
| DoWhileStmt (Node attr lexeme) (Node attr lexeme)
| Case (Node attr lexeme) (Node attr lexeme)
| Default (Node attr lexeme)
| Label lexeme (Node attr lexeme)
| Return (Maybe a)
| SwitchStmt a [a]
| IfStmt a a (Maybe a)
| ForStmt a a a a
| WhileStmt a a
| DoWhileStmt a a
| Case a a
| Default a
| Label lexeme a
-- Variable declarations
| VLA (Node attr lexeme) lexeme (Node attr lexeme)
| VarDecl (Node attr lexeme) (Node attr lexeme)
| Declarator (Node attr lexeme) (Maybe (Node attr lexeme))
| VLA a lexeme a
| VarDecl a a
| Declarator a (Maybe a)
| DeclSpecVar lexeme
| DeclSpecArray (Node attr lexeme) (Maybe (Node attr lexeme))
| DeclSpecArray a (Maybe a)
-- Expressions
| InitialiserList [Node attr lexeme]
| UnaryExpr UnaryOp (Node attr lexeme)
| BinaryExpr (Node attr lexeme) BinaryOp (Node attr lexeme)
| TernaryExpr (Node attr lexeme) (Node attr lexeme) (Node attr lexeme)
| AssignExpr (Node attr lexeme) AssignOp (Node attr lexeme)
| ParenExpr (Node attr lexeme)
| CastExpr (Node attr lexeme) (Node attr lexeme)
| CompoundExpr (Node attr lexeme) (Node attr lexeme)
| SizeofExpr (Node attr lexeme)
| SizeofType (Node attr lexeme)
| InitialiserList [a]
| UnaryExpr UnaryOp a
| BinaryExpr a BinaryOp a
| TernaryExpr a a a
| AssignExpr a AssignOp a
| ParenExpr a
| CastExpr a a
| CompoundExpr a a
| SizeofExpr a
| SizeofType a
| LiteralExpr LiteralType lexeme
| VarExpr lexeme
| MemberAccess (Node attr lexeme) lexeme
| PointerAccess (Node attr lexeme) lexeme
| ArrayAccess (Node attr lexeme) (Node attr lexeme)
| FunctionCall (Node attr lexeme) [Node attr lexeme]
| CommentExpr (Node attr lexeme) (Node attr lexeme)
| MemberAccess a lexeme
| PointerAccess a lexeme
| ArrayAccess a a
| FunctionCall a [a]
| CommentExpr a a
-- Type definitions
| EnumClass lexeme [Node attr lexeme]
| EnumConsts (Maybe lexeme) [Node attr lexeme]
| EnumDecl lexeme [Node attr lexeme] lexeme
| Enumerator lexeme (Maybe (Node attr lexeme))
| ClassForward lexeme [Node attr lexeme]
| Typedef (Node attr lexeme) lexeme
| TypedefFunction (Node attr lexeme)
| Struct lexeme [Node attr lexeme]
| Union lexeme [Node attr lexeme]
| MemberDecl (Node attr lexeme) (Node attr lexeme) (Maybe lexeme)
| TyConst (Node attr lexeme)
| TyPointer (Node attr lexeme)
| EnumClass lexeme [a]
| EnumConsts (Maybe lexeme) [a]
| EnumDecl lexeme [a] lexeme
| Enumerator lexeme (Maybe a)
| ClassForward lexeme [a]
| Typedef a lexeme
| TypedefFunction a
| Struct lexeme [a]
| Union lexeme [a]
| MemberDecl a a (Maybe lexeme)
| TyConst a
| TyPointer a
| TyStruct lexeme
| TyFunc lexeme
| TyStd lexeme
| TyVar lexeme
| TyUserDefined lexeme
-- Functions
| FunctionDecl Scope (Node attr lexeme) (Maybe (Node attr lexeme))
| FunctionDefn Scope (Node attr lexeme) (Node attr lexeme)
| FunctionPrototype (Node attr lexeme) lexeme [Node attr lexeme]
| FunctionParam (Node attr lexeme) (Node attr lexeme)
| Event lexeme (Node attr lexeme)
| EventParams [Node attr lexeme]
| Property (Node attr lexeme) (Node attr lexeme) [Node attr lexeme]
| Accessor lexeme [Node attr lexeme] (Maybe (Node attr lexeme))
| ErrorDecl lexeme [Node attr lexeme]
| ErrorList [Node attr lexeme]
| FunctionDecl Scope a (Maybe a)
| FunctionDefn Scope a a
| FunctionPrototype a lexeme [a]
| FunctionParam a a
| Event lexeme a
| EventParams [a]
| Property a a [a]
| Accessor lexeme [a] (Maybe a)
| ErrorDecl lexeme [a]
| ErrorList [a]
| ErrorFor lexeme
| Ellipsis
-- Constants
| ConstDecl (Node attr lexeme) lexeme
| ConstDefn Scope (Node attr lexeme) lexeme (Node attr lexeme)
deriving (Show, Eq, Generic, Functor, Foldable, Traversable)
| ConstDecl a lexeme
| ConstDefn Scope a lexeme a
deriving (Show, Read, Eq, Generic, Generic1, Functor, Foldable, Traversable)
deriving (Show1, Read1, Eq1) via FunctorClassesDefault (NodeF lexeme)

instance (FromJSON attr, FromJSON lexeme) => FromJSON (Node attr lexeme)
instance (ToJSON attr, ToJSON lexeme) => ToJSON (Node attr lexeme)
type Node lexeme = Fix (NodeF lexeme)

instance (FromJSON lexeme, FromJSON a) => FromJSON (NodeF lexeme a)
instance (ToJSON lexeme, ToJSON a) => ToJSON (NodeF lexeme a)

data AssignOp
= AopEq
Expand All @@ -133,7 +141,7 @@ data AssignOp
| AopMod
| AopLsh
| AopRsh
deriving (Show, Eq, Generic)
deriving (Show, Read, Eq, Generic)

instance FromJSON AssignOp
instance ToJSON AssignOp
Expand All @@ -157,7 +165,7 @@ data BinaryOp
| BopGt
| BopGe
| BopRsh
deriving (Show, Eq, Generic)
deriving (Show, Read, Eq, Generic)

instance FromJSON BinaryOp
instance ToJSON BinaryOp
Expand All @@ -170,7 +178,7 @@ data UnaryOp
| UopDeref
| UopIncr
| UopDecr
deriving (Show, Eq, Generic)
deriving (Show, Read, Eq, Generic)

instance FromJSON UnaryOp
instance ToJSON UnaryOp
Expand All @@ -181,15 +189,15 @@ data LiteralType
| Bool
| String
| ConstId
deriving (Show, Eq, Generic)
deriving (Show, Read, Eq, Generic)

instance FromJSON LiteralType
instance ToJSON LiteralType

data Scope
= Global
| Static
deriving (Show, Eq, Generic)
deriving (Show, Read, Eq, Generic)

instance FromJSON Scope
instance ToJSON Scope
Expand All @@ -198,7 +206,7 @@ data CommentStyle
= Regular
| Doxygen
| Block
deriving (Show, Eq, Generic)
deriving (Show, Read, Eq, Generic)

instance FromJSON CommentStyle
instance ToJSON CommentStyle

0 comments on commit 19e45c1

Please sign in to comment.