File: ProjectTemplateSpec.hs

package info (click to toggle)
haskell-project-template 0.2.1.0-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 92 kB
  • sloc: haskell: 202; makefile: 3
file content (57 lines) | stat: -rw-r--r-- 2,094 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
{-# LANGUAGE OverloadedStrings #-}
module Text.ProjectTemplateSpec where

import Test.Hspec
import Test.Hspec.QuickCheck
import Text.ProjectTemplate
import Data.Conduit
import Control.Monad.Trans.Writer (execWriterT)
import Test.QuickCheck.Arbitrary
import Data.Char (isAlphaNum)
import qualified Data.ByteString.Base64 as B64
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString as S
import qualified Data.Map as Map
import Control.Arrow (second, (***))
import Control.Applicative ((<$>))
import Data.Monoid (mconcat, mappend)

spec :: Spec
spec = do
    describe "create/unpack" $ do
        prop "is idempotent" $ \(Helper m) -> do
            m' <-
                        execWriterT
                      $ runConduit
                      $ mapM_ (yield . second return) (Map.toList m)
                     .| createTemplate
                     .| unpackTemplate receiveMem id
            let m'' = Map.fromList $ map (second $ mconcat . L.toChunks) $ Map.toList m'
            m `shouldBe` m''
    describe "binaries" $ do
        prop "works with multilines" $ \words' -> do
            let bs = S.pack words'
                encoded = joinWith "\n" 5 $ B64.encode bs
                content = "{-# START_FILE BASE64 foo #-}\n" `mappend` encoded
            m <- execWriterT $ runConduit $ yield content .| unpackTemplate receiveMem id
            Map.lookup "foo" m `shouldBe` Just (L.fromChunks [bs])

joinWith :: S.ByteString -> Int -> S.ByteString -> S.ByteString
joinWith joiner size = S.concat . map (`S.append` joiner) . chunksOf size

chunksOf :: Int -> S.ByteString -> [S.ByteString]
chunksOf _ bs | S.null bs = []
chunksOf size bs =
    let (x, y) = S.splitAt size bs
     in x : chunksOf size y

newtype Helper = Helper (Map.Map FilePath S.ByteString)
    deriving (Show, Eq)

instance Arbitrary Helper where
    arbitrary =
        Helper . Map.fromList <$> mapM (const $ (def "foo" . filter isAlphaNum *** S.pack . def (S.unpack "bar")) <$> arbitrary) [1..10 :: Int]
      where
        def x y
            | null y = x
            | otherwise = y