Copyright | (C) 2016-17 William Casarin |
---|---|
License | MIT |
Maintainer | William Casarin <bill@casarin.me> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Usage
newtypeEnt
(field ::Symbol
) a =Ent
(Entity
a) deriving (Generic
) typeEntId
a =Ent
"id" a
Ent
is a newtype that wraps Persistent Entity
s, allowing you to export
them to Elm types. Specifically, it adds a {To,From}JSON instance which
adds an id
field, as well as an
instance that adds an ElmType
id
field constructor.
Example
Let's define a Persistent model:
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE StandaloneDeriving #-} module Main where import Data.Aeson import Data.Text
import Database.Persist.TH import Elm import GHC.Generics import Elm.Export.Persist import Elm.Export.Persist.BackendKey () share [mkPersist sqlSettings, mkMigrate "migrateAccount"] [persistLowerCase| Account emailText
passwordText
deriving ShowGeneric
UniqueEmail email |] instanceToJSON
Account instanceFromJSON
Account instanceElmType
Account -- use GeneralizedNewtypeDeriving for ids -- this picks a simpler int-encoding deriving instanceElmType
AccountId
Now let's export it with an id field:
module Main where import Db import Elm import Data.Proxy mkSpecBody ::ElmType
a => a -> [Text
] mkSpecBody a = [ toElmTypeSource a , toElmDecoderSource a , toElmEncoderSource a ] defImports :: [Text
] defImports = [ "import Json.Decode exposing (..)" , "import Json.Decode.Pipeline exposing (..)" , "import Json.Encode" , "import Http" , "import String" ] accountSpec :: Spec accountSpec = Spec ["Generated", "Account"] $ defImports ++ mkSpecBody (Proxy
::Proxy
(EntId
Account)) main :: IO () main = specsToDir [accountSpec] "some/where/output"
This generates:
module Generated.Account exposing (..) import Json.Decode exposing (..) import Json.Decode.Pipeline exposing (..) import Json.Encode import Http import String type alias Account = { accountEmail : String , accountPassword : String , id : Int } decodeAccount : Decoder Account decodeAccount = decode Account |> required "accountEmail" string |> required "accountPassword" string |> required "id" int encodeAccount : Account -> Json.Encode.Value encodeAccount x = Json.Encode.object [ ( "accountEmail", Json.Encode.string x.accountEmail ) , ( "accountPassword", Json.Encode.string x.accountPassword ) , ( "id", Json.Encode.int x.id ) ]
Documentation
module Elm.Export.Persist.Ent