module Generation.TemplateCompiler where
import Data.Data
import Data.DeriveTH
import qualified Data.Text.Lazy as TL
import Data.Typeable ()
import Paths_harmony
import Test.QuickCheck
import Text.Hastache
import Text.Hastache.Context
data StrValue = StrValue { value :: String } deriving (Show, Data, Typeable, Eq)
data EnumValues = EnumValue { values :: [StrValue] } deriving (Show, Data, Typeable, Eq)
data SchemaVar = SchemaVar { varName :: String
, varType :: String
, isList :: Bool
, isEnum :: Maybe EnumValues
, isStruct :: Bool
, isKey :: Bool
, isRequired :: Bool
, isHidden :: Bool
, isUnique :: Bool
, isUserLogin :: Bool
} deriving (Show, Data, Typeable, Eq)
data Schema = Schema { schemaName :: String
, schemaRoute :: Maybe StrValue
, writable :: Bool
, hasKeyField :: Bool
, keyField :: String
, schemaVars :: [SchemaVar] } deriving (Show, Data, Typeable)
data Service = Service { name :: String
, version :: String
, requiresAuth :: Bool
, schema :: [Schema] } deriving (Show, Data, Typeable)
render:: String -> Service -> IO TL.Text
render templateLoc service =
do
template <- getDataFileName templateLoc >>= readFile
let context = mkGenericContext service in
hastacheStr defaultConfig (encodeStr template) context
derive makeArbitrary ''Service
derive makeArbitrary ''StrValue
derive makeArbitrary ''Schema
derive makeArbitrary ''SchemaVar
derive makeArbitrary ''EnumValues