split out types

This commit is contained in:
Joey Hess 2014-02-17 00:18:57 -04:00
parent d7a95098fb
commit e806152f77
2 changed files with 63 additions and 42 deletions

View file

@ -10,15 +10,13 @@
module Annex.View where
import Common.Annex
import Logs.MetaData
import Types.View
import Types.MetaData
import qualified Git.Types as Git
import qualified Git.Ref
import qualified Git.DiffTree
import qualified Git.Branch
import qualified Git.Index
import Git.Sha (nullSha)
import Utility.QuickCheck
import qualified Data.Set as S
import Data.Char
@ -31,42 +29,6 @@ import Text.Regex.TDFA.String
#else
#endif
type View = [(MetaField, ViewFilter)]
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
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
matchGlob :: Glob -> String -> Bool
#ifdef WITH_TDFA
matchGlob (Glob _ r) s = case execute r s of
@ -153,9 +115,6 @@ multiValue (FilterGlob _) = True
viewTooLarge :: View -> Bool
viewTooLarge view = length (filter (multiValue . snd) view) > 5
type FileView = FilePath
type MkFileView = FilePath -> FileView
{- Checks if metadata matches a filter, and if so returns the value,
- or values that match. -}
matchFilter :: MetaData -> MetaField -> ViewFilter -> Maybe [MetaValue]

62
Types/View.hs Normal file
View file

@ -0,0 +1,62 @@
{- types for metadata based branch views
-
- Copyright 2014 Joey Hess <joey@kitenet.net>
-
- 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 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. -}
type View = [(MetaField, ViewFilter)]
{- Only files with metadata matching the view are displayed. -}
type FileView = FilePath
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
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