Created
June 2, 2017 23:38
-
-
Save johnhaley81/e38fef196b82454a530ad69dad28eaf2 to your computer and use it in GitHub Desktop.
Spock and Yesod persisted types
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| {-# LANGUAGE EmptyDataDecls #-} | |
| {-# LANGUAGE FlexibleContexts #-} | |
| {-# LANGUAGE FlexibleInstances #-} | |
| {-# LANGUAGE GADTs #-} | |
| {-# LANGUAGE GeneralizedNewtypeDeriving #-} | |
| {-# LANGUAGE MultiParamTypeClasses #-} | |
| {-# LANGUAGE OverloadedStrings #-} | |
| {-# LANGUAGE QuasiQuotes #-} | |
| {-# LANGUAGE TemplateHaskell #-} | |
| {-# LANGUAGE TypeFamilies #-} | |
| -- This works for some reason. PersonId is correctly configured and sorted ASC with results that come back from the DB | |
| module Person where | |
| import Control.Monad.Logger (LoggingT, runStdoutLoggingT) | |
| import Data.Aeson hiding (json) | |
| import Data.Monoid ((<>)) | |
| import Data.Text (Text, pack) | |
| import Database.Persist hiding (delete, get) | |
| import qualified Database.Persist as P | |
| import Database.Persist.Class hiding (delete, get) | |
| import Database.Persist.Sqlite hiding (delete, get) | |
| import Database.Persist.TH | |
| import Web.Spock | |
| import Web.Spock.Config | |
| mkPersist sqlSettings [persistLowerCase| | |
| Person | |
| name String | |
| age Int | |
| deriving Show | |
| |] | |
| type Api = SpockM SqlBackend () () () | |
| runSQL :: (HasSpock m, SpockConn m ~ SqlBackend) => SqlPersistT (LoggingT IO) a -> m a | |
| runSQL action = runQuery $ \conn -> runStdoutLoggingT $ runSqlConn action conn | |
| getAll :: Api | |
| getAll = get "person" $ do | |
| allPeople <- runSQL $ selectList [] [Asc PersonId] | |
| json allPeople |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| {-# LANGUAGE GADTs #-} | |
| {-# LANGUAGE GeneralizedNewtypeDeriving #-} | |
| {-# LANGUAGE OverloadedStrings #-} | |
| {-# LANGUAGE QuasiQuotes #-} | |
| {-# LANGUAGE TemplateHaskell #-} | |
| {-# LANGUAGE TypeFamilies #-} | |
| module PersonModel where | |
| import Database.Persist | |
| import Database.Persist.TH | |
| import Database.Persist.Sqlite | |
| import Control.Monad.IO.Class (liftIO) | |
| mkPersist sqlSettings [persistLowerCase| | |
| Person | |
| name String | |
| age Int | |
| deriving Show | |
| |] |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| {-# LANGUAGE EmptyDataDecls #-} | |
| {-# LANGUAGE FlexibleContexts #-} | |
| {-# LANGUAGE FlexibleInstances #-} | |
| {-# LANGUAGE GADTs #-} | |
| {-# LANGUAGE GeneralizedNewtypeDeriving #-} | |
| {-# LANGUAGE MultiParamTypeClasses #-} | |
| {-# LANGUAGE OverloadedStrings #-} | |
| {-# LANGUAGE QuasiQuotes #-} | |
| {-# LANGUAGE TemplateHaskell #-} | |
| {-# LANGUAGE TypeFamilies #-} | |
| -- This does *NOT* work for some reason. PersonId yields the error: | |
| -- Data constructor not in scope: | |
| -- PersonId :: EntityField record0 typ0 | |
| -- For reference I'm doing https://www.yesodweb.com/book/persistent#persistent_code_generation | |
| -- and it shows the exported code from the template. | |
| module PersonRoute where | |
| import Control.Monad.Logger (LoggingT, runStdoutLoggingT) | |
| import Data.Aeson hiding (json) | |
| import Data.Monoid ((<>)) | |
| import Data.Text (Text, pack) | |
| import Database.Persist hiding (delete, get) | |
| import qualified Database.Persist as P | |
| import Database.Persist.Class hiding (delete, get) | |
| import Database.Persist.Sqlite hiding (delete, get) | |
| import Database.Persist.TH | |
| import Web.Spock | |
| import Web.Spock.Config | |
| import Models.Person | |
| type Api = SpockM SqlBackend () () () | |
| runSQL :: (HasSpock m, SpockConn m ~ SqlBackend) => SqlPersistT (LoggingT IO) a -> m a | |
| runSQL action = runQuery $ \conn -> runStdoutLoggingT $ runSqlConn action conn | |
| getAll :: Api | |
| getAll = get "person" $ do | |
| allPeople <- runSQL $ selectList [] [Asc PersonId] | |
| json allPeople |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment