update-nix-fetchgit-0.2.2: A program to update fetchgit values in Nix expressions
Safe HaskellNone
LanguageHaskell2010

Nix.Match

Description

A set of functions for matching on Nix expression trees and extracting the values of sub-trees.

Synopsis

Documentation

match :: Matchable t => WithHoles t v -> Fix t -> Maybe [(v, Fix t)] Source #

Match a tree with holes against a tree without holes, returning the values of the holes if it matches.

NExprF and NExprLocF are both instances of Matchable. NExprLocF does not require the annotations to match. Please see the Matchable instance documentation for NExprF for more details.

>>> import Nix.TH
>>> match (addHoles [nix|{foo = x: ^foo; bar = ^bar;}|]) [nix|{foo = x: "hello"; bar = "world"; baz = "!";}|]
Just [("bar",Fix (NStr (DoubleQuoted [Plain "world"]))),("foo",Fix (NStr (DoubleQuoted [Plain "hello"])))]

findMatches Source #

Arguments

:: Matchable t 
=> WithHoles t v

Needle

-> Fix t

Haystack

-> [(Fix t, [(v, Fix t)])] 

Find all the needles in a haystack, returning the matched expression as well as their filled holes. Results are returned productively in preorder.

>>> import Nix.TH
>>> import Control.Arrow
>>> pretty = prettyNix *** (fmap @[] (fmap @((,) Text) prettyNix))
>>> pretty <$> findMatches (addHoles [nix|{x=^x;}|]) [nix|{x=1;a={x=2;};}|]
[({ x = 1; a = { x = 2; }; },[("x",1)]),({ x = 2; },[("x",2)])]

class Traversable t => Matchable t where Source #

Instances for this class can be derived for any type with a Generic1 instance.

Minimal complete definition

Nothing

Methods

zipMatchLeft :: t a -> t b -> Maybe (t (a, b)) Source #

Match one level of structure, returning the matched structure with sub structures to match. Needle is the first argument, matchee is the second.

Unlike the Unifiable class in the "unification-fd" package, this doesn't have to be a commutative operation, the needle will always be the first parameter and instances are free to treat if differently if appropriate.

default zipMatchLeft :: (Generic1 t, GMatchable (Rep1 t)) => t a -> t b -> Maybe (t (a, b)) Source #

Instances

Instances details
Matchable [] Source # 
Instance details

Defined in Nix.Match

Methods

zipMatchLeft :: [a] -> [b] -> Maybe [(a, b)] Source #

Matchable Maybe Source # 
Instance details

Defined in Nix.Match

Methods

zipMatchLeft :: Maybe a -> Maybe b -> Maybe (Maybe (a, b)) Source #

Matchable NonEmpty Source # 
Instance details

Defined in Nix.Match

Methods

zipMatchLeft :: NonEmpty a -> NonEmpty b -> Maybe (NonEmpty (a, b)) Source #

Matchable NExprF Source #

There are a few special cases when matching expressions to make writing matchers nicer:

  • For attrsets and let bindings, the matching is done on the needle's keys only. i.e. the matchee may have extra keys which are ignored.
  • For attrsets and let bindings, bindings which have a LHS beginning with _ are treated as optional. If they are not present then any holes on their RHS will not be filled.
  • Attrsets match ignoring recursiveness
  • If a function in the needle has _ as its parameter, it matches everything, so _ acts as a wildcard pattern.
Instance details

Defined in Nix.Match

Methods

zipMatchLeft :: NExprF a -> NExprF b -> Maybe (NExprF (a, b)) Source #

Matchable Binding Source #

The matched pair uses the source location of the first argument

Instance details

Defined in Nix.Match

Methods

zipMatchLeft :: Binding a -> Binding b -> Maybe (Binding (a, b)) Source #

Matchable Params Source # 
Instance details

Defined in Nix.Match

Methods

zipMatchLeft :: Params a -> Params b -> Maybe (Params (a, b)) Source #

Matchable NString Source # 
Instance details

Defined in Nix.Match

Methods

zipMatchLeft :: NString a -> NString b -> Maybe (NString (a, b)) Source #

Matchable NKeyName Source #

No Generic1 instance

Instance details

Defined in Nix.Match

Methods

zipMatchLeft :: NKeyName a -> NKeyName b -> Maybe (NKeyName (a, b)) Source #

