diff --git a/src/Language/Cimple/Lexer.x b/src/Language/Cimple/Lexer.x index 5508521..60959a4 100644 --- a/src/Language/Cimple/Lexer.x +++ b/src/Language/Cimple/Lexer.x @@ -132,6 +132,8 @@ tokens :- <0> [\ \n]+ ; <0> $white { mkE ErrorToken } <0> "//!TOKSTYLE-" { mkL IgnStart `andBegin` ignoreSC } +<0> "/*!" { mkL CmtStartCode } +<0> "*/" { mkL CmtEnd } <0> "/*" { mkL CmtStart `andBegin` cmtSC } <0> "/**" { mkL CmtStartDoc `andBegin` cmtSC } <0> "/** @{" { mkL CmtStartDocSection `andBegin` cmtSC } diff --git a/src/Language/Cimple/MapAst.hs b/src/Language/Cimple/MapAst.hs index e423e23..3f1c563 100644 --- a/src/Language/Cimple/MapAst.hs +++ b/src/Language/Cimple/MapAst.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE MultiParamTypeClasses #-} @@ -6,7 +7,7 @@ {-# LANGUAGE Strict #-} {-# LANGUAGE TypeFamilies #-} module Language.Cimple.MapAst - ( mapAst + ( mapAst, mapFileAst , doFiles, doFile , doNodes, doNode @@ -14,12 +15,13 @@ module Language.Cimple.MapAst , doLexemes, doLexeme , doText - , astActions + , AstActions, astActions , TextActions, textActions , IdentityActions, identityActions ) where import Data.Fix (Fix (..)) +import GHC.Stack (HasCallStack) import Language.Cimple.Ast (Comment, CommentF (..), Node, NodeF (..)) import Language.Cimple.Lexer (Lexeme (..)) @@ -27,14 +29,14 @@ import Language.Cimple.Lexer (Lexeme (..)) class MapAst itext otext a where type Mapped itext otext a mapFileAst - :: Applicative f + :: (Applicative f, HasCallStack) => AstActions f itext otext -> FilePath -> a -> f (Mapped itext otext a) mapAst - :: (MapAst itext otext a, Applicative f) + :: (MapAst itext otext a, Applicative f, HasCallStack) => AstActions f itext otext -> a -> f (Mapped itext otext a) mapAst = flip mapFileAst "" @@ -86,7 +88,7 @@ identityActions = astActions pure instance MapAst itext otext (Lexeme itext) where type Mapped itext otext (Lexeme itext) = Lexeme otext - mapFileAst :: forall f . Applicative f + mapFileAst :: (Applicative f, HasCallStack) => AstActions f itext otext -> FilePath -> Lexeme itext -> f (Lexeme otext) mapFileAst AstActions{..} currentFile = doLexeme currentFile <*> \(L p c s) -> L p c <$> doText currentFile s @@ -101,7 +103,7 @@ instance MapAst itext otext (Comment (Lexeme itext)) where type Mapped itext otext (Comment (Lexeme itext)) = Comment (Lexeme otext) mapFileAst - :: forall f . Applicative f + :: forall f. (Applicative f, HasCallStack) => AstActions f itext otext -> FilePath -> Comment (Lexeme itext) @@ -177,7 +179,7 @@ instance MapAst itext otext (Node (Lexeme itext)) where type Mapped itext otext (Node (Lexeme itext)) = Node (Lexeme otext) mapFileAst - :: forall f . Applicative f + :: forall f . (Applicative f, HasCallStack) => AstActions f itext otext -> FilePath -> Node (Lexeme itext) diff --git a/src/Language/Cimple/Parser.y b/src/Language/Cimple/Parser.y index ed26583..942825d 100644 --- a/src/Language/Cimple/Parser.y +++ b/src/Language/Cimple/Parser.y @@ -126,6 +126,7 @@ import Language.Cimple.Tokens (LexemeClass (..)) '#undef' { L _ PpUndef _ } '\n' { L _ PpNewline _ } '/*' { L _ CmtStart _ } + '/*!' { L _ CmtStartCode _ } '/**' { L _ CmtStartDoc _ } '/** @{' { L _ CmtStartDocSection _ } '/** @} */' { L _ CmtEndDocSection _ } @@ -439,6 +440,7 @@ DeclSpecArray :: { NonTerm } DeclSpecArray : '[' ']' { Fix $ DeclSpecArray Nothing } | '[' Expr ']' { Fix $ DeclSpecArray (Just $2) } +| '[' '/*!' Expr '*/' ']' { Fix $ DeclSpecArray (Just $3) } InitialiserExpr :: { NonTerm } InitialiserExpr diff --git a/src/Language/Cimple/Tokens.hs b/src/Language/Cimple/Tokens.hs index 7153232..a5ba3ff 100644 --- a/src/Language/Cimple/Tokens.hs +++ b/src/Language/Cimple/Tokens.hs @@ -109,6 +109,7 @@ data LexemeClass | CmtPrefix | CmtIndent | CmtStart + | CmtStartCode | CmtStartBlock | CmtStartDoc | CmtStartDocSection