Skip to content

Commit 732a862

Browse files
committed
feat: add implementation of std.thisFile
Fixes #65
1 parent bb95143 commit 732a862

File tree

4 files changed

+19
-3
lines changed

4 files changed

+19
-3
lines changed

src/Language/Jsonnet/Eval.hs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,7 @@ rnf = whnf >=> manifest
5656
whnfV :: Value -> Eval Value
5757
whnfV (VIndir loc) = whnfIndir loc >>= whnfV
5858
whnfV (VThunk c e) = withEnv e (whnf c)
59+
whnfV (VThunk' v) = v
5960
whnfV v = pure v
6061

6162
whnf :: Core -> Eval Value
@@ -417,6 +418,7 @@ manifest = \case
417418
VFun _ -> throwE (ManifestError "function")
418419
v@VThunk {} -> whnfV v >>= manifest
419420
v@VIndir {} -> whnfV v >>= manifest
421+
v@VThunk' {} -> whnfV v >>= manifest
420422
_ -> throwE (ManifestError "impossible")
421423
where
422424
filterNonAssertionFields :: HashMap Text (JSON.Value, Bool) -> HashMap Text JSON.Value
@@ -517,6 +519,7 @@ showTy = \case
517519
VPrim _ -> pure "function"
518520
VThunk {} -> pure "thunk"
519521
VIndir {} -> pure "pointer"
522+
VThunk' _ -> pure "thunk"
520523

521524
--v@VThunk {} -> whnfV v >>= showTy
522525
--v@VIndir {} -> whnfV v >>= showTy
@@ -597,6 +600,10 @@ instance {-# OVERLAPS #-} (HasValue a, HasValue b, HasValue c) => HasValue (a ->
597600
{-# INLINE inj #-}
598601
proj = throwTypeMismatch "impossible"
599602

603+
instance {-# OVERLAPS #-} HasValue a => HasValue (Eval a) where
604+
inj a = VThunk' $ inj <$> a
605+
proj = proj'
606+
600607
instance {-# OVERLAPS #-} (HasValue a, HasValue b) => HasValue (a -> Eval b) where
601608
inj f = VFun $ proj' >=> fmap inj . f
602609
{-# INLINE inj #-}

src/Language/Jsonnet/Eval/Monad.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,9 +21,10 @@ import qualified Data.Map.Lazy as M (union)
2121
import Language.Jsonnet.Common (Backtrace (..), StackFrame (..))
2222
import Language.Jsonnet.Core (Core)
2323
import Language.Jsonnet.Error (Error (EvalError), EvalError)
24-
import Language.Jsonnet.Parser.SrcSpan (SrcSpan)
24+
import Language.Jsonnet.Parser.SrcSpan (SrcSpan, spanBegin)
2525
import Unbound.Generics.LocallyNameless
2626
import Unbound.Generics.LocallyNameless.Name
27+
import Text.Megaparsec.Pos
2728

2829
type Ctx a = Map (Name Core) a
2930

@@ -107,3 +108,6 @@ getBacktrace = do
107108
case sequence sp of
108109
Just sp' -> zipWith StackFrame sc sp'
109110
Nothing -> []
111+
112+
getFilename :: EvalM a (Maybe FilePath)
113+
getFilename = (sourceName . spanBegin <$>) <$> view currentPos

src/Language/Jsonnet/Std/Lib.hs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ import Data.Word
2828
import Language.Jsonnet.Common
2929
import Language.Jsonnet.Error
3030
import Language.Jsonnet.Eval
31-
import Language.Jsonnet.Eval.Monad
31+
import Language.Jsonnet.Eval.Monad (getFilename, throwE)
3232
import Language.Jsonnet.Value
3333
import Unbound.Generics.LocallyNameless
3434
import Prelude hiding (length)
@@ -71,7 +71,8 @@ std extVars = VObj $ H.fromList $ map f xs
7171
("objectHasEx", inj objectHasEx),
7272
("objectFieldsEx", inj objectFieldsEx),
7373
("parseJson", inj (JSON.decodeStrict @Value)),
74-
("extVar", inj (lookupExtVar extVars))
74+
("extVar", inj (lookupExtVar extVars)),
75+
("thisFile", inj thisFile)
7576
]
7677

7778
lookupExtVar :: ExtVars -> Text -> Eval Value
@@ -105,3 +106,6 @@ makeArray n f = traverse f (V.fromList [0 .. n - 1])
105106

106107
hypot :: Double -> Double -> Double
107108
hypot a b = sqrt (a * a + b * b)
109+
110+
thisFile :: Eval Value
111+
thisFile = inj <$> getFilename

src/Language/Jsonnet/Value.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,7 @@ data Value
4444
| VPrim !Prim
4545
| VClos !Lam !Env
4646
| VFun !Fun
47+
| VThunk' !(Eval Value)
4748

4849
instance FromJSON Value where
4950
parseJSON = \case

0 commit comments

Comments
 (0)