Eq a => Matchable ((,) a) Source # 
Instance details

Defined in Nix.Match

Methods

zipMatchLeft :: (a, a0) -> (a, b) -> Maybe (a, (a0, b)) Source #

Matchable (Ann ann) Source #

Doesn't require the annotations to match, returns the second annotation.

Instance details

Defined in Nix.Match

Methods

zipMatchLeft :: Ann ann a -> Ann ann b -> Maybe (Ann ann (a, b)) Source #

Matchable (Antiquoted Text) Source # 
Instance details

Defined in Nix.Match

(Matchable f, Matchable g) => Matchable (Compose f g) Source # 
Instance details

Defined in Nix.Match

Methods

zipMatchLeft :: Compose f g a -> Compose f g b -> Maybe (Compose f g (a, b)) Source #

class (Traversable t, Generic1 t) => GMatchable t where Source #

A class used in the default definition for zipMatchLeft

Methods

gZipMatchLeft :: t a -> t b -> Maybe (t (a, b)) Source #

Instances

Instances details
GMatchable Par1 Source # 
Instance details

Defined in Nix.Match

Methods

gZipMatchLeft :: Par1 a -> Par1 b -> Maybe (Par1 (a, b)) Source #

GMatchable (U1 :: Type -> Type) Source # 
Instance details

Defined in Nix.Match

Methods

gZipMatchLeft :: U1 a -> U1 b -> Maybe (U1 (a, b)) Source #

Matchable x => GMatchable (Rec1 x) Source # 
Instance details

Defined in Nix.Match

Methods

gZipMatchLeft :: Rec1 x a -> Rec1 x b -> Maybe (Rec1 x (a, b)) Source #

Eq c => GMatchable (K1 m c :: Type -> Type) Source # 
Instance details

Defined in Nix.Match

Methods

gZipMatchLeft :: K1 m c a -> K1 m c b -> Maybe (K1 m c (a, b)) Source #

(GMatchable l, GMatchable r) => GMatchable (l :+: r) Source # 
Instance details

Defined in Nix.Match

Methods

gZipMatchLeft :: (l :+: r) a -> (l :+: r) b -> Maybe ((l :+: r) (a, b)) Source #

(GMatchable l, GMatchable r) => GMatchable (l :*: r) Source # 
Instance details

Defined in Nix.Match

Methods

gZipMatchLeft :: (l :*: r) a -> (l :*: r) b -> Maybe ((l :*: r) (a, b)) Source #

GMatchable t => GMatchable (M1 m i t) Source # 
Instance details

Defined in Nix.Match

Methods

gZipMatchLeft :: M1 m i t a -> M1 m i t b -> Maybe (M1 m i t (a, b)) Source #

(Matchable a, GMatchable b) => GMatchable (a :.: b) Source # 
Instance details

Defined in Nix.Match

Methods

gZipMatchLeft :: (a :.: b) a0 -> (a :.: b) b0 -> Maybe ((a :.: b) (a0, b0)) Source #

data WithHoles t v Source #

Like Fix but each layer could instead be a Hole

Constructors

Hole !v 
Term !(t (WithHoles t v)) 

Instances

Instances details
(Typeable t, Data (t (WithHoles t v)), Data v) => Data (WithHoles t v) Source # 
Instance details

Defined in Nix.Match

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WithHoles t v -> c (WithHoles t v) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WithHoles t v) #

toConstr :: WithHoles t v -> Constr #

dataTypeOf :: WithHoles t v -> DataType #

dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (WithHoles t v)) #

dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (WithHoles t v)) #

gmapT :: (forall b. Data b => b -> b) -> WithHoles t v -> WithHoles t v #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WithHoles t v -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WithHoles t v -> r #

gmapQ :: (forall d. Data d => d -> u) -> WithHoles t v -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WithHoles t v -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WithHoles t v -> m (WithHoles t v) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WithHoles t v -> m (WithHoles t v) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WithHoles t v -> m (WithHoles t v) #

addHoles :: NExpr -> WithHoles NExprF Text Source #

Make syntactic holes into Holes

addHolesLoc :: NExprLoc -> WithHoles NExprLocF Text Source #

Make syntactic holes into Holes

isOptionalPath :: NAttrPath r -> Maybe (NAttrPath r) Source #

Basically: does the path begin with an underscore, if so return it removed without the underscore.