Make URI's be separate from strings

This commit is contained in:
Silvan Mosberger 2019-05-16 21:42:49 +02:00 committed by John Wiegley
parent 8341c1b4ac
commit f682907c97
6 changed files with 14 additions and 6 deletions

View file

@ -22,9 +22,11 @@ import GHC.Generics
-- they appear in both the parsed AST (in the form of literals) and -- they appear in both the parsed AST (in the form of literals) and
-- the evaluated form. -- the evaluated form.
data NAtom data NAtom
-- | An URI like @https://example.com@.
= NURI Text
-- | An integer. The c nix implementation currently only supports -- | An integer. The c nix implementation currently only supports
-- integers that fit in the range of 'Int64'. -- integers that fit in the range of 'Int64'.
= NInt Integer | NInt Integer
-- | A floating point number -- | A floating point number
| NFloat Float | NFloat Float
-- | Booleans. -- | Booleans.
@ -40,6 +42,7 @@ instance Serialise NAtom
-- | Translate an atom into its nix representation. -- | Translate an atom into its nix representation.
atomText :: NAtom -> Text atomText :: NAtom -> Text
atomText (NURI t) = t
atomText (NInt i) = pack (show i) atomText (NInt i) = pack (show i)
atomText (NFloat f) = pack (showNixFloat f) atomText (NFloat f) = pack (showNixFloat f)
where where

View file

@ -1347,6 +1347,7 @@ toXML_ v = demand v $ fmap (nvStr . toXML) . normalForm
typeOf :: MonadNix e t f m => NValue t f m -> m (NValue t f m) typeOf :: MonadNix e t f m => NValue t f m -> m (NValue t f m)
typeOf v = demand v $ toValue . principledMakeNixStringWithoutContext . \case typeOf v = demand v $ toValue . principledMakeNixStringWithoutContext . \case
NVConstant a -> case a of NVConstant a -> case a of
NURI _ -> "string"
NInt _ -> "int" NInt _ -> "int"
NFloat _ -> "float" NFloat _ -> "float"
NBool _ -> "bool" NBool _ -> "bool"

View file

@ -300,13 +300,14 @@ instance MonadLint e m => MonadEval (Symbolic m) m where
go f l c = go f l c =
[(Text.pack "file", f), (Text.pack "line", l), (Text.pack "col", c)] [(Text.pack "file", f), (Text.pack "line", l), (Text.pack "col", c)]
evalConstant c = mkSymbolic [TConstant [go c]] evalConstant c = mkSymbolic [go c]
where where
go = \case go = \case
NInt _ -> TInt NURI _ -> TStr
NFloat _ -> TFloat NInt _ -> TConstant [TInt]
NBool _ -> TBool NFloat _ -> TConstant [TFloat]
NNull -> TNull NBool _ -> TConstant [TBool]
NNull -> TConstant [TNull]
evalString = const $ mkSymbolic [TStr] evalString = const $ mkSymbolic [TStr]
evalLiteralPath = const $ mkSymbolic [TPath] evalLiteralPath = const $ mkSymbolic [TPath]

View file

@ -442,6 +442,7 @@ instance MonadInfer m => MonadEval (Judgment s) (InferT s m) where
evalConstant c = return $ Judgment As.empty [] (go c) evalConstant c = return $ Judgment As.empty [] (go c)
where where
go = \case go = \case
NURI _ -> typeString
NInt _ -> typeInt NInt _ -> typeInt
NFloat _ -> typeFloat NFloat _ -> typeFloat
NBool _ -> typeBool NBool _ -> typeBool

View file

@ -413,6 +413,7 @@ data ValueType
valueType :: NValueF a m r -> ValueType valueType :: NValueF a m r -> ValueType
valueType = \case valueType = \case
NVConstantF a -> case a of NVConstantF a -> case a of
NURI _ -> TString NoContext
NInt _ -> TInt NInt _ -> TInt
NFloat _ -> TFloat NFloat _ -> TFloat
NBool _ -> TBool NBool _ -> TBool

View file

@ -30,6 +30,7 @@ toXML = runWithStringContext . fmap pp . iterNValue (\_ _ -> cyc) phi
phi :: NValue' t f m (WithStringContext Element) -> WithStringContext Element phi :: NValue' t f m (WithStringContext Element) -> WithStringContext Element
phi = \case phi = \case
NVConstant' a -> case a of NVConstant' a -> case a of
NURI t -> return $ mkElem "string" "value" (Text.unpack t)
NInt n -> return $ mkElem "int" "value" (show n) NInt n -> return $ mkElem "int" "value" (show n)
NFloat f -> return $ mkElem "float" "value" (show f) NFloat f -> return $ mkElem "float" "value" (show f)
NBool b -> return $ mkElem "bool" "value" (if b then "true" else "false") NBool b -> return $ mkElem "bool" "value" (if b then "true" else "false")