Compare commits

..

22 Commits

Author SHA1 Message Date
c05161eb73 Import firefox UX 2021-01-03 22:08:59 +02:00
e3d47d4d9d Improve readability 2021-01-03 22:08:59 +02:00
ae68414db3 Insert to buuka 2021-01-03 22:08:59 +02:00
01c591434e Some lenses and incomplete importer 2021-01-03 22:08:59 +02:00
b1f3760e06 Query bookmarks from firefox
N+1 queries :/
2021-01-03 22:08:59 +02:00
25ecac21fa List the firefox places.sqlite 2021-01-03 22:08:59 +02:00
a1e67c6387 Refactor to use text instead of string 2021-01-03 22:08:59 +02:00
a921139295 Merge remote-tracking branch 'origin/master' into query 2021-01-03 00:43:39 +02:00
cee5ad8add Query with regexes 2021-01-03 00:39:44 +02:00
527cc0a34c Add regex to the query language 2021-01-03 00:23:43 +02:00
7bae9ca92e More type safety on string types? 2021-01-03 00:16:36 +02:00
9048581ea1 Do GADT instead 2021-01-03 00:14:52 +02:00
4112ed2aeb Tests for foldable 2021-01-03 00:05:33 +02:00
1906ce9964 Use an override for home if it exists 2021-01-02 23:10:07 +02:00
3c1ea67566 Tests for query 2021-01-02 09:17:29 +02:00
55188f514f Initial query AST 2021-01-02 09:09:38 +02:00
e802f66599 Refactor the formatter to its own module 2021-01-02 08:30:56 +02:00
29b71fc216 Fingerprint the 'Buuka' and use it as context 2021-01-01 09:04:48 +02:00
ec5576213f Use hashids for index 2021-01-01 08:34:09 +02:00
d9445823bb List and format 2021-01-01 08:29:24 +02:00
32afc6ba29 Find directory if missing 2021-01-01 08:00:39 +02:00
e741d7fd59 Change the format to a list 2021-01-01 07:55:10 +02:00
17 changed files with 587 additions and 32 deletions

View File

