aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorLibravatar Alexander Foremny <aforemny@posteo.de>2024-12-17 20:34:31 +0100
committerLibravatar Alexander Foremny <aforemny@posteo.de>2025-02-19 18:09:41 +0100
commitd29d951cf8c5558511830a85bb91ab030711b7e7 (patch)
tree88fa48bad69815b7e2a30cb9de3393343c555c6c
parentfe07f05b8e4f0c7e6eec2714ee1ed5a67b227eda (diff)
ignore nulls in types
-rw-r--r--autotypes/app/Main.hs5
-rw-r--r--autotypes/src/AutoTypes.hs3
-rw-r--r--autotypes/src/AutoTypes/Unify.hs34
3 files changed, 24 insertions, 18 deletions
diff --git a/autotypes/app/Main.hs b/autotypes/app/Main.hs
index d9fa7f4..5ebb30d 100644
--- a/autotypes/app/Main.hs
+++ b/autotypes/app/Main.hs
@@ -3,6 +3,7 @@ module Main where
import AutoTypes.Unify as U
import Data.Aeson (Value, decodeFileStrict', encode)
import qualified Data.ByteString.Lazy as B
+import Data.Maybe
import System.Environment (getArgs)
import System.FilePath (takeFileName)
@@ -10,7 +11,7 @@ main :: IO ()
main = do
filePaths <- getArgs
types <-
- mapM
+ mapMaybeM
( \filePath -> do
Just value <- decodeFileStrict' filePath
pure (U.fromJson value)
@@ -25,3 +26,5 @@ main = do
)
)
)
+
+mapMaybeM = (fmap catMaybes .) . mapM
diff --git a/autotypes/src/AutoTypes.hs b/autotypes/src/AutoTypes.hs
index ddc948c..493fe11 100644
--- a/autotypes/src/AutoTypes.hs
+++ b/autotypes/src/AutoTypes.hs
@@ -6,6 +6,7 @@ where
import qualified AutoTypes.Unify as U
import Data.Aeson (Value, decodeFileStrict', encode)
+import Data.Maybe
import Data.Maybe (fromJust)
import System.Environment (getArgs)
import System.FilePath (takeFileName)
@@ -17,7 +18,7 @@ autoTypes fp fps = autoTypes' <$> go fp <*> mapM go (fp : fps)
autoTypes' :: Value -> [Value] -> U.T
autoTypes' t' ts' =
- let types = map U.fromJson (t' : ts')
+ let types = mapMaybe U.fromJson (t' : ts')
in head
( foldr1
(\ls rs -> (concat [U.unify1 l r | l <- ls, r <- rs]))
diff --git a/autotypes/src/AutoTypes/Unify.hs b/autotypes/src/AutoTypes/Unify.hs
index bfbd05b..29d7ed2 100644
--- a/autotypes/src/AutoTypes/Unify.hs
+++ b/autotypes/src/AutoTypes/Unify.hs
@@ -16,12 +16,13 @@ import qualified Data.Aeson as A
import qualified Data.Aeson.Encode.Pretty as A
import qualified Data.Aeson.Key as K
import qualified Data.Aeson.KeyMap as KM
-import qualified Data.ByteString.Lazy.Char8 as BL
import Data.Aeson.QQ
+import qualified Data.ByteString.Lazy.Char8 as BL
import Data.List (intercalate, nub)
import Data.Map (Map)
import qualified Data.Map as M
import qualified Data.Map.Merge.Lazy as M
+import Data.Maybe
import qualified Data.Set as S
import qualified Data.Text as T
import Data.Time.Clock
@@ -175,31 +176,31 @@ unify (Option Nothing) (Option (Just r)) = Right (Option (Just r))
unify (Option (Just l)) (Option (Just r)) = Option . Just <$> unify l r
-}
-object :: Map String T -> T
-object = Object
+object :: Map String T -> Maybe T
+object = Just . Object
-list :: Maybe T -> T
-list = List
+list :: Maybe T -> Maybe T
+list = Just . List
-string, number, bool, dateTime, null :: T
-string = Scalar String
-number = Scalar Number
-bool = Scalar Bool
-dateTime = Scalar DateTime
-null = Option Nothing
+string, number, bool, dateTime, null :: Maybe T
+string = Just (Scalar String)
+number = Just (Scalar Number)
+bool = Just (Scalar Bool)
+dateTime = Just (Scalar DateTime)
+null = Nothing
data InferException = InferException [T]
deriving (Show)
instance Exception InferException
-fromJson :: A.Value -> T
+fromJson :: A.Value -> Maybe T
fromJson (A.Object kvs) =
case map (first K.toString) (KM.toList kvs) of
- [("$ref", A.String i)] -> Reference (takeDirectory (T.unpack i))
- _ -> object (M.mapKeys K.toString (M.map fromJson (KM.toMap kvs)))
+ [("$ref", A.String i)] -> Just (Reference (takeDirectory (T.unpack i)))
+ _ -> object (M.mapKeys K.toString (M.mapMaybe fromJson (KM.toMap kvs)))
fromJson t@(A.Array vs) =
- let ts = map fromJson (V.toList vs)
+ let ts = mapMaybe fromJson (V.toList vs)
in case nub ts of
[] -> list Nothing
[t] -> list (Just t)
@@ -211,6 +212,7 @@ fromJson (A.Number _) = number
fromJson (A.Bool _) = bool
fromJson A.Null = null
+{-
object1 =
[aesonQQ|{
"firstName": "firstName",
@@ -263,7 +265,7 @@ main =
)
)
)
- )
+ )-}
-- >>= unify (fromJson object2)
-- >>= unify (fromJson object4)