Skip to content

Commit

Permalink
Merge pull request #140 from qrilka/depend-on-microlens-in-tests
Browse files Browse the repository at this point in the history
Depend on microlens in tests when microlens flag is set
  • Loading branch information
qrilka authored Jun 19, 2021
2 parents 831d5b0 + 61b72cb commit 412296f
Show file tree
Hide file tree
Showing 4 changed files with 56 additions and 27 deletions.
5 changes: 5 additions & 0 deletions test/DrawingTests.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module DrawingTests
Expand All @@ -6,7 +7,11 @@ module DrawingTests
, testLineChartSpace
) where

#ifdef USE_MICROLENS
import Lens.Micro
#else
import Control.Lens
#endif
import Data.ByteString.Lazy (ByteString)
import Test.Tasty (testGroup, TestTree)
import Test.Tasty.HUnit (testCase)
Expand Down
66 changes: 40 additions & 26 deletions test/Main.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE RecordWildCards #-}
Expand All @@ -6,7 +7,12 @@ module Main
( main
) where

#ifdef USE_MICROLENS
import Lens.Micro
import Lens.Micro.Mtl
#else
import Control.Lens
#endif
import Control.Monad.State.Lazy
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as LB
Expand Down Expand Up @@ -267,8 +273,8 @@ withDoubleUnderline = withUnderline FontUnderlineDouble

withUnderline :: FontUnderline -> SharedStringTable -> SharedStringTable
withUnderline u (SharedStringTable [text, XlsxRichText [rich1, RichTextRun (Just props) val]]) =
let newprops = props & runPropertiesUnderline .~ Just u
in SharedStringTable [text, XlsxRichText [rich1, RichTextRun (Just newprops) val]]
let newprops = props & runPropertiesUnderline .~ Just u
in SharedStringTable [text, XlsxRichText [rich1, RichTextRun (Just newprops) val]]

testSharedStringTable :: SharedStringTable
testSharedStringTable = SharedStringTable $ V.fromList items
Expand Down Expand Up @@ -311,34 +317,42 @@ testCommentTable = CommentTable $ M.fromList
, _richTextRunText = "Why such high expense?"}]

testStrings :: ByteString
testStrings = "<?xml version=\"1.0\" encoding=\"UTF-8\" standalone=\"yes\"?>\
\<sst xmlns=\"http://schemas.openxmlformats.org/spreadsheetml/2006/main\" count=\"2\" uniqueCount=\"2\">\
\<si><t>plain text</t></si>\
\<si><r><t>Just </t></r><r><rPr><b /><i />\
\<sz val=\"10\"/><rFont val=\"Arial\"/><family val=\"2\"/></rPr><t>example</t></r></si>\
\</sst>"
testStrings = [r|
<?xml version="1.0" encoding="UTF-8" standalone="yes"?>
<sst xmlns="http://schemas.openxmlformats.org/spreadsheetml/2006/main" count="2" uniqueCount="2">
<si><t>plain text</t></si>
<si><r><t>Just </t></r><r><rPr><b /><i />
<sz val="10"/><rFont val="Arial"/><family val="2"/></rPr><t>example</t></r></si>
</sst>
|]

testStringsWithSingleUnderline :: ByteString
testStringsWithSingleUnderline = "<?xml version=\"1.0\" encoding=\"UTF-8\" standalone=\"yes\"?>\
\<sst xmlns=\"http://schemas.openxmlformats.org/spreadsheetml/2006/main\" count=\"2\" uniqueCount=\"2\">\
\<si><t>plain text</t></si>\
\<si><r><t>Just </t></r><r><rPr><b /><i /><u />\
\<sz val=\"10\"/><rFont val=\"Arial\"/><family val=\"2\"/></rPr><t>example</t></r></si>\
\</sst>"
testStringsWithSingleUnderline = [r|
<?xml version="1.0" encoding="UTF-8" standalone="yes"?>
<sst xmlns="http://schemas.openxmlformats.org/spreadsheetml/2006/main" count="2" uniqueCount="2">
<si><t>plain text</t></si>
<si><r><t>Just </t></r><r><rPr><b /><i /><u />
<sz val="10"/><rFont val="Arial"/><family val="2"/></rPr><t>example</t></r></si>
</sst>
|]

