Skip to content

Commit

Permalink
fixed vCalendar generation bug and deleted useless dependency
Browse files Browse the repository at this point in the history
  • Loading branch information
gaa-cifasis committed Jul 5, 2016
1 parent 547d52b commit c0e1bb7
Show file tree
Hide file tree
Showing 4 changed files with 26 additions and 8 deletions.
2 changes: 1 addition & 1 deletion QuickFuzz.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,7 @@ executable QuickFuzz
build-depends: zlib, tar, zip-archive, base16-bytestring

if flag(docs)
build-depends: pandoc-types, pandoc, data-default, hps, hcg-minus, iCalendar, quickcheck-instances
build-depends: pandoc-types, pandoc, data-default, hps, hcg-minus, iCalendar

if flag(pki)
build-depends: certificate, asn1-data, time
Expand Down
7 changes: 4 additions & 3 deletions src/ICal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,17 +4,18 @@
module ICal where

import Test.QuickCheck
import Test.QuickCheck.Instances

import DeriveArbitrary
import Text.ICalendar.Types
import Text.ICalendar.Printer
import Data.Char (ord)

--import Time
import qualified Data.ByteString.Lazy.Char8 as LC8

import qualified Data.ByteString.Lazy.Builder as Bu

import Time
import Strings

$(devArbitrary ''VCalendar)

utf8Len :: Char -> Int
Expand Down
17 changes: 17 additions & 0 deletions src/Strings.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,23 @@ module Strings where
import Test.QuickCheck
import Data.Char (chr)

import qualified Data.Text as TS
import qualified Data.Text.Lazy as TL

-- Text
instance Arbitrary TS.Text where
arbitrary = TS.pack <$> arbitrary
shrink xs = TS.pack <$> shrink (TS.unpack xs)

instance Arbitrary TL.Text where
arbitrary = TL.pack <$> arbitrary
shrink xs = TL.pack <$> shrink (TL.unpack xs)

instance CoArbitrary TS.Text where
coarbitrary = coarbitrary . TS.unpack

instance CoArbitrary TL.Text where
coarbitrary = coarbitrary . TL.unpack

genName :: Gen String
genName = listOf1 validChars :: Gen String
Expand Down
8 changes: 4 additions & 4 deletions src/Svg.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,10 +44,10 @@ import Images

data MSvgFile = MSvgFile Document deriving Show

instance Arbitrary DT.Text where
arbitrary = do
xs <- mgenName
oneof $ Prelude.map (return . T.pack) [xs]
--instance Arbitrary DT.Text where
-- arbitrary = do
-- xs <- mgenName
-- oneof $ Prelude.map (return . T.pack) [xs]

instance Arbitrary String where
arbitrary = mgenName
Expand Down

0 comments on commit c0e1bb7

Please sign in to comment.