Skip to content

Commit

Permalink
Merge pull request #1290 from digitallyinduced/trimming-prelude
Browse files Browse the repository at this point in the history
Trimming prelude
  • Loading branch information
mpscholten authored Dec 27, 2021
2 parents 8b611db + 156ab9d commit 3d727b1
Show file tree
Hide file tree
Showing 4 changed files with 10 additions and 12 deletions.
2 changes: 0 additions & 2 deletions Guide/mail.markdown
Original file line number Diff line number Diff line change
Expand Up @@ -226,8 +226,6 @@ Every email should have a plain text version for people with reasonable mail cli
The better option is to manually provide a useful plain text version of your emails:

```haskell
import NeatInterpolation

text ConfirmationMail { .. } = cs [trimming|
Hey ${userName},

Expand Down
1 change: 0 additions & 1 deletion IHP/IDE/CodeGen/ViewGenerator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@ import qualified Data.Text as Text
import IHP.IDE.CodeGen.Types
import qualified IHP.IDE.SchemaDesigner.Parser as SchemaDesigner
import IHP.IDE.SchemaDesigner.Types
import NeatInterpolation

data ViewConfig = ViewConfig
{ controllerName :: Text
Expand Down
2 changes: 2 additions & 0 deletions IHP/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ module IHP.Prelude
, module Control.Exception
, module Control.Monad.Fail
, module Control.Concurrent.Async
, module NeatInterpolation
)
where

Expand Down Expand Up @@ -73,6 +74,7 @@ import Data.Time.Format
import Control.Exception (throw, throwIO, catch)
import Control.Monad.Fail (fail)
import Control.Concurrent.Async
import NeatInterpolation (trimming)

-- Alias for haskell newcomers :)
a ++ b = a <> b
Expand Down
17 changes: 8 additions & 9 deletions Test/SchemaCompilerSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@ import Test.Hspec
import IHP.Prelude
import IHP.SchemaCompiler
import IHP.IDE.SchemaDesigner.Types
import NeatInterpolation
import qualified Data.Text as Text

tests = do
Expand All @@ -18,7 +17,7 @@ tests = do
let statement = CreateEnumType { name = "mood", values = ["happy", "very happy", "sad", "very sad"] }
let output = compileStatementPreview [statement] statement |> Text.strip

output `shouldBe` [text|
output `shouldBe` [trimming|
data Mood = Happy | VeryHappy | Sad | VerySad deriving (Eq, Show, Read, Enum)
instance FromField Mood where
fromField field (Just value) | value == (Data.Text.Encoding.encodeUtf8 "happy") = pure Happy
Expand Down Expand Up @@ -55,7 +54,7 @@ tests = do
let statement = CreateEnumType { name = "Province", values = ["Alberta", "BritishColumbia", "Saskatchewan", "Manitoba", "Ontario", "Quebec", "NovaScotia", "NewBrunswick", "PrinceEdwardIsland", "NewfoundlandAndLabrador"] }
let output = compileStatementPreview [statement] statement |> Text.strip

output `shouldBe` [text|
output `shouldBe` [trimming|
data Province = Alberta | Britishcolumbia | Saskatchewan | Manitoba | Ontario | Quebec | Novascotia | Newbrunswick | Princeedwardisland | Newfoundlandandlabrador deriving (Eq, Show, Read, Enum)
instance FromField Province where
fromField field (Just value) | value == (Data.Text.Encoding.encodeUtf8 "Alberta") = pure Alberta
Expand Down Expand Up @@ -101,7 +100,7 @@ tests = do
let enum2 = CreateEnumType { name = "apartment_type", values = ["LOFT", "APARTMENT"] }
let output = compileStatementPreview [enum1, enum2] enum1 |> Text.strip

output `shouldBe` [text|
output `shouldBe` [trimming|
data PropertyType = PropertyTypeApartment | House deriving (Eq, Show, Read, Enum)
instance FromField PropertyType where
fromField field (Just value) | value == (Data.Text.Encoding.encodeUtf8 "APARTMENT") = pure PropertyTypeApartment
Expand All @@ -128,7 +127,7 @@ tests = do
let compileOutput = compileStatementPreview [statement] statement |> Text.strip

it "should compile CanCreate instance with sqlQuery" $ \statement -> do
getInstanceDecl "CanCreate" compileOutput `shouldBe` [text|
getInstanceDecl "CanCreate" compileOutput `shouldBe` [trimming|
instance CanCreate User where
create :: (?modelContext :: ModelContext) => User -> IO User
create model = do
Expand All @@ -138,7 +137,7 @@ tests = do
sqlQuery (Query $ "INSERT INTO users (id) VALUES " <> (ByteString.intercalate ", " (List.map (\_ -> "(?)") models)) <> " RETURNING id") (List.concat $ List.map (\model -> [toField (get #id model)]) models)
|]
it "should compile CanUpdate instance with sqlQuery" $ \statement -> do
getInstanceDecl "CanUpdate" compileOutput `shouldBe` [text|
getInstanceDecl "CanUpdate" compileOutput `shouldBe` [trimming|
instance CanUpdate User where
updateRecord model = do
List.head <$> sqlQuery "UPDATE users SET id = ? WHERE id = ? RETURNING id" ((fieldWithUpdate #id model, get #id model))
Expand All @@ -153,7 +152,7 @@ tests = do
}
let compileOutput = compileStatementPreview [statement] statement |> Text.strip

getInstanceDecl "CanUpdate" compileOutput `shouldBe` [text|
getInstanceDecl "CanUpdate" compileOutput `shouldBe` [trimming|
instance CanUpdate User where
updateRecord model = do
List.head <$> sqlQuery "UPDATE users SET id = ?, ids = ? :: UUID[] WHERE id = ? RETURNING id, ids" ((fieldWithUpdate #id model, fieldWithUpdate #ids model, get #id model))
Expand All @@ -170,7 +169,7 @@ tests = do
}
let compileOutput = compileStatementPreview [statement] statement |> Text.strip

compileOutput `shouldBe` [text|
compileOutput `shouldBe` [trimming|
data User' = User {id :: (Id' "users"), ids :: (Maybe [UUID]), electricityUnitPrice :: Double, meta :: MetaBag} deriving (Eq, Show)
instance InputValue User where inputValue = IHP.ModelSupport.recordToInputValue
type User = User'
Expand Down Expand Up @@ -229,7 +228,7 @@ tests = do
}
let compileOutput = compileStatementPreview [statement] statement |> Text.strip

compileOutput `shouldBe` [text|
compileOutput `shouldBe` [trimming|
data User' = User {id :: (Id' "users"), ids :: (Maybe [UUID]), electricityUnitPrice :: Double, meta :: MetaBag} deriving (Eq, Show)
instance InputValue User where inputValue = IHP.ModelSupport.recordToInputValue
type User = User'
Expand Down

0 comments on commit 3d727b1

Please sign in to comment.