@ -1,3 +1,4 @@
{-# LANGUAGE TupleSections #-}
module Main where module Main where
import Options.Applicative import Options.Applicative
@ -10,17 +11,36 @@ import Data.Environment
import UnliftIO.Directory import UnliftIO.Directory
(XdgDirectory(XdgData), getXdgDirectory) (XdgDirectory(XdgData), getXdgDirectory)
import Data.Foldable
(asum)
import System.Environment
(lookupEnv)
import qualified Operations import qualified Operations
import Data.Query
(Field(..))
commands :: Parser (BuukaM ()) commands :: Parser (BuukaM ())
commands = subparser commands = subparser
( command "insert" (info (insertOpts Operations.insert) (progDesc "Insert a new bookmark"))) ( command "insert" (info (insertOpts Operations.insert <**> helper) (progDesc "Insert a new bookmark"))
<> command "list" (info (pure Operations.list <**> helper) (progDesc "List all the bookmarks"))
<> command "query" (info (queryOpts Operations.query <**> helper) (progDesc "Query the bookmarks"))
<> command "import" (info (pure Operations.importFirefox <**> helper) (progDesc "Import"))
)
where where
insertOpts f = insertOpts f =
f <$> strOption (long "url" <> short 'u' <> metavar "URL") f <$> strOption (long "url" <> short 'u' <> metavar "URL")
<*> optional (strOption (long "title")) <*> optional (strOption (long "title"))
queryOpts f =
uncurry f <$> asum [tagged Title "title", tagged Url "url"]
tagged t x = (t, ) <$> strOption (long x <> metavar "REGEX")
main :: IO () main :: IO ()
main = do main = do
env <- Environment <$> getXdgDirectory XdgData "buuka" env <- Environment <$> (lookupEnv "BUUKA_HOME" >>= maybe defaultHome pure)
execParser (info (commands <**> helper) fullDesc) >>= runBuukaM env execParser (info (commands <**> helper) (fullDesc <> progDesc description)) >>= runBuukaM env
where
defaultHome = getXdgDirectory XdgData "buuka"
description = "Bookmarks manager. Stores the bookmarks in a yaml file under your xdg directory or in a folder specified by the BUUKA_HOME environment variable"

View File

@ -36,22 +36,35 @@ library
exposed-modules: MyLib exposed-modules: MyLib
, Database.Migrations , Database.Migrations
, Control.Monad.Buuka , Control.Monad.Buuka
, Operations.Format
, Operations.Insert , Operations.Insert
, Operations.List
, Operations.Query
, Operations.Import.Firefox
, Operations , Operations
, Data.Environment , Data.Environment
, Data.Buuka , Data.Buuka
, Data.Query
, Data.Functor.Foldable
-- other-modules: -- other-modules:
build-depends: aeson build-depends: aeson
, yaml , yaml
, mtl , mtl
, transformers , transformers
, unliftio , unliftio
, conduit
, conduit-extra
, containers , containers
, exceptions , exceptions
, bytestring , bytestring
, filepath , filepath
, vector
, hashids
, text
, lens
, hashable
, regex-tdfa
, sqlite-simple
, conduit
, conduit-extra
hs-source-dirs: src hs-source-dirs: src
executable buuka executable buuka
@ -68,6 +81,8 @@ test-suite buuka-test
import: common-stanza import: common-stanza
other-modules: Test.Database.Migrations other-modules: Test.Database.Migrations
Test.Data.Buuka Test.Data.Buuka
Test.Data.Query
Test.Data.Functor.Foldable
type: exitcode-stdio-1.0 type: exitcode-stdio-1.0
hs-source-dirs: test hs-source-dirs: test
main-is: MyLibTest.hs main-is: MyLibTest.hs
@ -75,6 +90,8 @@ test-suite buuka-test
, hedgehog , hedgehog
, hedgehog-corpus , hedgehog-corpus
, tasty-hedgehog , tasty-hedgehog
, tasty-hunit
, tasty , tasty
, text , text
, aeson , aeson
, deriving-compat

View File

@ -1,7 +1,9 @@
{ mkDerivation, aeson, base, bytestring, conduit, conduit-extra { mkDerivation, aeson, base, bytestring, conduit, conduit-extra
, containers, exceptions, filepath, hedgehog, hedgehog-corpus, mtl , containers, deriving-compat, exceptions, filepath, hashable
, optparse-applicative, stdenv, tasty, tasty-hedgehog, text , hashids, hedgehog, hedgehog-corpus, lens, mtl
, transformers, unliftio, yaml , optparse-applicative, regex-tdfa, sqlite-simple, stdenv, tasty
, tasty-hedgehog, tasty-hunit, text, transformers, unliftio, vector
, yaml
}: }:
mkDerivation { mkDerivation {
pname = "buuka"; pname = "buuka";
@ -11,11 +13,13 @@ mkDerivation {
isExecutable = true; isExecutable = true;
libraryHaskellDepends = [ libraryHaskellDepends = [
aeson base bytestring conduit conduit-extra containers exceptions aeson base bytestring conduit conduit-extra containers exceptions
filepath mtl transformers unliftio yaml filepath hashable hashids lens mtl regex-tdfa sqlite-simple text
transformers unliftio vector yaml
]; ];
executableHaskellDepends = [ base optparse-applicative unliftio ]; executableHaskellDepends = [ base optparse-applicative unliftio ];
testHaskellDepends = [ testHaskellDepends = [
aeson base hedgehog hedgehog-corpus tasty tasty-hedgehog text aeson base deriving-compat hedgehog hedgehog-corpus tasty
tasty-hedgehog tasty-hunit text
]; ];
license = stdenv.lib.licenses.bsd3; license = stdenv.lib.licenses.bsd3;
} }

View File

@ -25,7 +25,7 @@ import Control.Monad.State
import UnliftIO import UnliftIO
(MonadUnliftIO(..)) (MonadUnliftIO(..))
import UnliftIO.Directory import UnliftIO.Directory
(copyFile) (copyFile, createDirectoryIfMissing)
import UnliftIO.Temporary import UnliftIO.Temporary
(withSystemTempDirectory) (withSystemTempDirectory)
@ -44,7 +44,9 @@ newtype BuukaM a = BuukaM (ReaderT Environment IO a)
) )
runBuukaM :: Environment -> BuukaM a -> IO a runBuukaM :: Environment -> BuukaM a -> IO a
runBuukaM env (BuukaM f) = runReaderT f env runBuukaM env (BuukaM f) = do
createDirectoryIfMissing True (workdir env)
runReaderT f env
data DecodeException data DecodeException
= YamlParseException ParseException = YamlParseException ParseException
@ -56,7 +58,7 @@ buukaQ :: BuukaQ a -> BuukaM a
buukaQ q = do buukaQ q = do
w <- asks workdir w <- asks workdir
decoded <- (decode <$> liftIO (B.readFile (w </> "buuka.yaml"))) `catch` handleNotFound decoded <- (decode <$> liftIO (B.readFile (w </> "buuka.yaml"))) `catch` handleNotFound
either (throwM) (pure . runReader (runBuukaQ q)) decoded either throwM (pure . runReader (runBuukaQ q)) decoded
where where
handleNotFound IOError{ioe_type = NoSuchThing} = pure (Right mempty) handleNotFound IOError{ioe_type = NoSuchThing} = pure (Right mempty)
handleNotFound e = throwM e handleNotFound e = throwM e

