summaryrefslogtreecommitdiff
path: root/Types
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2014-02-18 21:50:24 -0400
committerGravatar Joey Hess <joey@kitenet.net>2014-02-18 21:50:24 -0400
commitb20cb8393f503ea6b12d6155f80c5be12157af49 (patch)
treecba6a8e88b6a9731911bd9e99a401a59fe09a497 /Types
parent7ca70b4a07ae9b1f9b217c0e960001ff3147bf5a (diff)
parentd8cc840cc7fd9d543486b7a86426eb4bc444b5aa (diff)
Merge branch 'view'
Diffstat (limited to 'Types')
-rw-r--r--Types/MetaData.hs6
-rw-r--r--Types/View.hs51
2 files changed, 20 insertions, 37 deletions
diff --git a/Types/MetaData.hs b/Types/MetaData.hs
index 248a96abb..601757315 100644
--- a/Types/MetaData.hs
+++ b/Types/MetaData.hs
@@ -53,13 +53,13 @@ newtype MetaData = MetaData (M.Map MetaField (S.Set MetaValue))
{- A metadata value can be currently be set (True), or may have been
- set before and we're remembering it no longer is (False). -}
newtype CurrentlySet = CurrentlySet Bool
- deriving (Show, Eq, Ord, Arbitrary)
+ deriving (Read, Show, Eq, Ord, Arbitrary)
newtype MetaField = MetaField String
- deriving (Show, Eq, Ord)
+ deriving (Read, Show, Eq, Ord)
data MetaValue = MetaValue CurrentlySet String
- deriving (Show)
+ deriving (Read, Show)
{- Metadata values compare and order the same whether currently set or not. -}
instance Eq MetaValue where
diff --git a/Types/View.hs b/Types/View.hs
index 2c30541fa..f1759e0e0 100644
--- a/Types/View.hs
+++ b/Types/View.hs
@@ -5,29 +5,31 @@
- Licensed under the GNU GPL version 3 or higher.
-}
-{-# LANGUAGE CPP #-}
-
module Types.View where
import Common.Annex
import Types.MetaData
import Utility.QuickCheck
+import qualified Git
import qualified Data.Set as S
-#ifdef WITH_TDFA
-import Text.Regex.TDFA
-#else
-#endif
+{- A view is a list of fields with filters on their allowed values,
+ - which are applied to files in a parent git branch. -}
+data View = View
+ { viewParentBranch :: Git.Branch
+ , viewComponents :: [ViewComponent]
+ }
+ deriving (Eq, Show)
-{- A view is a list of fields with filters on their allowed values. -}
-type View = [ViewComponent]
+instance Arbitrary View where
+ arbitrary = View <$> pure (Git.Ref "master") <*> arbitrary
data ViewComponent = ViewComponent
{ viewField :: MetaField
, viewFilter :: ViewFilter
}
- deriving (Show, Eq)
+ deriving (Eq, Show, Read)
instance Arbitrary ViewComponent where
arbitrary = ViewComponent <$> arbitrary <*> arbitrary
@@ -38,34 +40,15 @@ type MkFileView = FilePath -> FileView
data ViewFilter
= FilterValues (S.Set MetaValue)
- | FilterGlob Glob
-
-instance Show ViewFilter where
- show (FilterValues s) = show s
- show (FilterGlob g) = getGlob g
-
-instance Eq ViewFilter where
- FilterValues x == FilterValues y = x == y
- FilterGlob x == FilterGlob y = x == y
- _ == _ = False
+ | FilterGlob String
+ deriving (Eq, Show, Read)
instance Arbitrary ViewFilter where
arbitrary = do
size <- arbitrarySizedBoundedIntegral `suchThat` (< 100)
FilterValues . S.fromList <$> vector size
-#ifdef WITH_TDFA
-data Glob = Glob String Regex
-#else
-data Glob = Glob String
-#endif
-
-instance Eq Glob where
- a == b = getGlob a == getGlob b
-
-getGlob :: Glob -> String
-#ifdef WITH_TDFA
-getGlob (Glob g _) = g
-#else
-getGlob (Glob g) = g
-#endif
+{- Can a ViewFilter match multiple different MetaValues? -}
+multiValue :: ViewFilter -> Bool
+multiValue (FilterValues s) = S.size s > 1
+multiValue (FilterGlob _) = True