{-# LANGUAGE ScopedTypeVariables #-}
module Zinza (
parseAndCompileTemplate,
parseAndCompileTemplateIO,
parseAndCompileModule,
parseAndCompileModuleIO,
ModuleConfig (..),
simpleConfig,
Zinza (..),
genericToType,
genericToValue,
genericFromValue,
genericToTypeSFP,
genericToValueSFP,
genericFromValueSFP,
stripFieldPrefix,
GZinzaType, GZinzaValue, GZinzaFrom, GFieldNames,
Node (..), Nodes, Expr (..), LExpr,
Ty (..),
displayTy,
Value (..),
ParseError (..),
CompileError (..),
CompileOrParseError (..),
RuntimeError (..),
AsRuntimeError (..),
ThrowRuntime (..),
Loc (..), Located (..), zeroLoc, displayLoc, TraversableWithLoc (..),
Var, Selector,
) where
import Control.Exception (throwIO)
import Data.Typeable (Typeable, typeRep)
import Zinza.Check
import Zinza.Errors
import Zinza.Expr
import Zinza.Generic
import Zinza.Module
import Zinza.Node
import Zinza.Parser
import Zinza.Pos
import Zinza.Type
import Zinza.Value
import Zinza.Var
parseAndCompileTemplate
:: (Zinza a, ThrowRuntime m)
=> FilePath
-> String
-> Either CompileOrParseError (a -> m String)
parseAndCompileTemplate :: forall a (m :: * -> *).
(Zinza a, ThrowRuntime m) =>
FilePath
-> FilePath -> Either CompileOrParseError (a -> m FilePath)
parseAndCompileTemplate FilePath
name FilePath
contents =
case FilePath -> FilePath -> Either ParseError (Nodes FilePath)
parseTemplate FilePath
name FilePath
contents of
Left ParseError
err -> CompileOrParseError -> Either CompileOrParseError (a -> m FilePath)
forall a b. a -> Either a b
Left (ParseError -> CompileOrParseError
AParseError ParseError
err)
Right Nodes FilePath
nodes -> case Nodes FilePath -> Either CompileError (a -> m FilePath)
forall a (m :: * -> *).
(Zinza a, ThrowRuntime m) =>
Nodes FilePath -> Either CompileError (a -> m FilePath)
check Nodes FilePath
nodes of
Left CompileError
err' -> CompileOrParseError -> Either CompileOrParseError (a -> m FilePath)
forall a b. a -> Either a b
Left (CompileError -> CompileOrParseError
ACompileError CompileError
err')
Right a -> m FilePath
res -> (a -> m FilePath) -> Either CompileOrParseError (a -> m FilePath)
forall a b. b -> Either a b
Right a -> m FilePath
res
parseAndCompileTemplateIO :: (Zinza a, ThrowRuntime m) => FilePath -> IO (a -> m String)
parseAndCompileTemplateIO :: forall a (m :: * -> *).
(Zinza a, ThrowRuntime m) =>
FilePath -> IO (a -> m FilePath)
parseAndCompileTemplateIO FilePath
name = do
FilePath
contents <- FilePath -> IO FilePath
readFile FilePath
name
(CompileOrParseError -> IO (a -> m FilePath))
-> ((a -> m FilePath) -> IO (a -> m FilePath))
-> Either CompileOrParseError (a -> m FilePath)
-> IO (a -> m FilePath)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either CompileOrParseError -> IO (a -> m FilePath)
forall e a. Exception e => e -> IO a
throwIO (a -> m FilePath) -> IO (a -> m FilePath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either CompileOrParseError (a -> m FilePath)
-> IO (a -> m FilePath))
-> Either CompileOrParseError (a -> m FilePath)
-> IO (a -> m FilePath)
forall a b. (a -> b) -> a -> b
$ FilePath
-> FilePath -> Either CompileOrParseError (a -> m FilePath)
forall a (m :: * -> *).
(Zinza a, ThrowRuntime m) =>
FilePath
-> FilePath -> Either CompileOrParseError (a -> m FilePath)
parseAndCompileTemplate FilePath
name FilePath
contents
parseAndCompileModule
:: Zinza a
=> ModuleConfig a
-> FilePath
-> String
-> Either CompileOrParseError String
parseAndCompileModule :: forall a.
Zinza a =>
ModuleConfig a
-> FilePath -> FilePath -> Either CompileOrParseError FilePath
parseAndCompileModule ModuleConfig a
mc FilePath
name FilePath
contents =
case FilePath -> FilePath -> Either ParseError (Nodes FilePath)
parseTemplate FilePath
name FilePath
contents of
Left ParseError
err -> CompileOrParseError -> Either CompileOrParseError FilePath
forall a b. a -> Either a b
Left (ParseError -> CompileOrParseError
AParseError ParseError
err)
Right Nodes FilePath
nodes -> case ModuleConfig a -> Nodes FilePath -> Either CompileError FilePath
forall a.
Zinza a =>
ModuleConfig a -> Nodes FilePath -> Either CompileError FilePath
checkModule ModuleConfig a
mc Nodes FilePath
nodes of
Left CompileError
err -> CompileOrParseError -> Either CompileOrParseError FilePath
forall a b. a -> Either a b
Left (CompileError -> CompileOrParseError
ACompileError CompileError
err)
Right FilePath
res -> FilePath -> Either CompileOrParseError FilePath
forall a b. b -> Either a b
Right FilePath
res
parseAndCompileModuleIO :: Zinza a => ModuleConfig a -> FilePath -> IO String
parseAndCompileModuleIO :: forall a. Zinza a => ModuleConfig a -> FilePath -> IO FilePath
parseAndCompileModuleIO ModuleConfig a
mc FilePath
name = do
FilePath
contents <- FilePath -> IO FilePath
readFile FilePath
name
(CompileOrParseError -> IO FilePath)
-> (FilePath -> IO FilePath)
-> Either CompileOrParseError FilePath
-> IO FilePath
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either CompileOrParseError -> IO FilePath
forall e a. Exception e => e -> IO a
throwIO FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either CompileOrParseError FilePath -> IO FilePath)
-> Either CompileOrParseError FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ ModuleConfig a
-> FilePath -> FilePath -> Either CompileOrParseError FilePath
forall a.
Zinza a =>
ModuleConfig a
-> FilePath -> FilePath -> Either CompileOrParseError FilePath
parseAndCompileModule ModuleConfig a
mc FilePath
name FilePath
contents
simpleConfig
:: forall a. Typeable a
=> String
-> [String]
-> ModuleConfig a
simpleConfig :: forall a. Typeable a => FilePath -> [FilePath] -> ModuleConfig a
simpleConfig FilePath
moduleName [FilePath]
imports = ModuleConfig
{ mcRender :: FilePath
mcRender = FilePath
"render"
, mcHeader :: [FilePath]
mcHeader =
[ FilePath
"{-# OPTIONS_GHC -fno-warn-unused-imports #-}"
, FilePath
"module " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
moduleName FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" (render) where"
, FilePath
"import Prelude (String, fst, snd, ($), return)"
, FilePath
"import Control.Monad (forM_)"
] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
[ FilePath
"import " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
i
| FilePath
i <- [FilePath]
imports
] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
[ FilePath
"type Writer a = (String, a)"
, FilePath
"tell :: String -> Writer (); tell x = (x, ())"
, FilePath
"execWriter :: Writer a -> String; execWriter = fst"
, FilePath
"render :: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
typeName FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" -> String"
]
}
where
typeName :: FilePath
typeName = TypeRep -> FilePath
forall a. Show a => a -> FilePath
show ([a] -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep ([] :: [a]))