View File

@ -1,49 +1,83 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
module Data.Buuka module Data.Buuka
( BuukaQ(..) ( BuukaQ(..)
, BuukaU(..) , BuukaU(..)
, BuukaEntry(..) , BuukaEntry(..)
, url
, title
, URL(..) , URL(..)
, _URL
, Buuka , Buuka
, _Buuka
, insert , insert
, elements
, fingerprint
) )
where where
import Data.Map import Control.Lens (makeLenses, Iso', iso)
(Map)
import qualified Data.Map.Strict as M
import Database.Migrations import Database.Migrations
import Data.Aeson import Data.Aeson
import Data.Bits
(finiteBitSize, shiftR, (.&.))
import Data.Hashable
(Hashable, hash)
import GHC.Generics import GHC.Generics
(Generic) (Generic)
import Data.Text
import Control.Monad.Reader import Control.Monad.Reader
import Control.Monad.State import Control.Monad.State
newtype URL = URL String import Data.ByteString
(ByteString)
import qualified Data.ByteString as B
newtype URL = URL Text
deriving stock (Show, Eq, Generic, Ord) deriving stock (Show, Eq, Generic, Ord)
deriving newtype (ToJSON, FromJSON, FromJSONKey, ToJSONKey) deriving newtype (ToJSON, FromJSON, FromJSONKey, ToJSONKey, Hashable)
_URL :: Iso' URL Text
_URL = iso (\(URL t) -> t) URL
data BuukaEntry data BuukaEntry
= BuukaEntry { url :: URL = BuukaEntry { _url :: URL
, title :: Maybe String , _title :: Maybe Text
} }
deriving stock (Show, Eq, Generic) deriving stock (Show, Eq, Generic)
deriving anyclass (ToJSON, FromJSON) deriving anyclass (ToJSON, FromJSON, Hashable)
makeLenses ''BuukaEntry
instance SafeJSON BuukaEntry where instance SafeJSON BuukaEntry where
type Version BuukaEntry = 0 type Version BuukaEntry = 0
newtype Buuka = Buuka ( Map URL BuukaEntry ) newtype Buuka = Buuka [BuukaEntry]
deriving stock (Show, Eq) deriving stock (Show, Eq)
deriving newtype (Semigroup, Monoid, FromJSON, ToJSON) deriving newtype (Semigroup, Monoid, FromJSON, ToJSON, Hashable)
_Buuka :: Iso' Buuka [BuukaEntry]
_Buuka = iso (\(Buuka b) -> b) Buuka
insert :: BuukaEntry -> Buuka -> Buuka insert :: BuukaEntry -> Buuka -> Buuka
insert e (Buuka b) = Buuka (M.insert (url e) e b) insert e (Buuka b) = Buuka (e : b)
elements :: Buuka -> [BuukaEntry]
elements (Buuka b) = b
-- | Create a (non-cryptographic) hash out of the 'Buuka'
fingerprint :: Buuka -> ByteString
fingerprint = toBS . hash
where
toBS x =
let bs = finiteBitSize x
in B.pack [fromIntegral ((x `shiftR` s) .&. 255) | s <- [0..bs - 1]]
instance SafeJSON Buuka where instance SafeJSON Buuka where
type Version Buuka = 0 type Version Buuka = 0

View File

@ -0,0 +1,44 @@
{-|
Module : Data.Functor.Foldable
Description : Simplified recursion schemes
Copyright : (c) Mats Rauhala, 2020
License : BSD-3-Clause
Maintainer : mats.rauhala@iki.fi
Stability : experimental
Portability : POSIX
Simplified recursion schemes, providing only the minimal schemes
-}
module Data.Functor.Foldable
( Fix(..)
, cata
, ana
, hylo
)
where
import Data.Functor.Classes
newtype Fix f = Fix { getFix :: f (Fix f) }
instance Show1 f => Show (Fix f) where
showsPrec d (Fix f) = showString "Fix " . showsPrec1 d f
instance Eq1 f => Eq (Fix f) where
(Fix a) == (Fix b) = liftEq (==) a b
-- | Catamorphism or the fold
--
-- Fold a recursive structure into a value
cata :: Functor f => (f a -> a) -> Fix f -> a
cata f = a where a = f . fmap a . getFix
-- | Anamorphism or the unfold
--
-- Unfold a seed into a recursive structure
ana :: Functor f => (a -> f a) -> a -> Fix f
ana f = a where a = Fix . fmap a . f
-- | Combined fold and unfold
hylo :: (Functor f) => (f a -> a) -> (b -> f b) -> b -> a
hylo f u = a where a = f . fmap a . u

72
src/Data/Query.hs Normal file
View File

@ -0,0 +1,72 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
module Data.Query
(
-- * AST
Field(..)
-- * Combinators
, startsWith
, endsWith
, regex
, (.&&.)
-- * Evaluating queries
, evaluate
, predicate
)
where
import Data.Buuka
(BuukaEntry, title, url, _URL)
import Control.Lens
import Text.Regex.TDFA
((=~))
import Data.Functor.Foldable
(Fix(..), cata)
import Data.Text
(Text)
import qualified Data.Text as T
data Field a where
Url :: Field Text
Title :: Field Text
data QueryF f where
StartsWith :: Field Text -> Text -> QueryF f
EndsWith :: Field Text -> Text -> QueryF f
Regex :: Field Text -> Text -> QueryF f
And :: f -> f -> QueryF f
deriving instance Functor QueryF
type Query = Fix QueryF
startsWith :: Field Text -> Text -> Query
startsWith field x = Fix (StartsWith field x)
endsWith :: Field Text -> Text -> Query
endsWith field x = Fix (EndsWith field x)
regex :: Field Text -> Text -> Query
regex field x = Fix (Regex field x)
(.&&.) :: Query -> Query -> Query
a .&&. b = Fix (And a b)
evaluate :: QueryF (BuukaEntry -> Bool) -> (BuukaEntry -> Bool)
evaluate = \case
StartsWith Url x -> \e -> x `T.isPrefixOf` (e ^. url . _URL)
EndsWith Url x -> \e -> x `T.isSuffixOf` (e ^. url . _URL)
StartsWith Title x -> \e -> maybe False (x `T.isPrefixOf`) $ e ^. title
EndsWith Title x -> \e -> maybe False (x `T.isSuffixOf`) $ e ^. title
Regex Url x -> \e -> (e ^. url . _URL) =~ x
Regex Title x -> \e -> maybe False (=~ x) $ e ^. title
And a b -> \e -> a e && b e
predicate :: Query -> BuukaEntry -> Bool
predicate = cata evaluate

View File

@ -1,6 +1,16 @@
module Operations module Operations
( module Operations.Insert ) ( module Operations.Insert
, module Operations.List
, module Operations.Query
, module Operations.Import.Firefox
)
where where
import Operations.Insert import Operations.Insert
(insert) (insert)
import Operations.List
(list)
import Operations.Query
(query)
import Operations.Import.Firefox
(importFirefox)

51
src/Operations/Format.hs Normal file
View File

@ -0,0 +1,51 @@
{-# LANGUAGE LambdaCase #-}
{-|
Module : Operations.Format
Description : Format the list of bookmarks
Copyright : (c) Mats Rauhala, 2020
License : BSD-3-Clause
Maintainer : mats.rauhala@iki.fi
Stability : experimental
Portability : POSIX
Format the list of bookmarks. It uses the "hashids" module to create a unique
hash for each entry. Some extra (user) security is given by using the hash of
the full entries as the initial context for hashids. If the state has been
modified between operations, the ids change.
-}
module Operations.Format where
import Data.Buuka
(Buuka, BuukaEntry(..), URL(..))
import qualified Data.Buuka as B
import Data.Semigroup
(Max(..))
import Web.Hashids
import Control.Lens
import Data.Text.Strict.Lens
(utf8)
import Data.Text
(Text)
import qualified Data.Text as T
-- | Format the entries
formatEntries
:: Buuka -- ^ The full set of entries, for the context
-> [BuukaEntry] -- ^ The list of entries to be formatted
-> [Text]
formatEntries buuka xs =
let formatted = zipWith formatEntry [1..] xs
indexWidth = getMax . foldMap (Max . T.length . fst) $ formatted
in fmap (\(idx,x) -> idx <> T.replicate (indexWidth - T.length idx) " " <> ". " <> x) formatted
where
ctx = mkContext buuka
mkContext :: Buuka -> HashidsContext
mkContext = hashidsSimple . B.fingerprint
formatEntry :: Int -> BuukaEntry -> (Text, Text)
formatEntry n = \case
BuukaEntry{_title=Just t} -> (encode ctx n ^. utf8, t)
BuukaEntry{_url=URL u} -> (encode ctx n ^. utf8, u)

View File

@ -0,0 +1,132 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-|
Module : Operations.Import.Firefox
Description : Imports from firefox
Copyright : (c) Mats Rauhala, 2020
License : BSD-3-Clause
Maintainer : mats.rauhala@iki.fi
Stability : experimental
Portability : POSIX
Imports from firefox. Firefox needs to be closed when doing the import
-}
module Operations.Import.Firefox
( importFirefox )
where
import Data.Monoid
(Endo(..))
import qualified Data.Foldable as F
import qualified Data.Set as S
import Control.Monad.State
(modify)
import Data.Buuka
(Buuka)
import qualified Data.Buuka as B
import Conduit
import qualified Data.Conduit.Combinators as C
import Data.Text
(Text)
import System.FilePath
(takeFileName, (</>))
import Control.Exception
(Exception)
import System.Environment
(lookupEnv)
import GHC.Stack
import Control.Lens
( Lens'
, foldMapOf
, folded
, has
, ix
, lens
, makeLenses
, to
, (%~)
, (&)
, (<>~)
, (^.)
)
import qualified Database.SQLite.Simple as SQL
import Data.Traversable
(for)
import Control.Monad.Buuka
-- select p.title, p.url from moz_bookmarks b join moz_places p on b.fk = p.id
--
-- select keyword from moz_keywords where place_id = ?
newtype ImportException
= HomeNotFound CallStack
deriving stock (Show)
deriving anyclass (Exception)
data Firefox
= Firefox { _url :: Text
, _title :: Text
, _keywords :: [Text]
}
deriving stock (Show, Eq)
url :: Lens' Firefox Text
url = lens _url (\f u -> f{_url = u})
stores
:: MonadResource m
=> MonadThrow m
=> MonadIO m
=> HasCallStack
=> ConduitT i FilePath m ()
stores = liftIO (lookupEnv "HOME") >>= maybe (throwM (HomeNotFound callStack)) listStores
where
listStores home =
sourceDirectoryDeep False (home </> ".mozilla/firefox")
.| C.filter (\p -> takeFileName p == "places.sqlite")
bookmarks :: MonadIO m => FilePath -> m [Firefox]
bookmarks path = liftIO $ SQL.withConnection path $ \conn -> do
elems <- SQL.query_ conn "select p.id, p.title, p.url from moz_bookmarks b join moz_places p on b.fk = p.id"
for elems $ \(_id, _title, _url) -> do
_keywords <- fmap SQL.fromOnly <$> SQL.query conn "select keyword from moz_keywords where place_id = ?" (SQL.Only @Int _id)
pure Firefox{..}
data Update
= Update { _buuka :: !Buuka
, _seen :: !(S.Set Text)
}
deriving stock (Show)
makeLenses ''Update
importFirefox :: BuukaM ()
importFirefox = do
-- Collect all the imported bookmarks
fs <- (`appEndo` []) <$> runResourceT (runConduit $ stores .| C.mapM bookmarks .| C.foldMap (\f -> Endo (++ f)))
-- Insert to the buuka store iff, the urls don't already exist in the store
-- The fold keeps track of a set of already seen entries. Every iteration
-- adds the current url to the known set of urls. Only if the url doesn't
-- exist in the set, will it be inserted to the store
buukaU $ modify $ \oldState -> F.foldl' update (initialState oldState) fs ^. buuka
where
toEntry Firefox{..} = B.BuukaEntry{ B._url = B.URL _url, B._title = Just _title }
update acc f = acc
& seen <>~ (f ^. url . to S.singleton)
& if has (seen . ix (f ^. url)) acc then id else buuka %~ (B.insert (toEntry f))
initialState oldState = Update oldState (initialUrls oldState)
initialUrls = foldMapOf (B._Buuka . folded . B.url . B._URL) S.singleton

View File

@ -7,7 +7,10 @@ import Control.Monad.State
import qualified Data.Buuka as B import qualified Data.Buuka as B
insert :: String -> Maybe String -> BuukaM () import Data.Text
(Text)
insert :: Text -> Maybe Text -> BuukaM ()
insert url title = buukaU (modify (B.insert entry)) insert url title = buukaU (modify (B.insert entry))
where where
entry = B.BuukaEntry{ B.url = B.URL url, B.title = title } entry = B.BuukaEntry{ B._url = B.URL url, B._title = title }

27
src/Operations/List.hs Normal file
View File

@ -0,0 +1,27 @@
{-# LANGUAGE LambdaCase #-}
module Operations.List where
import Control.Monad.Buuka
import Control.Monad.Reader
(asks, liftIO)
import Data.Foldable
(traverse_)
import Data.Buuka
(Buuka)
import qualified Data.Buuka as B
import Operations.Format
import Data.Text
(Text)
import qualified Data.Text.IO as T
list :: BuukaM ()
list =
buukaQ (asks go) >>= traverse_ (liftIO . T.putStrLn)
where
go :: Buuka -> [Text]
go b = formatEntries b (B.elements b)

27
src/Operations/Query.hs Normal file
View File

@ -0,0 +1,27 @@
module Operations.Query where
import Data.Query
import Control.Monad.Buuka
import Control.Monad.Reader
import Data.Foldable
(traverse_)
import Data.Buuka
(Buuka)
import qualified Data.Buuka as B
import Operations.Format
import Data.Text
(Text)
import qualified Data.Text.IO as T
query :: Field Text -> Text -> BuukaM ()
query field q =
buukaQ (asks go) >>= traverse_ (liftIO . T.putStrLn)
where
go :: Buuka -> [Text]
go b = formatEntries b (filter (predicate (regex field q)) . B.elements $ b)

View File

@ -3,12 +3,16 @@ module Main (main) where
import Test.Tasty import Test.Tasty
import qualified Test.Data.Buuka as Data.Buuka import qualified Test.Data.Buuka as Data.Buuka
import qualified Test.Data.Query as Data.Query
import qualified Test.Data.Functor.Foldable as Data.Functor.Foldable
import qualified Test.Database.Migrations as Database.Migrations import qualified Test.Database.Migrations as Database.Migrations
tests :: TestTree tests :: TestTree
tests = testGroup "buuka" tests = testGroup "buuka"
[ Database.Migrations.tests [ Database.Migrations.tests
, Data.Buuka.tests , Data.Buuka.tests
, Data.Functor.Foldable.tests
, Data.Query.tests
] ]
main :: IO () main :: IO ()

View File

@ -1,3 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
module Test.Data.Buuka where module Test.Data.Buuka where
import Hedgehog import Hedgehog
@ -8,26 +9,26 @@ import Test.Tasty.Hedgehog
import qualified Data.Aeson as A import qualified Data.Aeson as A
import Data.List
(intercalate)
import qualified Data.Foldable as F import qualified Data.Foldable as F
import qualified Data.Text as T
import Data.Buuka import Data.Buuka
genUrl :: Gen URL genUrl :: Gen URL
genUrl = URL . concat <$> sequence go genUrl = URL . T.concat <$> sequence go
where where
go = [ Gen.element protocols, Gen.element domains, Gen.element tlds, pure "/", genPath ] go = [ Gen.element protocols, Gen.element domains, Gen.element tlds, pure "/", genPath ]
protocols = ["http://", "https://"] protocols = ["http://", "https://"]
domains = ["example", "foo", "bar"] domains = ["example", "foo", "bar"]
tlds = ["com", "fi", "org", "net", "info"] tlds = ["com", "fi", "org", "net", "info"]
genPath = intercalate "/" <$> Gen.list (Range.linear 0 10) (Gen.element paths) genPath = T.intercalate "/" <$> Gen.list (Range.linear 0 10) (Gen.element paths)
paths = ["foo", "bar", "asd", "xyzzy"] paths = ["foo", "bar", "asd", "xyzzy"]
genBuukaEntry :: Gen BuukaEntry genBuukaEntry :: Gen BuukaEntry
genBuukaEntry = BuukaEntry <$> genUrl <*> genTitle genBuukaEntry = BuukaEntry <$> genUrl <*> genTitle
where where
genTitle = Gen.maybe (Gen.string (Range.linear 0 10) Gen.unicode) genTitle = Gen.maybe (Gen.text (Range.linear 0 10) Gen.unicode)
genBuuka :: Gen Buuka genBuuka :: Gen Buuka
genBuuka = F.foldl' (flip insert) mempty <$> Gen.list (Range.linear 0 10) genBuukaEntry genBuuka = F.foldl' (flip insert) mempty <$> Gen.list (Range.linear 0 10) genBuukaEntry

View File

@ -0,0 +1,68 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TemplateHaskell #-}
module Test.Data.Functor.Foldable where
import Hedgehog
import qualified Hedgehog.Gen as Gen
import qualified Hedgehog.Range as Range
import Test.Tasty
import Test.Tasty.Hedgehog
import Data.Eq.Deriving
(deriveEq1)
import Text.Show.Deriving
(deriveShow1)
import Data.Functor.Foldable
data AST f
= Addition f f
| Value Int
deriving stock (Functor, Eq, Show)
deriveShow1 ''AST
deriveEq1 ''AST
evaluate :: AST Int -> Int
evaluate = \case
Addition a b -> a + b
Value x -> x
render :: AST String -> String
render = \case
Addition a b -> a <> " + " <> b
Value x -> show x
parse :: [String] -> AST [String]
parse = \case
a : "+" : b : xs -> Addition (a : xs) [b]
[a] -> Value (read a)
_ -> Value 0
genAST :: Gen (Fix AST)
genAST = Gen.recursive Gen.choice
[ Fix . Value <$> Gen.integral (Range.linear 0 100) ]
[ Gen.subterm2 genAST genAST (\a b -> Fix (Addition a b))
]
prop_parse_render_tripping :: Property
prop_parse_render_tripping = property $ do
x <- forAll genAST
let rendered = cata render x
parsed = ana parse . words $ rendered
annotateShow rendered
annotateShow parsed
annotateShow $ cata evaluate x
cata evaluate parsed === cata evaluate x
prop_parse_render_hylo :: Property
prop_parse_render_hylo = property $ do
x <- forAll genAST
let rendered = cata render x
hylo evaluate parse (words rendered) === cata evaluate x
tests :: TestTree
tests = testGroup "Data.Functor.Foldable"
[ testProperty "cata and ana do reverse" $ prop_parse_render_tripping
, testProperty "hylo do reverse" $ prop_parse_render_hylo
]

39
test/Test/Data/Query.hs Normal file
View File

@ -0,0 +1,39 @@
module Test.Data.Query where
import Test.Tasty
import Test.Tasty.HUnit
import Data.Buuka
(BuukaEntry(..), URL(..))
import Data.Functor.Foldable
(cata)
import Data.Query
test_startswith :: Assertion
test_startswith = do
let entry = BuukaEntry (URL "http://example.com") (Just "foo")
cata evaluate (startsWith Url "http://") entry @?= True
cata evaluate (startsWith Url "https://") entry @?= False
cata evaluate (startsWith Title "foo") entry @?= True
cata evaluate (startsWith Title "bar") entry @?= False
test_endswith :: Assertion
test_endswith = do
let entry = BuukaEntry (URL "http://example.com") (Just "foo")
cata evaluate (endsWith Url "com") entry @?= True
cata evaluate (endsWith Url "fi") entry @?= False
cata evaluate (endsWith Title "foo") entry @?= True
cata evaluate (endsWith Title "bar") entry @?= False
test_and :: Assertion
test_and = do
let entry = BuukaEntry (URL "http://example.com") (Just "foo")
cata evaluate (startsWith Url "http://" .&&. endsWith Url ".com") entry @?= True
cata evaluate (startsWith Url "http://" .&&. endsWith Url ".fi") entry @?= False
tests :: TestTree
tests = testGroup "Data.Query"
[ testCase "Queries startsWith" test_startswith
, testCase "Queries endsWith" test_endswith
, testCase "Queries and" test_and
]