{-# LANGUAGE OverloadedStrings #-}
module Text.EDE.Internal.Syntax where
import Control.Lens ((.~))
import Data.Function ((&))
import Data.HashSet (HashSet)
import qualified Data.HashSet as HashSet
import Text.EDE.Internal.Types
import Text.Parser.Token.Style (CommentStyle)
import qualified Text.Parser.Token.Style as Token
import Text.Trifecta (IdentifierStyle, TokenParsing)
import qualified Text.Trifecta as Trifecta
defaultSyntax :: Syntax
defaultSyntax :: Syntax
defaultSyntax =
Syntax :: Delim -> Delim -> Delim -> Delim -> Syntax
Syntax
{ _delimPragma :: Delim
_delimPragma = (String
"{!", String
"!}"),
_delimInline :: Delim
_delimInline = (String
"{{", String
"}}"),
_delimComment :: Delim
_delimComment = (String
"{#", String
"#}"),
_delimBlock :: Delim
_delimBlock = (String
"{%", String
"%}")
}
alternateSyntax :: Syntax
alternateSyntax :: Syntax
alternateSyntax =
Syntax :: Delim -> Delim -> Delim -> Delim -> Syntax
Syntax
{ _delimPragma :: Delim
_delimPragma = (String
"@!", String
"!@"),
_delimInline :: Delim
_delimInline = (String
"<@", String
"@>"),
_delimComment :: Delim
_delimComment = (String
"@*", String
"*@"),
_delimBlock :: Delim
_delimBlock = (String
"@(", String
")@")
}
commentStyle :: String -> String -> CommentStyle
String
s String
e =
CommentStyle
Token.emptyCommentStyle CommentStyle -> (CommentStyle -> CommentStyle) -> CommentStyle
forall a b. a -> (a -> b) -> b
& (String -> Identity String)
-> CommentStyle -> Identity CommentStyle
forall (f :: * -> *).
Functor f =>
(String -> f String) -> CommentStyle -> f CommentStyle
Token.commentStart ((String -> Identity String)
-> CommentStyle -> Identity CommentStyle)
-> String -> CommentStyle -> CommentStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ String
s CommentStyle -> (CommentStyle -> CommentStyle) -> CommentStyle
forall a b. a -> (a -> b) -> b
& (String -> Identity String)
-> CommentStyle -> Identity CommentStyle
forall (f :: * -> *).
Functor f =>
(String -> f String) -> CommentStyle -> f CommentStyle
Token.commentEnd ((String -> Identity String)
-> CommentStyle -> Identity CommentStyle)
-> String -> CommentStyle -> CommentStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ String
e
operatorStyle :: TokenParsing m => IdentifierStyle m
operatorStyle :: IdentifierStyle m
operatorStyle =
IdentifierStyle m
forall (m :: * -> *). TokenParsing m => IdentifierStyle m
Token.haskellOps IdentifierStyle m
-> (IdentifierStyle m -> IdentifierStyle m) -> IdentifierStyle m
forall a b. a -> (a -> b) -> b
& (m Char -> Identity (m Char))
-> IdentifierStyle m -> Identity (IdentifierStyle m)
forall (f :: * -> *) (m :: * -> *).
Functor f =>
(m Char -> f (m Char))
-> IdentifierStyle m -> f (IdentifierStyle m)
Trifecta.styleLetter ((m Char -> Identity (m Char))
-> IdentifierStyle m -> Identity (IdentifierStyle m))
-> m Char -> IdentifierStyle m -> IdentifierStyle m
forall s t a b. ASetter s t a b -> b -> s -> t
.~ String -> m Char
forall (m :: * -> *). CharParsing m => String -> m Char
Trifecta.oneOf String
"-+!&|=><"
variableStyle :: TokenParsing m => IdentifierStyle m
variableStyle :: IdentifierStyle m
variableStyle =
IdentifierStyle m
forall (m :: * -> *). TokenParsing m => IdentifierStyle m
keywordStyle IdentifierStyle m
-> (IdentifierStyle m -> IdentifierStyle m) -> IdentifierStyle m
forall a b. a -> (a -> b) -> b
& (String -> Identity String)
-> IdentifierStyle m -> Identity (IdentifierStyle m)
forall (f :: * -> *) (m :: * -> *).
Functor f =>
(String -> f String) -> IdentifierStyle m -> f (IdentifierStyle m)
Trifecta.styleName ((String -> Identity String)
-> IdentifierStyle m -> Identity (IdentifierStyle m))
-> String -> IdentifierStyle m -> IdentifierStyle m
forall s t a b. ASetter s t a b -> b -> s -> t
.~ String
"variable"
keywordStyle :: TokenParsing m => IdentifierStyle m
keywordStyle :: IdentifierStyle m
keywordStyle =
IdentifierStyle m
forall (m :: * -> *). TokenParsing m => IdentifierStyle m
Token.haskellIdents
IdentifierStyle m
-> (IdentifierStyle m -> IdentifierStyle m) -> IdentifierStyle m
forall a b. a -> (a -> b) -> b
& (HashSet String -> Identity (HashSet String))
-> IdentifierStyle m -> Identity (IdentifierStyle m)
forall (f :: * -> *) (m :: * -> *).
Functor f =>
(HashSet String -> f (HashSet String))
-> IdentifierStyle m -> f (IdentifierStyle m)
Trifecta.styleReserved ((HashSet String -> Identity (HashSet String))
-> IdentifierStyle m -> Identity (IdentifierStyle m))
-> HashSet String -> IdentifierStyle m -> IdentifierStyle m
forall s t a b. ASetter s t a b -> b -> s -> t
.~ HashSet String
keywordSet
IdentifierStyle m
-> (IdentifierStyle m -> IdentifierStyle m) -> IdentifierStyle m
forall a b. a -> (a -> b) -> b
& (String -> Identity String)
-> IdentifierStyle m -> Identity (IdentifierStyle m)
forall (f :: * -> *) (m :: * -> *).
Functor f =>
(String -> f String) -> IdentifierStyle m -> f (IdentifierStyle m)
Trifecta.styleName ((String -> Identity String)
-> IdentifierStyle m -> Identity (IdentifierStyle m))
-> String -> IdentifierStyle m -> IdentifierStyle m
forall s t a b. ASetter s t a b -> b -> s -> t
.~ String
"keyword"
keywordSet :: HashSet String
keywordSet :: HashSet String
keywordSet =
[String] -> HashSet String
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList
[ String
"if",
String
"elif",
String
"else",
String
"case",
String
"when",
String
"for",
String
"include",
String
"let",
String
"endif",
String
"endcase",
String
"endfor",
String
"endlet",
String
"in",
String
"with",
String
"_",
String
".",
String
"true",
String
"false"
]
pragmaStyle :: TokenParsing m => IdentifierStyle m
pragmaStyle :: IdentifierStyle m
pragmaStyle =
IdentifierStyle m
forall (m :: * -> *). TokenParsing m => IdentifierStyle m
Token.haskellIdents
IdentifierStyle m
-> (IdentifierStyle m -> IdentifierStyle m) -> IdentifierStyle m
forall a b. a -> (a -> b) -> b
& (HashSet String -> Identity (HashSet String))
-> IdentifierStyle m -> Identity (IdentifierStyle m)
forall (f :: * -> *) (m :: * -> *).
Functor f =>
(HashSet String -> f (HashSet String))
-> IdentifierStyle m -> f (IdentifierStyle m)
Trifecta.styleReserved ((HashSet String -> Identity (HashSet String))
-> IdentifierStyle m -> Identity (IdentifierStyle m))
-> HashSet String -> IdentifierStyle m -> IdentifierStyle m
forall s t a b. ASetter s t a b -> b -> s -> t
.~ HashSet String
pragmaSet
IdentifierStyle m
-> (IdentifierStyle m -> IdentifierStyle m) -> IdentifierStyle m
forall a b. a -> (a -> b) -> b
& (String -> Identity String)
-> IdentifierStyle m -> Identity (IdentifierStyle m)
forall (f :: * -> *) (m :: * -> *).
Functor f =>
(String -> f String) -> IdentifierStyle m -> f (IdentifierStyle m)
Trifecta.styleName ((String -> Identity String)
-> IdentifierStyle m -> Identity (IdentifierStyle m))
-> String -> IdentifierStyle m -> IdentifierStyle m
forall s t a b. ASetter s t a b -> b -> s -> t
.~ String
"pragma field"
pragmaSet :: HashSet String
pragmaSet :: HashSet String
pragmaSet =
[String] -> HashSet String
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList
[ String
"pragma",
String
"inline",
String
"comment",
String
"block"
]