hnix/src/Nix/Cited.hs

63 lines
1.9 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DeriveAnyClass #-}
2019-03-12 15:21:24 +01:00
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-missing-signatures #-}
module Nix.Cited where
import Control.Comonad
import Control.Comonad.Env
import Data.Typeable ( Typeable )
import GHC.Generics
import Lens.Family2.TH
2019-03-12 15:21:24 +01:00
import Nix.Expr.Types.Annotated
import Nix.Scope
2019-03-12 15:21:24 +01:00
data Provenance m v = Provenance
{ _lexicalScope :: Scopes m v
, _originExpr :: NExprLocF (Maybe v)
2019-03-12 15:21:24 +01:00
-- ^ When calling the function x: x + 2 with argument x = 3, the
-- 'originExpr' for the resulting value will be 3 + 2, while the
-- 'contextExpr' will be @(x: x + 2) 3@, preserving not only the
-- result of the call, but what was called and with what arguments.
}
deriving (Generic, Typeable, Show)
2019-03-12 15:21:24 +01:00
data NCited m v a = NCited
{ _provenance :: [Provenance m v]
2019-03-12 15:21:24 +01:00
, _cited :: a
}
deriving (Generic, Typeable, Functor, Foldable, Traversable, Show)
instance Applicative (NCited m v) where
2019-03-12 15:21:24 +01:00
pure = NCited []
NCited xs f <*> NCited ys x = NCited (xs <> ys) (f x)
instance Comonad (NCited m v) where
2019-03-12 15:21:24 +01:00
duplicate p = NCited (_provenance p) p
extract = _cited
instance ComonadEnv [Provenance m v] (NCited m v) where
2019-03-12 15:21:24 +01:00
ask = _provenance
$(makeLenses ''Provenance)
$(makeLenses ''NCited)
2019-03-14 07:24:11 +01:00
class HasCitations m v a where
citations :: a -> [Provenance m v]
addProvenance :: Provenance m v -> a -> a
2019-03-14 07:24:11 +01:00
instance HasCitations m v (NCited m v a) where
citations = _provenance
addProvenance x (NCited p v) = (NCited (x : p) v)
2019-03-14 07:24:11 +01:00
class HasCitations1 m v f where
citations1 :: f a -> [Provenance m v]
addProvenance1 :: Provenance m v -> f a -> f a