├── .gitignore
├── .travis.yml
├── CHANGELOG.md
├── CONTRIBUTING.md
├── LICENSE
├── README.md
├── Setup.lhs
├── karver.cabal
├── src
└── Text
│ ├── Karver.hs
│ └── Karver
│ ├── Parse.hs
│ └── Types.hs
└── test
├── Spec.hs
├── Text
├── Karver
│ ├── ParseSpec.hs
│ └── TypesSpec.hs
└── KarverSpec.hs
├── json
└── test-data.json
└── template
├── template.html
└── text.html
/.gitignore:
--------------------------------------------------------------------------------
1 | # OS Level
2 | .DS_Store
3 |
4 | # Compiled files
5 | *.o
6 | *.hi
7 |
8 | # cabal build
9 | .cabal-sandbox/
10 | cabal.sandbox.config
11 | dist/
12 |
--------------------------------------------------------------------------------
/.travis.yml:
--------------------------------------------------------------------------------
1 | language: haskell
2 | ghc:
3 | - 7.8
4 | sudo: false
5 |
--------------------------------------------------------------------------------
/CHANGELOG.md:
--------------------------------------------------------------------------------
1 | ## [0.1.2] - 2015-04-21
2 |
3 | ### Fixed
4 |
5 | * Parser stop consuming input after single `{`
6 | * Parser failing when `{` is at the end of the input
7 |
8 | ## [0.1.1] - 2013-08-28
9 |
10 | ### Changed
11 |
12 | * Data type `Tokens` to `Token`
13 | * Import structure to include `Text.Karver.Types`
14 |
15 | ### Fixed
16 |
17 | * Examples of using JSON as data
18 |
19 | ## [0.1.0] - 2013-06-21
20 |
21 | ### Added
22 |
23 | * Represent template data with JSON
24 |
25 | ## 0.0.1 - 2013-06-18
26 |
27 | ### Added
28 |
29 | * Regular template variables
30 | * Object template variables
31 | * List template variables
32 | * If expressions
33 | * For loop expressions
34 | * File importing expressions
35 |
36 | [0.1.2]: https://github.com/sourrust/karver/compare/v0.1.1...v0.1.2
37 | [0.1.1]: https://github.com/sourrust/karver/compare/v0.1.0...v0.1.1
38 | [0.1.0]: https://github.com/sourrust/karver/compare/v0.0.1...v0.1.0
39 |
--------------------------------------------------------------------------------
/CONTRIBUTING.md:
--------------------------------------------------------------------------------
1 | # How to Contribute
2 |
3 | Since karver is in early development, there is still work needed to be
4 | done. Whenever there is something that needs work on, it will typically
5 | be in [issues][1]. If there isn't issues open, try working on a feature
6 | that is in jinja, or an other template engines, that you want to see in
7 | karver.
8 |
9 | And before you start hacking on karver, here a same guide to go from add
10 | code to the project and getting it into the main repo.
11 |
12 | ### Never use the `master` branch while developing a feature.
13 |
14 | When writing a new feature use a branch name that describes what you are
15 | working one, e.g. `parse/variable-assignment` if were working on a
16 | parser for variable assignment.
17 |
18 | The `master` branch is mainly for merging and some time version bumping;
19 | but, most of the time, you are never going to touch it directly.
20 |
21 | ### Keep commits to one idea at a time.
22 |
23 | Committing small changes is the best way, for me at least, to look at
24 | what has changed during development. It is almost like a self documented
25 | changelog in the commit message.
26 |
27 | For a easy guide on how to structure you commit message just [follow
28 | tpope's, guide][2]. And if you want to make things easier on yourself,
29 | use a client for working with commit message. For me personally, I use
30 | [fugitive][3] because my editor of choice is vim.
31 |
32 | ### If the feature is a new parser or function, write a test for it.
33 |
34 | I don't care whether you write test first and then add the
35 | implementation, or vice-versa. As long as there is some kind of test,
36 | that will show that the function is working correctly, I am happy.
37 |
38 | ### Compile and run tests on feature.
39 |
40 | This the just so I know, at the very least, the code is working for you
41 | computer and you didn't break any of the other tests.
42 |
43 | ### Submit pull request using the branch you are working on.
44 |
45 | Simple as that.
46 |
47 | [1]: https://github.com/sourrust/karver/issues
48 | [2]: http://tbaggery.com/2008/04/19/a-note-about-git-commit-messages.html
49 | [3]: https://github.com/tpope/vim-fugitive
50 |
--------------------------------------------------------------------------------
/LICENSE:
--------------------------------------------------------------------------------
1 | Copyright (c) 2015, Jeremy Hull
2 | All rights reserved.
3 |
4 | Redistribution and use in source and binary forms, with or without
5 | modification, are permitted provided that the following conditions
6 | are met:
7 |
8 | * Redistributions of source code must retain the above copyright
9 | notice, this list of conditions and the following disclaimer.
10 | * Redistributions in binary form must reproduce the above copyright
11 | notice, this list of conditions and the following disclaimer in the
12 | documentation and/or other materials provided with the distribution.
13 | * Neither the name of the author nor the names of its contributors may
14 | be used to endorse or promote products derived from this software
15 | without specific prior written permission.
16 |
17 | THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
18 | "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
19 | LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
20 | A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
21 | HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
22 | SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
23 | LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
24 | DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
25 | THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
26 | (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
27 | OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
28 |
--------------------------------------------------------------------------------
/README.md:
--------------------------------------------------------------------------------
1 | # Karver
2 |
3 | [](https://travis-ci.org/sourrust/karver)
4 |
5 | Karver is a template engine written in Haskell, and the syntax is
6 | heavily inspired by [jinja2][1].
7 |
8 | The project is in early development, so it isn't as full featured or
9 | production ready as jinja is. However, karver's main focus is for
10 | Haskell programmers, wanting a template engine that is simple and has
11 | good performance.
12 |
13 | A small taste of the syntax being:
14 |
15 | ```
16 | {% if title %}
17 |
{{ title }}
18 | {% endif %}
19 |
20 |
21 | {% for item in items %}
22 |
{{ item.name }} for {{ item.price }}
23 | {% endfor %}
24 |
25 | ```
26 |
27 | # Interface of Karver
28 |
29 | The meat of karver is the `renderTemplate` function. With it's type
30 | signature being, `renderTemplate :: HashMap Text Value -> Text -> Text`,
31 | it takes a hashmap of variables being used by the template, and the
32 | template text itself. It of course returns the translated result, and
33 | since the type is `Text`, it supports Unicode right out of the box.
34 |
35 | Programs using karver might look something like:
36 |
37 | ```haskell
38 | {-# LANGUAGE OverloadedStrings #-}
39 |
40 | import Text.Karver
41 | import Data.HashMap.Strict (HashMap)
42 | import qualified Data.HashMap.Strict as H
43 | import Data.Text (Text)
44 | import qualified Data.Text.IO as T
45 | import qualified Data.Vector as V
46 |
47 | templateHashMap :: HashMap Text Value
48 | templateHashMap = H.fromList $
49 | [ ("title", Literal "Grocery List")
50 | , ("items", List $ V.fromList [ Literal "eggs"
51 | , Literal "flour"
52 | , Literal "cereal"
53 | ])
54 | ]
55 |
56 | main :: IO ()
57 | main = do
58 | tplStr <- T.readFile "path/to/template.html"
59 | let htmlStr = renderTemplate templateHashMap tplStr
60 | T.writeFile "path/to/output.html" htmlStr
61 | ```
62 |
63 | or if JSON is more your flavor:
64 |
65 | ```haskell
66 | {-# LANGUAGE OverloadedStrings #-}
67 |
68 | import Text.Karver
69 | import Data.Text (Text)
70 | import qualified Data.Text as T
71 | import qualified Data.Text.IO as TI
72 |
73 | templateHashMap :: Text
74 | templateHashMap = T.concat $
75 | [ "{ \"title\": \"Grocery List\""
76 | , ", \"items\": [ \"eggs\", \"flour\", \"cereal\" ]"
77 | , "}"
78 | ]
79 |
80 | main :: IO ()
81 | main = do
82 | tplStr <- TI.readFile "path/to/template.html"
83 | let htmlStr = renderTemplate' templateHashMap tplStr
84 | TI.writeFile "path/to/output.html" htmlStr
85 | ```
86 |
87 | ## Getting Started
88 |
89 | ```bash
90 | git clone git://github.com/sourrust/karver.git
91 | cd karver
92 | cabal configure --enable-tests
93 | ```
94 |
95 | If the configure set fails you are going to want to install the missing
96 | packages and try again. Karver is built on the [latest Haskell
97 | Platform][2] and a few other dependencies.
98 |
99 | ```bash
100 | cabal update
101 | cabal install attoparsec \
102 | hspec \
103 | unordered-containers
104 | ```
105 |
106 | And you're pretty much good to go. Just re-configure and `cabal build`
107 | and `cabal test` to run the test suite.
108 |
109 | ## Writing Tests
110 |
111 | Karver uses [`hspec`][3] for testing. Tests are located in the `test/`
112 | directory and each file, being tested, has it's own corresponding Spec
113 | file. For example, `Text/Karver/Parser.hs` in `src/`, has a spec file
114 | `Text/Karver/ParserSpec.hs` inside of `test/`. Follow this rule if you
115 | add a new file that you want to test, because [`Spec.hs`][4] discovers
116 | the files with the name, so it needs Spec prefixing the file name for
117 | hspec to add it to the suite.
118 |
119 | Now, actually writing the test is pretty simple.
120 |
121 | ```haskell
122 | describe "function you are testing" $ do
123 | it "case you will test for" $ do
124 | let value = -- result from the function you are testing
125 | expected = -- what you expect the value to be
126 | value `shouldBe` expected
127 | ```
128 |
129 | You can add more variable if needed, but the **value should be
130 | expected**, is just my personal preference to how the test should end.
131 |
132 | [1]: http://jinja.pocoo.org/
133 | [2]: http://www.haskell.org/platform/
134 | [3]: http://hspec.github.io/
135 | [4]: https://github.com/sourrust/karver/blob/master/test/Spec.hs
136 |
--------------------------------------------------------------------------------
/Setup.lhs:
--------------------------------------------------------------------------------
1 | #!/usr/bin/env runhaskell
2 | > import Distribution.Simple
3 | > main = defaultMain
4 |
--------------------------------------------------------------------------------
/karver.cabal:
--------------------------------------------------------------------------------
1 | name: karver
2 | version: 0.1.2
3 | cabal-version: >= 1.8
4 | build-type: Simple
5 | license: BSD3
6 | license-file: LICENSE
7 | copyright: (c) 2015 Jeremy Hull
8 | author: Jeremy Hull
9 | maintainer: Jeremy Hull
10 | bug-reports: https://github.com/sourrust/karver/issues
11 | stability: experimental
12 | category: Text
13 | tested-with: GHC == 7.4.2
14 | synopsis: A simple template engine, inspired by jinja2
15 | description: Karver is heavily inspired by the python project jinja2,
16 | at least syntactic wise. This template engine strives to
17 | be simple and fast, leveraging libraries like attoparsec
18 | and data types like Text.
19 |
20 | source-repository head
21 | type: git
22 | location: git://github.com/sourrust/karver.git
23 |
24 | library
25 | ghc-options: -Wall
26 | -fno-warn-unused-do-bind
27 | hs-source-dirs: src
28 | exposed-modules:
29 | Text.Karver
30 | Text.Karver.Parse
31 | Text.Karver.Types
32 | build-depends: base >= 4 && < 5,
33 | text >= 0.11,
34 | unordered-containers >= 0.2,
35 | vector >= 0.10,
36 | attoparsec >= 0.12,
37 | bytestring >= 0.10,
38 | aeson >= 0.6
39 |
40 | test-suite spec
41 | type: exitcode-stdio-1.0
42 | ghc-options: -Wall -Werror
43 | hs-source-dirs: test
44 | main-is: Spec.hs
45 | build-depends: base >= 4 && < 5,
46 | karver,
47 | text >= 0.11,
48 | aeson >= 0.6,
49 | unordered-containers >= 0.2,
50 | attoparsec >= 0.12,
51 | vector >= 0.10,
52 | hspec >= 1.5
53 |
--------------------------------------------------------------------------------
/src/Text/Karver.hs:
--------------------------------------------------------------------------------
1 | -- |
2 | -- Module: Data.Karver
3 | -- Copyright: Jeremy Hull 2015
4 | -- License: BSD3
5 | --
6 | -- Maintainer: Jeremy Hull
7 | -- Stability: experimental
8 | -- Portability: unknown
9 | --
10 | -- The "Text.Karver" interface for translation 'Text' from it's template
11 | -- syntax, to a generated value — based on the data that was given.
12 |
13 | module Text.Karver
14 | ( renderTemplate
15 | , renderTemplate'
16 | , module Text.Karver.Types
17 | ) where
18 |
19 | import Text.Karver.Types
20 | import Text.Karver.Parse
21 |
22 | import Control.Applicative ((<$>))
23 | import Data.Aeson (decode')
24 | import Data.Attoparsec.Text
25 | import qualified Data.ByteString.Lazy.Char8 as L
26 | import Data.HashMap.Strict (HashMap)
27 | import qualified Data.HashMap.Strict as H
28 | import Data.Text (Text)
29 | import qualified Data.Text as T
30 | import qualified Data.Text.IO as TI
31 | import qualified Data.Vector as V
32 | import System.IO.Unsafe (unsafePerformIO)
33 |
34 | -- | Renders a template
35 | renderTemplate :: HashMap Text Value -- ^ Data map for variables inside
36 | -- a given template
37 | -> Text -- ^ Template
38 | -> Text
39 | renderTemplate varTable = encode
40 | where encode :: Text -> Text
41 | encode tlp
42 | | T.null tlp = tlp
43 | | otherwise = merge $
44 | case parseOnly templateParser tlp of
45 | (Left err) -> [LiteralTok $ T.pack err]
46 | (Right res) -> res
47 |
48 | merge :: [Token] -> Text
49 | merge = T.concat . map (decodeToken varTable)
50 | decodeToken _ (LiteralTok x) = x
51 | decodeToken vTable (IdentityTok x) =
52 | case H.lookup x vTable of
53 | (Just (Literal s)) -> s
54 | _ -> T.empty
55 | decodeToken vTable (ObjectTok i k) =
56 | case H.lookup i vTable of
57 | (Just (Object m)) -> maybe T.empty id $ H.lookup k m
58 | _ -> T.empty
59 | decodeToken vTable (ListTok a i) =
60 | case H.lookup a vTable of
61 | (Just (List l)) -> case l V.! i of
62 | (Literal t) -> t
63 | _ -> T.empty
64 | _ -> T.empty
65 | decodeToken _ (ConditionTok c t f) =
66 | encode $ if hasVariable c then t else f
67 | where hasVariable txt =
68 | case parseOnly variableParser' txt of
69 | (Right res) -> not . T.null $ decodeToken varTable res
70 | _ -> False
71 | decodeToken vTable (LoopTok a v b) =
72 | case H.lookup a vTable of
73 | (Just (List l)) ->
74 | let toks = either (\_ -> []) id $ parseOnly templateParser b
75 | mapVars x = let vTable' = H.insert v x vTable
76 | in map (decodeToken vTable') toks
77 | in if null toks
78 | then T.empty
79 | else T.concat . V.toList $ V.map (T.concat . mapVars) l
80 | _ -> T.empty
81 | decodeToken _ (IncludeTok f) =
82 | unsafePerformIO $ encode . T.init <$> TI.readFile (T.unpack f)
83 |
84 | -- | Similar to renderTemplate, only it takes JSON 'Text' instead of
85 | -- a 'HashMap'
86 | renderTemplate' :: Text -- ^ JSON data, for variables inside a given
87 | -- template
88 | -> Text -- ^ Template
89 | -> Text
90 | renderTemplate' json tpl =
91 | case decode' . L.pack $ T.unpack json of
92 | (Just hash) -> renderTemplate hash tpl
93 | Nothing -> T.empty
94 |
--------------------------------------------------------------------------------
/src/Text/Karver/Parse.hs:
--------------------------------------------------------------------------------
1 | -- |
2 | -- Module: Data.Karver.Parse
3 | -- Copyright: Jeremy Hull 2015
4 | -- License: BSD3
5 | --
6 | -- Maintainer: Jeremy Hull
7 | -- Stability: experimental
8 | -- Portability: unknown
9 | --
10 | -- All the 'Parser's are defined here, including the one used by the top
11 | -- level module "Text.Karver".
12 |
13 | {-# LANGUAGE OverloadedStrings #-}
14 |
15 | module Text.Karver.Parse
16 | ( templateParser
17 | , literalParser
18 | , variableParser
19 | , variableParser'
20 | , conditionParser
21 | , loopParser
22 | , includeParser
23 | ) where
24 |
25 | import Prelude hiding (take)
26 |
27 | import Text.Karver.Types
28 |
29 | import Data.Attoparsec.Text
30 | import Data.Attoparsec.Combinator (lookAhead)
31 | import Data.Monoid ((<>))
32 | import Data.Text (Text, empty, pack)
33 | import Control.Applicative ((<|>), (<$>), (*>), (<*))
34 |
35 | -- | Top level 'Parser' that will translate 'Text' into ['Token']
36 | templateParser :: Parser [Token]
37 | templateParser = many1 $ choice [ variableParser
38 | , conditionParser
39 | , loopParser
40 | , literalParser
41 | , includeParser
42 | ]
43 |
44 |
45 | -- | Takes everything until it reaches a @{@, resulting in the 'LiteralTok'
46 | literalParser :: Parser Token
47 | literalParser = LiteralTok <$> _literalParser
48 | where
49 | _literalParser = do
50 | html <- takeWhile1 (/= '{')
51 | isEnd <- atEnd
52 | if isEnd
53 | then return html
54 | else _continueParsing html
55 |
56 | _continueParsing html = do
57 | peek <- lookAhead $ take 2 <|> take 1
58 | case peek of
59 | "{{" -> return html
60 | "{%" -> return html
61 | "{" -> (html <>) <$> take 1
62 | _ -> do
63 | currentText <- (html <>) <$> take 1
64 | (currentText <>) <$> _literalParser
65 |
66 | -- General function for making parsers that will be surrounded by a curtain
67 | -- delimiter — which has both a beginning and end.
68 | delimiterParser :: Text -> Text -> Parser a -> Parser a
69 | delimiterParser begin end parseFunc = do
70 | string begin
71 | skipSpace
72 | val <- parseFunc
73 | skipSpace
74 | string end
75 | return val
76 |
77 | identityDelimiter, expressionDelimiter :: Parser a -> Parser a
78 |
79 | identityDelimiter = delimiterParser "{{" "}}"
80 | expressionDelimiter = delimiterParser "{%" "%}"
81 |
82 | -- General parser for the several variable types. It is basically used to
83 | -- not repeat parsers with and without a delimiter.
84 | variableParser_ :: (Parser Token -> Parser Token) -> Parser Token
85 | variableParser_ fn = fn $ do
86 | ident <- takeTill (inClass " .[}")
87 | peek <- peekChar
88 | case peek of
89 | (Just '[') -> do
90 | char '['
91 | idx <- decimal
92 | char ']'
93 | return $ ListTok ident idx
94 | (Just '.') -> do
95 | char '.'
96 | key <- takeTill (inClass " }")
97 | return $ ObjectTok ident key
98 | (Just ' ') -> return $ IdentityTok ident
99 | (Just '}') -> return $ IdentityTok ident
100 | Nothing -> return $ IdentityTok ident
101 | _ -> fail "variableParser_: failed with no token to apply."
102 |
103 | variableParser, variableParser' :: Parser Token
104 |
105 | -- | 'Parser' for all the variable types. Returning on of the following
106 | -- 'Token's:
107 | --
108 | -- * 'IncludeTok'
109 | --
110 | -- * 'ListTok'
111 | --
112 | -- * 'ObjectTok'
113 | variableParser = variableParser_ identityDelimiter
114 |
115 | -- | 'Parser' for all the variable types. Returning on of the following
116 | -- 'Token's:
117 | --
118 | -- * 'IncludeTok'
119 | --
120 | -- * 'ListTok'
121 | --
122 | -- * 'ObjectTok'
123 | --
124 | -- This is without the delimiter
125 | variableParser' = variableParser_ id
126 |
127 | -- Parser for skipping over horizontal space and end on a newline
128 | -- character, which will be skipped as well.
129 | skipSpaceTillEOL :: Parser ()
130 | skipSpaceTillEOL = option () $ skipWhile isHorizontalSpace >> endOfLine
131 | {-# INLINE skipSpaceTillEOL #-}
132 |
133 | -- | 'Parser' for if statements, that will result in the 'ConditionTok'
134 | conditionParser :: Parser Token
135 | conditionParser = do
136 | logic <- expressionDelimiter $ do
137 | string "if"
138 | skipSpace
139 | condition <- takeTill (inClass " %")
140 | return condition
141 | let anyTill = manyTill anyChar
142 | ifparse = skipSpaceTillEOL *> anyTill (expressionDelimiter
143 | $ string "endif"
144 | <|> string "else")
145 | elseparse = skipSpaceTillEOL *> anyTill (expressionDelimiter
146 | $ string "endif")
147 | ifbody <- pack <$> ifparse
148 | elsebody <- option empty (pack <$> elseparse)
149 | skipSpaceTillEOL
150 | return $ ConditionTok logic ifbody elsebody
151 |
152 | -- | 'Parser' for for loops, that will result in the 'LoopTok'
153 | loopParser :: Parser Token
154 | loopParser = do
155 | (arr, var) <- expressionDelimiter $ do
156 | string "for"
157 | skipSpace
158 | varName <- takeTill (== ' ')
159 | skipSpace
160 | string "in"
161 | skipSpace
162 | arrName <- takeTill (inClass " %")
163 | return (arrName, varName)
164 | skipSpaceTillEOL
165 | loopbody <- manyTill anyChar (expressionDelimiter $ string "endfor")
166 | skipSpaceTillEOL
167 | return $ LoopTok arr var $ pack loopbody
168 |
169 | -- | 'Parser' for includes, that will result in 'IncludeTok'
170 | includeParser :: Parser Token
171 | includeParser = expressionDelimiter $ do
172 | let quote c = char c *> takeTill (== c) <* char c
173 | string "include"
174 | skipSpace
175 | filepath <- quote '"' <|> quote '\''
176 | return $ IncludeTok filepath
177 |
--------------------------------------------------------------------------------
/src/Text/Karver/Types.hs:
--------------------------------------------------------------------------------
1 | -- |
2 | -- Module: Data.Karver.Types
3 | -- Copyright: Jeremy Hull 2015
4 | -- License: BSD3
5 | --
6 | -- Maintainer: Jeremy Hull
7 | -- Stability: experimental
8 | -- Portability: unknown
9 | --
10 | -- Base types used throughout Karver.
11 |
12 | module Text.Karver.Types
13 | ( Token(..)
14 | , Value(..)
15 | ) where
16 |
17 | import Control.Applicative ((<$>))
18 | import qualified Data.Aeson as A
19 | import Data.Text (Text)
20 | import Data.HashMap.Strict
21 | import Data.Vector
22 |
23 | -- | When dealing with the syntax of karver, we first translate the given
24 | -- 'Text' into 'Token's for easier manipulation. Each 'Token' type is
25 | -- a representation of a certain type of data.
26 | data Token = LiteralTok Text
27 | -- ^ Literal token. This is the default 'Token' that gets
28 | -- matched only if it isn't any of the others.
29 | | IdentityTok Text
30 | -- ^ Identity token. This is for a regular variable with no
31 | -- sign of it being an object or list. eg. {{ ident }}
32 | | ObjectTok Text Text
33 | -- ^ Object token. This is similar to 'IdentityTok', but if
34 | -- there is a dot, it gets placed in the second value. The
35 | -- first 'Text' is the object name, while the second 'Text'
36 | -- is the key to the object. eg. {{ ident.key }}
37 | | ListTok Text Int
38 | -- ^ List token. This is also similar to the 'IdentityTok', but
39 | -- if there is an opening square bracket, it gets place in
40 | -- the second value. 'Text' is the list name, while 'Int' is
41 | -- the index. eg {{ ident[4] }}
42 | | ConditionTok Text Text Text
43 | -- ^ If statement token. The first 'Text' will be the check if
44 | -- a identity is available or not. Second 'Text' is the body
45 | -- of the if statement. And the third 'Text' is the else body
46 | -- — if their isn't one, it will be empty.
47 | | LoopTok Text Text Text
48 | -- ^ For loop token. The first 'Text' is the list that will be
49 | -- iterated over. Second 'Text' is the variable name a single
50 | -- element of the list will be placed into. Third 'Text' is
51 | -- the body of the loop that will be repeatedly translated
52 | -- from.
53 | | IncludeTok Text
54 | -- ^ Include token. The 'Text' value store a file name, which
55 | -- includes its relative path, based on the current working
56 | -- directory.
57 | deriving (Show, Eq)
58 |
59 | -- | Fairly basic work around for using different types inside a 'HashMap'.
60 | -- The 'Value' type also make it possible for 'List' to contain more than
61 | -- one type.
62 | data Value = Literal Text
63 | -- ^ The base value for the storing of variable.
64 | | Object (HashMap Text Text)
65 | -- ^ An alias for 'HashMap', that will only hold 'Text' with
66 | -- 'Text' as a key as well.
67 | | List (Vector Value)
68 | -- ^ An alias for 'Vector', that can hold all three 'Value's
69 | -- — which isn't desirable, because their can be nested
70 | -- 'List's.
71 | deriving (Show, Eq)
72 |
73 | instance A.FromJSON Value where
74 | parseJSON o@(A.Object _) = Object <$> A.parseJSON o
75 | parseJSON a@(A.Array _) = List <$> A.parseJSON a
76 | parseJSON v = Literal <$> A.parseJSON v
77 | {-# INLINE parseJSON #-}
78 |
--------------------------------------------------------------------------------
/test/Spec.hs:
--------------------------------------------------------------------------------
1 | {-# OPTIONS_GHC -F -pgmF hspec-discover #-}
2 |
--------------------------------------------------------------------------------
/test/Text/Karver/ParseSpec.hs:
--------------------------------------------------------------------------------
1 | {-# LANGUAGE OverloadedStrings #-}
2 |
3 | module Text.Karver.ParseSpec (spec) where
4 |
5 | import Text.Karver.Parse
6 | import Text.Karver.Types
7 |
8 | import Prelude hiding (concat, unlines)
9 | import Data.Attoparsec.Text (parseOnly)
10 | import Data.Text (Text, concat, empty, pack, unlines)
11 | import Test.Hspec
12 |
13 | literal, variable, condition, loop, include
14 | :: Text -> Either String Token
15 | literal = parseOnly literalParser
16 | variable = parseOnly variableParser
17 | condition = parseOnly conditionParser
18 | loop = parseOnly loopParser
19 | include = parseOnly includeParser
20 |
21 | noDemVariable :: Text -> Either String Token
22 | noDemVariable = parseOnly variableParser'
23 |
24 | isLeft :: Either a b -> Bool
25 | isLeft (Left _) = True
26 | isLeft _ = False
27 |
28 | spec :: Spec
29 | spec = do
30 | describe "literalParser" $ do
31 | it "should return Left with an empty string" $ do
32 | let noText = empty
33 | value = literal noText
34 |
35 | value `shouldSatisfy` isLeft
36 |
37 | it "should continue parsing after `{`" $ do
38 | let text = "a{ should parse"
39 | value = literal text
40 | expected = Right $ LiteralTok text
41 |
42 | value `shouldBe` expected
43 |
44 | it "should stop parsing on `{{`" $ do
45 | let text = "a{{ should not parse"
46 | value = literal text
47 | expected = Right $ LiteralTok "a"
48 |
49 | value `shouldBe` expected
50 |
51 | it "should stop parsing on `{%`" $ do
52 | let text = "a{% should not parse"
53 | value = literal text
54 | expected = Right $ LiteralTok "a"
55 |
56 | value `shouldBe` expected
57 |
58 | it "should not fail with `{` at the end" $ do
59 | let text = "a sentence with {"
60 | value = literal text
61 | expected = Right $ LiteralTok text
62 |
63 | value `shouldBe` expected
64 |
65 | it "should parse all the way to the end" $ do
66 | let fullText = "all this text is here"
67 | value = literal fullText
68 | expected = Right $ LiteralTok fullText
69 |
70 | value `shouldBe` expected
71 |
72 | describe "identityParser" $ do
73 | it "should return Left with an empty string" $ do
74 | let noText = empty
75 | value = variable noText
76 |
77 | value `shouldSatisfy` isLeft
78 |
79 | it "should parse identity with spaces" $ do
80 | let regText = "{{ name }}"
81 | value = variable regText
82 | expected = Right $ IdentityTok "name"
83 |
84 | value `shouldBe` expected
85 |
86 | it "should parse identity without spaces" $ do
87 | let regText = "{{name}}"
88 | value = variable regText
89 | expected = Right $ IdentityTok "name"
90 |
91 | value `shouldBe` expected
92 |
93 | it "should parse identity with space to the left" $ do
94 | let rText = "{{ name}}"
95 | value = variable rText
96 | expected = Right $ IdentityTok "name"
97 |
98 | value `shouldBe` expected
99 |
100 | it "should parse identity with space to the right" $ do
101 | let lText = "{{name }}"
102 | value = variable lText
103 | expected = Right $ IdentityTok "name"
104 |
105 | value `shouldBe` expected
106 |
107 | it "should parse identity with multiple spaces" $ do
108 | let multiText = "{{ name }}"
109 | value = variable multiText
110 | expected = Right $ IdentityTok "name"
111 |
112 | value `shouldBe` expected
113 |
114 | describe "objectParser" $ do
115 | it "should parse normal object variables" $ do
116 | let regObj = "{{ person.name }}"
117 | value = variable regObj
118 | expected = Right $ ObjectTok "person" "name"
119 |
120 | value `shouldBe` expected
121 |
122 | describe "arrayParser" $ do
123 | it "should parse normal array variables" $ do
124 | let regList = "{{ names[1] }}"
125 | value = variable regList
126 | expected = Right $ ListTok "names" 1
127 |
128 | value `shouldBe` expected
129 |
130 | it "should parse array with max number index" $ do
131 | let maxInt = maxBound
132 | regList = concat [ "{{ names["
133 | , (pack $ show maxInt)
134 | , "] }}"
135 | ]
136 | value = variable regList
137 | expected = Right $ ListTok "names" maxInt
138 |
139 | value `shouldBe` expected
140 |
141 | describe "conditionParser" $ do
142 | it "should parse single line if statement" $ do
143 | let ifText = "{% if title %}{{ title }}{% endif %}"
144 | value = condition ifText
145 | expected = Right $ ConditionTok "title" "{{ title }}" empty
146 |
147 | value `shouldBe` expected
148 |
149 | it "should parse multi line if statement" $ do
150 | let ifText = unlines [ "{% if title %}"
151 | , " {{ title }}"
152 | , "{% endif %}"
153 | ]
154 | value = condition ifText
155 | expected = Right $ ConditionTok "title" " {{ title }}\n" empty
156 |
157 | value `shouldBe` expected
158 |
159 | it "should parse single line if else statement" $ do
160 | let ifelse = concat [ "{% if title %}{{ title }}{% else %}"
161 | , "no title{% endif %}"
162 | ]
163 | value = condition ifelse
164 | expected = Right $ ConditionTok "title" "{{ title }}" "no title"
165 |
166 | value `shouldBe` expected
167 |
168 | it "should parse multi line if else statement" $ do
169 | let ifText = unlines [ "{% if title %}"
170 | , " {{ title }}"
171 | , "{% else %}"
172 | , " title"
173 | , "{% endif %}"
174 | ]
175 | value = condition ifText
176 | expected = Right $ ConditionTok "title"
177 | " {{ title }}\n"
178 | " title\n"
179 |
180 | value `shouldBe` expected
181 |
182 | describe "loopParser" $ do
183 | it "should parse single line for loop" $ do
184 | let loopText = concat [ "{% for item in items %}"
185 | , " {{ item }}"
186 | , "{% endfor %}"
187 | ]
188 | value = loop loopText
189 | expected = Right $ LoopTok "items" "item" " {{ item }}"
190 |
191 | value `shouldBe` expected
192 |
193 | it "should parse multi line for loop" $ do
194 | let loopText = unlines [ "{% for item in items %}"
195 | , " {{ item }}"
196 | , "{% endfor %}"
197 | ]
198 | value = loop loopText
199 | expected = Right $ LoopTok "items" "item" " {{ item }}\n"
200 |
201 | value `shouldBe` expected
202 |
203 | describe "includeParser" $ do
204 | it "should import file with single quotes" $ do
205 | let includeText = "{% include 'template.html' %}"
206 | value = include includeText
207 | expected = Right $ IncludeTok "template.html"
208 |
209 | value `shouldBe` expected
210 |
211 | it "should import file with double quotes" $ do
212 | let includeText = "{% include \"template.html\" %}"
213 | value = include includeText
214 | expected = Right $ IncludeTok "template.html"
215 |
216 | value `shouldBe` expected
217 |
218 | describe "no delimiter" $ do
219 | it "should parse identity variable" $ do
220 | let value = noDemVariable "name"
221 | expected = Right $ IdentityTok "name"
222 |
223 | value `shouldBe` expected
224 |
225 | it "should parse object variable" $ do
226 | let value = noDemVariable "project.name"
227 | expected = Right $ ObjectTok "project" "name"
228 |
229 | value `shouldBe` expected
230 |
231 | it "should parse list variable" $ do
232 | let value = noDemVariable "names[4]"
233 | expected = Right $ ListTok "names" 4
234 |
235 | value `shouldBe` expected
236 |
--------------------------------------------------------------------------------
/test/Text/Karver/TypesSpec.hs:
--------------------------------------------------------------------------------
1 | {-# LANGUAGE OverloadedStrings #-}
2 |
3 | module Text.Karver.TypesSpec (spec) where
4 |
5 | import Text.Karver.Types
6 |
7 | import Data.Aeson (decode')
8 | import qualified Data.HashMap.Strict as H
9 | import Data.Monoid ((<>))
10 | import qualified Data.Vector as V
11 | import Test.Hspec
12 |
13 | spec :: Spec
14 | spec = do
15 | describe "Coverting JSON to HashMap" $ do
16 | it "should decode a list with one Literal" $ do
17 | let json = "[ \"Some text\" ]"
18 | value = decode' json
19 | expected = Just . List $ V.fromList [Literal "Some text"]
20 |
21 | value `shouldBe` expected
22 |
23 | it "should decode a list with one Literal and one Object" $ do
24 | let json = "[ \"Sample\", { \"key\": \"value\" } ]"
25 | value = decode' json
26 | expected = Just . List $ V.fromList
27 | [ Literal "Sample"
28 | , Object $ H.fromList [ ("key", "value") ]
29 | ]
30 |
31 | value `shouldBe` expected
32 |
33 | it "should decode an object with one key and value" $ do
34 | let json = "{ \"name\": \"value\" }"
35 | value = decode' json
36 | expected = Just . Object $ H.fromList [ ("name", "value") ]
37 |
38 | value `shouldBe` expected
39 |
40 | it "should decode an object with many keys and values" $ do
41 | let json = "{ \"name\": \"one\", \"value\": \"two\""
42 | <> ", \"key\": \"three\" }"
43 | value = decode' json
44 | expected = Just . Object $ H.fromList
45 | [ ("name", "one")
46 | , ("value", "two")
47 | , ("key", "three")
48 | ]
49 |
50 | value `shouldBe` expected
51 |
--------------------------------------------------------------------------------
/test/Text/KarverSpec.hs:
--------------------------------------------------------------------------------
1 | {-# LANGUAGE OverloadedStrings #-}
2 |
3 | module Text.KarverSpec (spec) where
4 |
5 | import Text.Karver
6 |
7 | import Prelude hiding (unlines, concat)
8 | import Data.Text (Text, append, concat, empty, unlines)
9 | import qualified Data.Text.IO as TI
10 | import System.IO.Unsafe (unsafePerformIO)
11 | import Test.Hspec
12 |
13 | renderer :: Text -> Text
14 | renderer t =
15 | let json = unsafePerformIO $ TI.readFile "test/json/test-data.json"
16 | in renderTemplate' json t
17 |
18 | spec :: Spec
19 | spec = do
20 | describe "renderTemplate" $ do
21 | it "should render template with identity at the end" $ do
22 | let endText = "Template engine named {{ project }}"
23 | value = renderer endText
24 | expected = "Template engine named karver"
25 |
26 | value `shouldBe` expected
27 |
28 | it "should render template with identity at the beginning" $ do
29 | let beginText = "{{ language }} is what we are written in."
30 | value = renderer beginText
31 | expected = "haskell is what we are written in."
32 |
33 | value `shouldBe` expected
34 |
35 | it "should render template with identity in the middle" $ do
36 | let middleText = "All kept in a {{ ver-control }} repo, on Github."
37 | value = renderer middleText
38 | expected = "All kept in a git repo, on Github."
39 |
40 | value `shouldBe` expected
41 |
42 | it "should render template with multiple identities" $ do
43 | let multiText = append "{{ project }} is written in {{ language }}"
44 | ", held in {{ ver-control }}."
45 | value = renderer multiText
46 | expected = "karver is written in haskell, held in git."
47 |
48 | value `shouldBe` expected
49 |
50 | it "should render template with multiple lines of identities" $ do
51 | let multiText = unlines
52 | [ "{{ project }} is the name"
53 | , "making template is my game"
54 | , "if need something done faster"
55 | , "you need something written in {{ language }}"
56 | ]
57 | value = renderer multiText
58 | expected = unlines
59 | [ "karver is the name"
60 | , "making template is my game"
61 | , "if need something done faster"
62 | , "you need something written in haskell"
63 | ]
64 |
65 | value `shouldBe` expected
66 |
67 | it "should render template with object identity" $ do
68 | let objText = "Templating with {{ template.name }} is easy."
69 | value = renderer objText
70 | expected = "Templating with karver is easy."
71 |
72 | value `shouldBe` expected
73 |
74 | it "should render template with a mix of object and identity #1" $ do
75 | let mixText = "My {{ project }} is your {{ template.name }}."
76 | value = renderer mixText
77 | expected = "My karver is your karver."
78 |
79 | value `shouldBe` expected
80 |
81 | it "should render template with a mix of object and identity #2" $ do
82 | let mixText = "My {{ template.name }} is your {{ project }}."
83 | value = renderer mixText
84 | expected = "My karver is your karver."
85 |
86 | value `shouldBe` expected
87 |
88 | it "should render template with a list identity" $ do
89 | let arrText = "karver uses {{ libraries[0] }} for parsing."
90 | value = renderer arrText
91 | expected = "karver uses attoparsec for parsing."
92 |
93 | value `shouldBe` expected
94 |
95 | it "should render template with a mix of list and identity" $ do
96 | let arrText = "{{ project }} uses {{ libraries[1] }} for testing."
97 | value = renderer arrText
98 | expected = "karver uses hspec for testing."
99 |
100 | value `shouldBe` expected
101 |
102 | it "should render template with a mix of list and object" $ do
103 | let arrText = append "{{ template.name }} uses"
104 | " {{ libraries[1] }} for testing."
105 | value = renderer arrText
106 | expected = "karver uses hspec for testing."
107 |
108 | value `shouldBe` expected
109 |
110 | it "should render template with true evaluated if" $ do
111 | let trueText = "{% if project %}{{ project }}{% endif %} is true"
112 | value = renderer trueText
113 | expected = "karver is true"
114 |
115 | value `shouldBe` expected
116 |
117 | it "should not render template with false evaluated if" $ do
118 | let falseText = concat [ "{% if closed %}"
119 | , " karver is closed source"
120 | , "{% endif %}"
121 | ]
122 | value = renderer falseText
123 | expected = empty
124 |
125 | value `shouldBe` expected
126 |
127 | it "should check if object element exists" $ do
128 | let elemText = concat [ "{% if template.name %}"
129 | , " {{ template.name }} is the template."
130 | , "{% endif %}"
131 | ]
132 | value = renderer elemText
133 | expected = " karver is the template."
134 |
135 | value `shouldBe` expected
136 |
137 | it "should check if list element exists" $ do
138 | let elemText = concat [ "{% if libraries[1] %}"
139 | , concat [ " {{ libraries[1] }} makes"
140 | , " testing enjoyable!"
141 | ]
142 | , "{% endif %}"
143 | ]
144 | value = renderer elemText
145 | expected = " hspec makes testing enjoyable!"
146 |
147 | value `shouldBe` expected
148 |
149 | it "should render template of false evaluated if else" $ do
150 | let falseText = concat [ "{% if closed %}"
151 | , " karver is closed source"
152 | , "{% else %}"
153 | , " karver is open source"
154 | , "{% endif %}"
155 | ]
156 | value = renderer falseText
157 | expected = " karver is open source"
158 |
159 | value `shouldBe` expected
160 |
161 | it "should render template of false evaluated if else, for objects" $ do
162 | let elemText = concat [ "{% if template.license %}"
163 | , " {{ template.license }} is the license."
164 | , "{% else %}"
165 | , " BSD3 is the license."
166 | , "{% endif %}"
167 | ]
168 | value = renderer elemText
169 | expected = " BSD3 is the license."
170 |
171 | value `shouldBe` expected
172 |
173 | it "should render template looping over an array #1" $ do
174 | let loopText = concat [ "Some libraries used: "
175 | , "{% for library in libraries %}"
176 | , "{{ library }} "
177 | , "{% endfor %}."
178 | ]
179 | value = renderer loopText
180 | expected = "Some libraries used: attoparsec hspec ."
181 |
182 | value `shouldBe` expected
183 |
184 | it "should render template looping over an array #2" $ do
185 | let loopText = unlines [ "Some libraries used:"
186 | , "{% for library in libraries %}"
187 | , " * {{ library }}"
188 | , "{% endfor %}"
189 | ]
190 | value = renderer loopText
191 | expected = unlines [ "Some libraries used:"
192 | , " * attoparsec"
193 | , " * hspec"
194 | ]
195 |
196 | value `shouldBe` expected
197 |
198 | it "should render template looping over an array with objects #1" $ do
199 | let withObj = concat [ "{% for title in titles %}"
200 | , ""
201 | , "{{ title.name }}"
202 | , "{% endfor %}"
203 | ]
204 | value = renderer withObj
205 | expected = concat [ ""
206 | , "Karver the Template"
207 | , "BDD with Hspec"
208 | , ""
209 | , "Attoparsec the Parser"
210 | ]
211 |
212 | value `shouldBe` expected
213 |
214 | it "should render template looping over an array with objects #2" $ do
215 | let withObj = unlines [ "{% for title in titles %}"
216 | , concat [ ""
217 | , "{{ title.name }}"
218 | ]
219 | , "{% endfor %}"
220 | ]
221 | value = renderer withObj
222 | expected = unlines [ concat [ ""
223 | , "Karver the Template"
224 | ]
225 | , "BDD with Hspec"
226 | , concat [ ""
227 | , "Attoparsec the Parser"
228 | ]
229 | ]
230 |
231 | value `shouldBe` expected
232 |
233 | it "should include a template alone" $ do
234 | let includeText = "{% include 'test/template/text.html' %}"
235 | value = renderer includeText
236 | expected = "Content in the file."
237 |
238 | value `shouldBe` expected
239 |
240 | it "should include a template surrounded by markup #1" $ do
241 | let includeText = concat [ ""
244 | ]
245 | value = renderer includeText
246 | expected = ""
247 |
248 | value `shouldBe` expected
249 |
250 | it "should include a template surrounded by markup #2" $ do
251 | let includeText = unlines [ "