Add a toXML serializer for values

Relates to issue #109
This commit is contained in:
John Wiegley 2018-04-05 01:13:13 -07:00
parent b4eb981ecc
commit d476b3f173
5 changed files with 57 additions and 5 deletions

View File

@ -56,6 +56,7 @@ import Nix.Scope
import Nix.Stack
import Nix.Thunk
import Nix.Utils
import Nix.XML
import System.FilePath
import System.Posix.Files
@ -132,8 +133,11 @@ builtinsList = sequence [
, add' Normal "hashString" hashString
, add Normal "readFile" readFile_
, add Normal "readDir" readDir_
, add' Normal "toJSON" (arity1 $ decodeUtf8 . LBS.toStrict . A.encodingToLazyByteString . toEncodingSorted)
, add' Normal "toJSON"
(arity1 $ decodeUtf8 . LBS.toStrict . A.encodingToLazyByteString
. toEncodingSorted)
, add Normal "fromJSON" fromJSON
, add Normal "toXML" toXML_
, add Normal "typeOf" typeOf
, add2 Normal "partition" partition_
, add0 Normal "currentSystem" currentSystem
@ -593,6 +597,10 @@ fromJSON t = do
Left jsonError -> throwError $ "builtins.fromJSON: " ++ jsonError
Right v -> toValue v
toXML_ :: MonadBuiltins e m => NThunk m -> m (NValue m)
toXML_ = force >=> normalForm >=> \x ->
pure $ NVStr (Text.pack (toXML x)) mempty
typeOf :: MonadBuiltins e m => NThunk m -> m (NValue m)
typeOf t = do
v <- force t

42
Nix/XML.hs Normal file
View File

@ -0,0 +1,42 @@
{-# LANGUAGE LambdaCase #-}
module Nix.XML where
import Data.Fix
import qualified Data.HashMap.Lazy as M
import qualified Data.Text as Text
import Nix.Atoms
import Nix.Monad
import Text.XML.Light
toXML :: Functor m => NValueNF m -> String
toXML = (.) ((++ "\n") .
("<?xml version='1.0' encoding='utf-8'?>\n" ++) .
ppElement .
(\e -> Element (unqual "expr") [] [Elem e] Nothing))
$ cata
$ \case
NVConstant a -> case a of
NInt n -> elem "int" "value" (show n)
NFloat f -> elem "float" "value" (show f)
NBool b -> elem "bool" "value" (if b then "true" else "false")
NNull -> Element (unqual "null") [] [] Nothing
NUri u -> elem "uri" "value" (Text.unpack u)
NVStr t _ -> elem "string" "value" (Text.unpack t)
NVList l -> Element (unqual "list") [] (Elem <$> l) Nothing
NVSet s -> Element (unqual "attrs") []
(map (\(k, v) -> Elem (Element (unqual "attr")
[Attr (unqual "name") (Text.unpack k)]
[Elem v] Nothing))
(M.toList s)) Nothing
NVClosure _ _p _ ->
Element (unqual "function") []
(error "NYI: XML function param attrset") Nothing
NVLiteralPath fp -> elem "path" "value" fp
NVEnvPath p -> elem "path" "value" p
NVBuiltin name _ -> elem "function" "name" name
where
elem n a v = Element (unqual n) [Attr (unqual a) v] [] Nothing

View File

@ -18,7 +18,7 @@ let
, tasty, tasty-hunit, tasty-th, text, transformers, trifecta
, unordered-containers, these, optparse-applicative, interpolate
, process, exceptions, bytestring, mtl, monadlist, base16-bytestring
, cryptohash, template-haskell, syb
, cryptohash, template-haskell, syb, xml
}:
mkDerivation {
pname = "hnix";
@ -31,7 +31,7 @@ let
parsers regex-tdfa regex-tdfa-text semigroups text transformers
trifecta unordered-containers these process directory filepath
exceptions bytestring mtl monadlist base16-bytestring cryptohash
template-haskell syb
template-haskell syb xml
];
executableHaskellDepends = [
ansi-wl-pprint base containers data-fix deepseq optparse-applicative

View File

@ -27,6 +27,7 @@ Library
Nix.Scope
Nix.Stack
Nix.Eval
Nix.XML
Nix.Thunk
Nix.Lint
Nix.Monad
@ -75,6 +76,7 @@ Library
, unix
, syb
, vector
, xml
if flag(parsec)
Cpp-options: -DUSE_PARSEC
Build-depends: parsec

View File

@ -18,7 +18,7 @@ let
, tasty, tasty-hunit, tasty-th, text, transformers, trifecta
, unordered-containers, these, optparse-applicative, free
, interpolate, process, exceptions, bytestring, mtl, monadlist
, base16-bytestring, cryptohash, template-haskell, syb
, base16-bytestring, cryptohash, template-haskell, syb, xml
}:
mkDerivation {
pname = "hnix";
@ -31,7 +31,7 @@ let
parsers regex-tdfa regex-tdfa-text semigroups text transformers
trifecta unordered-containers these free process directory
filepath exceptions bytestring mtl monadlist base16-bytestring
cryptohash template-haskell syb
cryptohash template-haskell syb xml
];
executableHaskellDepends = [
ansi-wl-pprint base containers data-fix deepseq optparse-applicative