small improvements, README and example

This commit is contained in:
Alexander Thiemann 2015-08-09 22:46:02 +02:00
parent a70750de09
commit 2e05a3380a
9 changed files with 71 additions and 20 deletions

2
.gitignore vendored
View File

@ -10,3 +10,5 @@ cabal-dev
cabal.sandbox.config
*~
.stack-work
*.dyn_o
*.dyn_hi

View File

@ -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

View File

@ -15,6 +15,7 @@ cabal-version: >=1.10
extra-source-files:
README.md
examples/*.hs
library
hs-source-dirs: src

20
examples/Example1.hs Normal file
View File

@ -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)
]

View File

@ -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

View File

@ -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) =

View File

@ -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

View File

@ -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 =

View File

@ -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"