Fix some 0.19 problems

This commit is contained in:
Simon Marechal 2019-10-21 18:29:22 +02:00
parent 907d91f0c4
commit d9d419e5f9
5 changed files with 29 additions and 28 deletions

View File

@ -18,7 +18,6 @@ import Data.Aeson.Types (SumEncoding (..))
import Data.List
import Elm.TyRep
import Elm.Utils
import Elm.Versions
data MaybeHandling = Root | Leaf
deriving Eq

View File

@ -23,7 +23,7 @@ data DefineElm
moduleHeader :: ElmVersion
-> String
-> String
moduleHeader Elm0p18 moduleName = "module " ++ moduleName ++ " exposing(..)"
moduleHeader _ moduleName = "module " ++ moduleName ++ " exposing(..)"
-- | Creates an Elm module for the given version. This will use the default
-- type conversion rules (to -- convert @Vector@ to @List@, @HashMap a b@
@ -43,14 +43,16 @@ makeElmModuleWithVersion elmVersion moduleName defs = unlines
, "import Set exposing (Set)"
, ""
, ""
]) ++ makeModuleContent defs
] ++ makeModuleContent defs
-- | Creates an Elm module. This will use the default type conversion rules (to
-- convert @Vector@ to @List@, @HashMap a b@ to @List (a,b)@, etc.).
--
-- default to 0.19
makeElmModule :: String -- ^ Module name
-> [DefineElm] -- ^ List of definitions to be included in the module
-> String
makeElmModule = makeElmModuleWithVersion Elm0p18
makeElmModule = makeElmModuleWithVersion Elm0p19
-- | Generates the content of a module. You will be responsible for
-- including the required Elm headers. This uses the default type

View File

@ -1,9 +1,9 @@
{-| A type to represent versions of Elm for produced code to work against.
This module only supports Elm 0.19.x !!!
-}
module Elm.Versions where
data ElmVersion
= Elm0p18
| Elm0p19
= Elm0p19

View File

@ -1,30 +1,30 @@
{-# LANGUAGE TemplateHaskell #-}
module Elm.JsonSpec (spec) where
import Elm.Derive
import Elm.TyRender
import Elm.TyRep
import Elm.Json
import Elm.Derive
import Elm.Json
import Elm.TyRender
import Elm.TyRep
import Data.Proxy
import Test.Hspec
import Data.Char (toLower)
import Data.Aeson.Types (defaultTaggedObject)
import qualified Data.Map.Strict as M
import qualified Data.Aeson.TH as TH
import qualified Data.Aeson.TH as TH
import Data.Aeson.Types (defaultTaggedObject)
import Data.Char (toLower)
import qualified Data.Map.Strict as M
import Data.Proxy
import Test.Hspec
data Foo
= Foo
{ f_name :: String
{ f_name :: String
, f_blablub :: Int
} deriving (Show, Eq)
data Bar a
= Bar
{ b_name :: a
{ b_name :: a
, b_blablub :: Int
, b_tuple :: (Int, String)
, b_list :: [Bool]
, b_tuple :: (Int, String)
, b_list :: [Bool]
} deriving (Show, Eq)
data SomeOpts a

View File

@ -26,7 +26,7 @@ $(deriveElmDef (defaultOptionsDropLower 2) ''Bar)
$(deriveElmDef (defaultOptionsDropLower 5) ''Qux)
moduleHeader' :: ElmVersion -> String -> String
moduleHeader' Elm0p18 name = "module " ++ name ++ " exposing(..)"
moduleHeader' Elm0p19 name = "module " ++ name ++ " exposing(..)"
moduleCode :: ElmVersion -> String
moduleCode elmVersion = unlines
@ -113,14 +113,14 @@ makeElmModuleSpec =
it "should produce the correct code" $
do let modu = makeElmModule "Foo" [DefineElm (Proxy :: Proxy (Bar a))]
let modu' = makeElmModule "Qux" [DefineElm (Proxy :: Proxy (Qux a))]
modu `shouldBe` (moduleCode Elm0p18)
modu' `shouldBe` (moduleCode' Elm0p18)
modu `shouldBe` moduleCode Elm0p19
modu' `shouldBe` moduleCode' Elm0p19
version0p18Spec :: Spec
version0p18Spec =
describe "makeElmModuleWithVersion Elm0p18" $
describe "makeElmModuleWithVersion Elm0p19" $
it "should produce the correct code" $
do let modu = makeElmModuleWithVersion Elm0p18 "Foo" [DefineElm (Proxy :: Proxy (Bar a))]
let modu' = makeElmModuleWithVersion Elm0p18 "Qux" [DefineElm (Proxy :: Proxy (Qux a))]
modu `shouldBe` (moduleCode Elm0p18)
modu' `shouldBe` (moduleCode' Elm0p18)
do let modu = makeElmModuleWithVersion Elm0p19 "Foo" [DefineElm (Proxy :: Proxy (Bar a))]
let modu' = makeElmModuleWithVersion Elm0p19 "Qux" [DefineElm (Proxy :: Proxy (Qux a))]
modu `shouldBe` moduleCode Elm0p19
modu' `shouldBe` moduleCode' Elm0p19