module B9.Content.AST ( ConcatableSyntax (..)
, ASTish(..)
, AST(..)
, CanRender(..)
) where
import qualified Data.ByteString as B
import Data.Semigroup
import Data.Data
import Control.Applicative
import Control.Monad.IO.Class
import Control.Monad.Reader
import B9.Content.StringTemplate
import Test.QuickCheck
import B9.QCUtil
class (Semigroup a) => ConcatableSyntax a where
decodeSyntax :: FilePath -> B.ByteString -> Either String a
encodeSyntax :: a -> B.ByteString
instance ConcatableSyntax B.ByteString where
decodeSyntax _ = Right
encodeSyntax = id
data AST c a = ASTObj [(String, AST c a)]
| ASTArr [AST c a]
| ASTMerge [AST c a]
| ASTEmbed c
| ASTString String
| ASTParse SourceFile
| AST a
deriving (Read, Show, Typeable, Data, Eq)
class (ConcatableSyntax a) => ASTish a where
fromAST :: (CanRender c
,Applicative m
,Monad m
,MonadIO m
,MonadReader Environment m)
=> AST c a
-> m a
class CanRender c where
render :: (Functor m
,Applicative m
,MonadIO m
,MonadReader Environment m)
=> c
-> m B.ByteString
instance (Arbitrary c, Arbitrary a) => Arbitrary (AST c a) where
arbitrary = oneof [ASTObj <$> smaller (listOf ((,)
<$> arbitrary
<*> arbitrary))
,ASTArr <$> smaller (listOf arbitrary)
,ASTMerge <$> sized
(\s -> resize (max 2 s)
(listOf (halfSize arbitrary)))
,ASTEmbed <$> smaller arbitrary
,ASTString <$> arbitrary
,ASTParse <$> smaller arbitrary
,AST <$> smaller arbitrary
]