testStringsWithDoubleUnderline :: ByteString
testStringsWithDoubleUnderline = "<?xml version=\"1.0\" encoding=\"UTF-8\" standalone=\"yes\"?>\
\<sst xmlns=\"http://schemas.openxmlformats.org/spreadsheetml/2006/main\" count=\"2\" uniqueCount=\"2\">\
\<si><t>plain text</t></si>\
\<si><r><t>Just </t></r><r><rPr><b /><i /><u val=\"double\"/>\
\<sz val=\"10\"/><rFont val=\"Arial\"/><family val=\"2\"/></rPr><t>example</t></r></si>\
\</sst>"
testStringsWithDoubleUnderline = [r|
<?xml version="1.0" encoding="UTF-8" standalone="yes"?>
<sst xmlns="http://schemas.openxmlformats.org/spreadsheetml/2006/main" count="2" uniqueCount="2">
<si><t>plain text</t></si>
<si><r><t>Just </t></r><r><rPr><b /><i /><u val="double"/>
<sz val="10"/><rFont val="Arial"/><family val="2"/></rPr><t>example</t></r></si>
</sst>
|]

testStringsWithEmpty :: ByteString
testStringsWithEmpty = "<?xml version=\"1.0\" encoding=\"UTF-8\" standalone=\"yes\"?>\
\<sst xmlns=\"http://schemas.openxmlformats.org/spreadsheetml/2006/main\" count=\"2\" uniqueCount=\"2\">\
\<si><t/></si>\
\</sst>"
testStringsWithEmpty = [r|
<?xml version="1.0" encoding="UTF-8" standalone="yes"?>
<sst xmlns="http://schemas.openxmlformats.org/spreadsheetml/2006/main" count="2" uniqueCount="2">
<si><t/></si>
</sst>
|]

testComments :: ByteString
testComments = [r|
Expand Down Expand Up @@ -495,13 +509,13 @@ testFormatWorkbookResult = def & xlSheets .~ sheets
cellXf2 = def
{ _cellXfApplyNumberFormat = Just True
, _cellXfNumFmtId = Just 164 }

testFormatWorkbook :: Xlsx
testFormatWorkbook = formatWorkbook sheets minimalStyleSheet
where
sheetNames = ["Sheet1", "Sheet2"]
testFormattedCellMap1 = M.fromList [((1,1), (def & formattedCell . cellValue ?~ CellText "text at A1 Sheet1"))]

testFormattedCellMap2 = M.fromList [((2,3), (def & formattedCell . cellValue ?~ CellDouble 1.23456
& formattedFormat . formatNumberFormat ?~ (UserNumberFormat "DD.MM.YYYY")))]
sheets = zip sheetNames [testFormattedCellMap1, testFormattedCellMap2]
Expand Down
5 changes: 5 additions & 0 deletions test/PivotTableTests.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module PivotTableTests
Expand All @@ -6,7 +7,11 @@ module PivotTableTests
, testPivotSrcCells
) where

#ifdef USE_MICROLENS
import Lens.Micro
#else
import Control.Lens
#endif
import Data.ByteString.Lazy (ByteString)
import qualified Data.Map as M
import Data.Maybe (mapMaybe)
Expand Down
7 changes: 6 additions & 1 deletion xlsx.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -137,7 +137,6 @@ test-suite data-test
, containers
, Diff >= 0.3.0
, groom
, lens >= 3.8 && < 5.1
, mtl
, raw-strings-qq
, smallcheck
Expand All @@ -149,6 +148,12 @@ test-suite data-test
, vector
, xlsx
, xml-conduit >= 1.1.0
if flag(microlens)
Build-depends: microlens >= 0.4 && < 0.5
, microlens-mtl
cpp-options: -DUSE_MICROLENS
else
Build-depends: lens >= 3.8 && < 5.1
Default-Language: Haskell2010

source-repository head
Expand Down

0 comments on commit 412296f

Please sign in to comment.