diff --git a/.gitignore b/.gitignore index 3f32ce7..20fd9f0 100644 --- a/.gitignore +++ b/.gitignore @@ -10,3 +10,5 @@ cabal-dev cabal.sandbox.config *~ .stack-work +*.dyn_o +*.dyn_hi diff --git a/README.md b/README.md index 0f9bae3..b2724a1 100644 --- a/README.md +++ b/README.md @@ -9,8 +9,6 @@ Elm Bridge Hackage: [elm-bridge](http://hackage.haskell.org/package/elm-bridge) - **WARNING: Work in progress!** - Building the bridge from [Haskell](http://haskell.org) to [Elm](http://elm-lang.org) and back. Define types once, use on both sides and enjoy easy (de)serialisation. Cheers! ## Usage @@ -18,8 +16,7 @@ Building the bridge from [Haskell](http://haskell.org) to [Elm](http://elm-lang. ```haskell {-# LANGUAGE TemplateHaskell #-} import Elm.Derive -import Elm.TyRender -import Elm.TyRep +import Elm.Module import Data.Proxy @@ -29,18 +26,41 @@ data Foo , f_blablub :: Int } deriving (Show, Eq) +deriveElmDef defaultOpts ''Foo + main :: IO () main = - putStrLn $ renderElm $ compileElmDef (Proxy :: Proxy Foo) + putStrLn $ makeElmModule "Foo" + [ DefineElm (Proxy :: Proxy Foo) + ] + ``` Output will be: ```elm -type alias Foo = - { f_name: String - , f_blablub: Int - } +module Foo where + +import Json.Decode +import Json.Decode exposing ((:=)) +import Json.Encode + + +type alias Foo = + { f_name: String + , f_blablub: Int + } + +jsonDecFoo = + ("f_name" := Json.Decode.string) `Json.Decode.andThen` \pf_name -> + ("f_blablub" := Json.Decode.int) `Json.Decode.andThen` \pf_blablub -> + Json.Decode.succeed {f_name = pf_name, f_blablub = pf_blablub} + +jsonEncFoo val = + Json.Encode.object + [ ("f_name", Json.Encode.string val.f_name) + , ("f_blablub", Json.Encode.int val.f_blablub) + ] ``` For more usage examples check the tests. @@ -49,7 +69,3 @@ For more usage examples check the tests. * Using cabal: `cabal install elm-bridge` * From Source: `git clone https://github.com/agrafix/elm-bridge.git && cd elm-bridge && cabal install` - -## Todo - -* Generate Elm JSON Serializer/Parser \ No newline at end of file diff --git a/elm-bridge.cabal b/elm-bridge.cabal index c3389cb..2a2121e 100644 --- a/elm-bridge.cabal +++ b/elm-bridge.cabal @@ -15,6 +15,7 @@ cabal-version: >=1.10 extra-source-files: README.md + examples/*.hs library hs-source-dirs: src diff --git a/examples/Example1.hs b/examples/Example1.hs new file mode 100644 index 0000000..d2ab9a6 --- /dev/null +++ b/examples/Example1.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE PackageImports #-} +{-# LANGUAGE TemplateHaskell #-} +import "elm-bridge" Elm.Derive +import "elm-bridge" Elm.Module + +import Data.Proxy + +data Foo + = Foo + { f_name :: String + , f_blablub :: Int + } deriving (Show, Eq) + +deriveElmDef defaultOpts ''Foo + +main :: IO () +main = + putStrLn $ makeElmModule "Foo" + [ DefineElm (Proxy :: Proxy Foo) + ] diff --git a/src/Elm/Json.hs b/src/Elm/Json.hs index 547941e..fcf4f11 100644 --- a/src/Elm/Json.hs +++ b/src/Elm/Json.hs @@ -1,3 +1,7 @@ +{- | +This module implements a generator for JSON serialisers and parsers of arbitrary elm types. +Please note: It's still very hacky and might not work for all possible elm types yet. +-} module Elm.Json ( jsonParserForDef , jsonSerForDef @@ -9,6 +13,7 @@ import Data.Maybe import Elm.TyRep +-- | Compile a JSON parser for an Elm type jsonParserForType :: EType -> String jsonParserForType ty = case ty of @@ -39,6 +44,7 @@ jsonParserForType ty = in "Json.Decode.tuple" ++ show tupleLen ++ " (" ++ commas ++ ") " ++ unwords (map (\t' -> "(" ++ jsonParserForType t' ++ ")") xs) +-- | Compile a JSON parser for an Elm type definition jsonParserForDef :: ETypeDef -> String jsonParserForDef etd = case etd of @@ -66,7 +72,7 @@ jsonParserForDef etd = "jsonDec" ++ et_name name ++ " " ++ unwords (map (\tv -> "localDecoder_" ++ tv_name tv) $ et_args name) - +-- | Compile a JSON serializer for an Elm type jsonSerForType :: EType -> String jsonSerForType ty = case ty of @@ -98,7 +104,7 @@ jsonSerForType ty = unwords $ map (\(_, v) -> "v" ++ show v) tupleArgsV in "(\\" ++ tupleArgs ++ " -> [" ++ intercalate "," (map (\(t', idx) -> "(" ++ jsonSerForType t' ++ ") v" ++ show idx) tupleArgsV) ++ "]" - +-- | Compile a JSON serializer for an Elm type definition jsonSerForDef :: ETypeDef -> String jsonSerForDef etd = case etd of diff --git a/src/Elm/Module.hs b/src/Elm/Module.hs index 46aa906..b3ecc86 100644 --- a/src/Elm/Module.hs +++ b/src/Elm/Module.hs @@ -9,12 +9,18 @@ import Elm.TyRep import Elm.TyRender import Elm.Json +-- | Existential quantification wrapper for lists of type definitions data DefineElm = forall a. IsElmDefinition a => DefineElm (Proxy a) +-- | Compile an Elm module makeElmModule :: String -> [DefineElm] -> String makeElmModule moduleName defs = - "module " ++ moduleName ++ " where \n" + "module " ++ moduleName ++ " where \n\n" + ++ "import Json.Decode\n" + ++ "import Json.Decode exposing ((:=))\n" + ++ "import Json.Encode\n" + ++ "\n\n" ++ intercalate "\n\n" (map mkDef defs) where mkDef (DefineElm proxy) = diff --git a/src/Elm/TyRender.hs b/src/Elm/TyRender.hs index a12c3fa..421ac4f 100644 --- a/src/Elm/TyRender.hs +++ b/src/Elm/TyRender.hs @@ -40,7 +40,7 @@ instance ElmRenderable ETypeName where instance ElmRenderable EAlias where renderElm alias = "type alias " ++ renderElm (ea_name alias) ++ " = \n { " - ++ intercalate "\n, " (map (\(fld, ty) -> fld ++ ": " ++ renderElm ty) (ea_fields alias)) + ++ intercalate "\n , " (map (\(fld, ty) -> fld ++ ": " ++ renderElm ty) (ea_fields alias)) ++ "\n }\n" instance ElmRenderable ESum where diff --git a/test/Elm/ModuleSpec.hs b/test/Elm/ModuleSpec.hs index db11ead..3901de7 100644 --- a/test/Elm/ModuleSpec.hs +++ b/test/Elm/ModuleSpec.hs @@ -20,7 +20,7 @@ data Bar a $(deriveElmDef (fieldDropOpts 2) ''Bar) moduleCode :: String -moduleCode = "module Foo where \ntype alias Bar a = \n { name: a\n, blablub: Int\n, tuple: (Int, String)\n, list: (List Bool)\n }\n\njsonDecBar localDecoder_a = \n (\"name\" := localDecoder_a) `Json.Decode.andThen` \\pname -> \n (\"blablub\" := Json.Decode.int) `Json.Decode.andThen` \\pblablub -> \n (\"tuple\" := Json.Decode.tuple2 (,) (Json.Decode.int) (Json.Decode.string)) `Json.Decode.andThen` \\ptuple -> \n (\"list\" := Json.Decode.list (Json.Decode.bool)) `Json.Decode.andThen` \\plist -> \n Json.Decode.succeed {name = pname, blablub = pblablub, tuple = ptuple, list = plist}\n\njsonEncBar localEncoder_a val = \n Json.Encode.object\n [ (\"name\", localEncoder_a val.name)\n , (\"blablub\", Json.Encode.int val.blablub)\n , (\"tuple\", (\\v1 v2 -> [(Json.Encode.int) v1,(Json.Encode.string) v2] val.tuple)\n , (\"list\", (Json.Encode.list << map Json.Encode.bool) val.list)\n ]\n\n" +moduleCode = "module Foo where \n\nimport Json.Decode\nimport Json.Decode exposing ((:=))\nimport Json.Encode\n\n\ntype alias Bar a = \n { name: a\n , blablub: Int\n , tuple: (Int, String)\n , list: (List Bool)\n }\n\njsonDecBar localDecoder_a = \n (\"name\" := localDecoder_a) `Json.Decode.andThen` \\pname -> \n (\"blablub\" := Json.Decode.int) `Json.Decode.andThen` \\pblablub -> \n (\"tuple\" := Json.Decode.tuple2 (,) (Json.Decode.int) (Json.Decode.string)) `Json.Decode.andThen` \\ptuple -> \n (\"list\" := Json.Decode.list (Json.Decode.bool)) `Json.Decode.andThen` \\plist -> \n Json.Decode.succeed {name = pname, blablub = pblablub, tuple = ptuple, list = plist}\n\njsonEncBar localEncoder_a val = \n Json.Encode.object\n [ (\"name\", localEncoder_a val.name)\n , (\"blablub\", Json.Encode.int val.blablub)\n , (\"tuple\", (\\v1 v2 -> [(Json.Encode.int) v1,(Json.Encode.string) v2] val.tuple)\n , (\"list\", (Json.Encode.list << map Json.Encode.bool) val.list)\n ]\n\n" spec :: Spec spec = diff --git a/test/Elm/TyRenderSpec.hs b/test/Elm/TyRenderSpec.hs index 283a44b..bf83309 100644 --- a/test/Elm/TyRenderSpec.hs +++ b/test/Elm/TyRenderSpec.hs @@ -33,10 +33,10 @@ $(deriveElmDef (fieldDropOpts 2) ''Bar) $(deriveElmDef defaultOpts ''SomeOpts) fooCode :: String -fooCode = "type alias Foo = \n { name: String\n, blablub: Int\n }\n" +fooCode = "type alias Foo = \n { name: String\n , blablub: Int\n }\n" barCode :: String -barCode = "type alias Bar a = \n { name: a\n, blablub: Int\n, tuple: (Int, String)\n, list: (List Bool)\n }\n" +barCode = "type alias Bar a = \n { name: a\n , blablub: Int\n , tuple: (Int, String)\n , list: (List Bool)\n }\n" someOptsCode :: String someOptsCode = "type SomeOpts a = \n Okay Int\n | NotOkay a\n"