Skip to content

Commit

Permalink
Enum values can contain spaces now
Browse files Browse the repository at this point in the history
  • Loading branch information
mpscholten committed Jan 2, 2021
1 parent 8b6e1bf commit 2370f24
Show file tree
Hide file tree
Showing 6 changed files with 95 additions and 7 deletions.
29 changes: 29 additions & 0 deletions IHP/NameSupport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ module IHP.NameSupport
, fieldNameToColumnName
, escapeHaskellKeyword
, tableNameToControllerName
, enumValueToControllerName
, toSlug
) where

Expand All @@ -23,6 +24,9 @@ import Data.String.Conversions (cs)
import qualified Data.Char as Char
import qualified Text.Inflections as Inflector
import qualified Text.Countable as Countable
import qualified Data.Maybe as Maybe
import qualified Data.List as List
import Control.Monad (join)

-- | Transforms a underscore table name to a camel case model name.
--
Expand Down Expand Up @@ -57,6 +61,31 @@ tableNameToControllerName tableName = do
else ucfirst tableName
{-# INLINABLE tableNameToControllerName #-}

-- | Transforms a enum value to a name for a model
--
-- >>> enumValueToControllerName "happy"
-- "Happy"
--
-- >>> enumValueToControllerName "very happy"
-- "VeryHappy"
--
-- >>> enumValueToControllerName "very_happy"
-- "VeryHappy"
enumValueToControllerName :: Text -> Text
enumValueToControllerName enumValue =
let
words :: [Inflector.SomeWord]
words =
enumValue
|> splitOn " "
|> List.map (Inflector.parseSnakeCase [])
|> List.map (\case
Left failed -> error (cs $ "enumValueToControllerName failed for " <> show failed)
Right result -> result)
|> join
in
Inflector.camelizeCustom True words

-- | Transforms a camel case model name to a underscored table name.
--
-- >>> modelNameToTableName "User"
Expand Down
12 changes: 6 additions & 6 deletions IHP/SchemaCompiler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module IHP.SchemaCompiler
import ClassyPrelude
import Data.String.Conversions (cs)
import Data.String.Interpolate (i)
import IHP.NameSupport (tableNameToModelName, columnNameToFieldName)
import IHP.NameSupport (tableNameToModelName, columnNameToFieldName, enumValueToControllerName)
import Data.Maybe (fromJust)
import qualified Data.Text as Text
import qualified System.Directory as Directory
Expand Down Expand Up @@ -334,16 +334,16 @@ compileEnumDataDefinitions enum@(CreateEnumType { name, values }) =
<> indent (unlines (map compileFromFieldInstanceForValue values))
<> " fromField field (Just value) = returnError ConversionFailed field (\"Unexpected value for enum value. Got: \" <> Data.String.Conversions.cs value)\n"
<> " fromField field Nothing = returnError UnexpectedNull field \"Unexpected null for enum value\"\n"
<> "instance Default " <> modelName <> " where def = " <> tableNameToModelName (unsafeHead values) <> "\n"
<> "instance Default " <> modelName <> " where def = " <> enumValueToControllerName (unsafeHead values) <> "\n"
<> "instance ToField " <> modelName <> " where\n" <> indent (unlines (map compileToFieldInstanceForValue values))
<> "instance InputValue " <> modelName <> " where\n" <> indent (unlines (map compileInputValue values)) <> "\n"
<> "instance IHP.Controller.Param.ParamReader " <> modelName <> " where readParameter = IHP.Controller.Param.enumParamReader\n"
where
modelName = tableNameToModelName name
valueConstructors = map tableNameToModelName values
compileFromFieldInstanceForValue value = "fromField field (Just value) | value == (Data.Text.Encoding.encodeUtf8 " <> tshow value <> ") = pure " <> tableNameToModelName value
compileToFieldInstanceForValue value = "toField " <> tableNameToModelName value <> " = toField (" <> tshow value <> " :: Text)"
compileInputValue value = "inputValue " <> tableNameToModelName value <> " = " <> tshow value <> " :: Text"
valueConstructors = map enumValueToControllerName values
compileFromFieldInstanceForValue value = "fromField field (Just value) | value == (Data.Text.Encoding.encodeUtf8 " <> tshow value <> ") = pure " <> enumValueToControllerName value
compileToFieldInstanceForValue value = "toField " <> enumValueToControllerName value <> " = toField (" <> tshow value <> " :: Text)"
compileInputValue value = "inputValue " <> enumValueToControllerName value <> " = " <> tshow value <> " :: Text"

compileToRowValues :: [Text] -> Text
compileToRowValues bindingValues | length bindingValues == 1 = "Only (" <> (unsafeHead bindingValues) <> ")"
Expand Down
4 changes: 3 additions & 1 deletion Test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ import qualified Test.Controller.ContextSpec
import qualified Test.Controller.ParamSpec
import qualified Test.SchemaMigrationSpec
import qualified Test.ModelSupportSpec
import qualified Test.SchemaCompilerSpec

main :: IO ()
main = hspec do
Expand All @@ -50,4 +51,5 @@ main = hspec do
Test.Controller.ContextSpec.tests
Test.Controller.ParamSpec.tests
Test.SchemaMigrationSpec.tests
Test.ModelSupportSpec.tests
Test.ModelSupportSpec.tests
Test.SchemaCompilerSpec.tests
13 changes: 13 additions & 0 deletions Test/NameSupportSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,19 @@ tests = do
tableNameToControllerName "user_projects" `shouldBe` "UserProjects"
tableNameToControllerName "users_projects" `shouldBe` "UsersProjects"
tableNameToControllerName "people" `shouldBe` "People"

describe "enumValueToControllerName" do
it "should handle spaces in table names" do
enumValueToControllerName "very happy" `shouldBe` "VeryHappy"
enumValueToControllerName "sad" `shouldBe` "Sad"
enumValueToControllerName "very sad" `shouldBe` "VerySad"

it "should deal with typical enum cases" do
enumValueToControllerName "job_status_not_started" `shouldBe` "JobStatusNotStarted"
enumValueToControllerName "job_status_running" `shouldBe` "JobStatusRunning"
enumValueToControllerName "job_status_failed" `shouldBe` "JobStatusFailed"
enumValueToControllerName "job_status_succeeded" `shouldBe` "JobStatusSucceeded"
enumValueToControllerName "job_status_retry" `shouldBe` "JobStatusRetry"

describe "modelNameToTableName" do
it "should deal with empty input" do
Expand Down
43 changes: 43 additions & 0 deletions Test/SchemaCompilerSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,43 @@
{-|
Module: Test.SchemaCompilerSpec
Copyright: (c) digitally induced GmbH, 2020
-}
module Test.SchemaCompilerSpec where

import Test.Hspec
import IHP.Prelude
import IHP.SchemaCompiler
import IHP.IDE.SchemaDesigner.Types
import NeatInterpolation
import qualified Data.Text as Text

tests = do
describe "SchemaCompiler" do
describe "compileEnumDataDefinitions" do
it "should deal with enum values that have spaces" do
let statement = CreateEnumType { name = "mood", values = ["happy", "very happy", "sad", "very sad"] }
let output = compileStatementPreview [statement] statement |> Text.strip

output `shouldBe` [text|
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
fromField field (Just value) | value == (Data.Text.Encoding.encodeUtf8 "very happy") = pure VeryHappy
fromField field (Just value) | value == (Data.Text.Encoding.encodeUtf8 "sad") = pure Sad
fromField field (Just value) | value == (Data.Text.Encoding.encodeUtf8 "very sad") = pure VerySad
fromField field (Just value) = returnError ConversionFailed field ("Unexpected value for enum value. Got: " <> Data.String.Conversions.cs value)
fromField field Nothing = returnError UnexpectedNull field "Unexpected null for enum value"
instance Default Mood where def = Happy
instance ToField Mood where
toField Happy = toField ("happy" :: Text)
toField VeryHappy = toField ("very happy" :: Text)
toField Sad = toField ("sad" :: Text)
toField VerySad = toField ("very sad" :: Text)
instance InputValue Mood where
inputValue Happy = "happy" :: Text
inputValue VeryHappy = "very happy" :: Text
inputValue Sad = "sad" :: Text
inputValue VerySad = "very sad" :: Text

instance IHP.Controller.Param.ParamReader Mood where readParameter = IHP.Controller.Param.enumParamReader
|]
1 change: 1 addition & 0 deletions shell.nix
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,7 @@ let
# Development Specific Tools (not in ihp.nix)
mmark-cli
hspec
neat-interpolation
]);
in
pkgs.stdenv.mkDerivation {
Expand Down

0 comments on commit 2370f24

Please sign in to comment.