Skip to content

Commit

Permalink
chore: format the repo
Browse files Browse the repository at this point in the history
  • Loading branch information
flhorizon committed Sep 3, 2022
1 parent ef5a4d1 commit c175e17
Show file tree
Hide file tree
Showing 51 changed files with 841 additions and 843 deletions.
4 changes: 2 additions & 2 deletions src/Codec/Xlsx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ module Codec.Xlsx
( module X
) where

import Codec.Xlsx.Types as X
import Codec.Xlsx.Lens as X
import Codec.Xlsx.Parser as X
import Codec.Xlsx.Types as X
import Codec.Xlsx.Writer as X
import Codec.Xlsx.Lens as X
10 changes: 5 additions & 5 deletions src/Codec/Xlsx/Formatted.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
-- | Higher level interface for creating styled worksheets
{-# LANGUAGE CPP #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
module Codec.Xlsx.Formatted
( FormattedCell(..)
, Formatted(..)
Expand Down Expand Up @@ -37,17 +37,17 @@ module Codec.Xlsx.Formatted

#ifdef USE_MICROLENS
import Lens.Micro
import Lens.Micro.GHC ()
import Lens.Micro.Mtl
import Lens.Micro.TH
import Lens.Micro.GHC ()
#else
import Control.Lens
#endif
import Control.Monad.State hiding (forM_, mapM)
import Data.Default
import Data.Foldable (asum, forM_)
import Data.Function (on)
import Data.List (foldl', groupBy, sortBy, sortBy)
import Data.List (foldl', groupBy, sortBy)
import Data.Map (Map)
import qualified Data.Map as M
import Data.Ord (comparing)
Expand All @@ -56,7 +56,7 @@ import Data.Traversable (mapM)
import Data.Tuple (swap)
import GHC.Generics (Generic)
import Prelude hiding (mapM)
import Safe (headNote, fromJustNote)
import Safe (fromJustNote, headNote)

import Codec.Xlsx.Types

Expand Down
8 changes: 4 additions & 4 deletions src/Codec/Xlsx/Lens.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}

-- | lenses to access sheets, cells and values of 'Xlsx'
module Codec.Xlsx.Lens
Expand All @@ -21,8 +21,8 @@ module Codec.Xlsx.Lens
import Codec.Xlsx.Types
#ifdef USE_MICROLENS
import Lens.Micro
import Lens.Micro.Internal
import Lens.Micro.GHC ()
import Lens.Micro.Internal
#else
import Control.Lens
#endif
Expand Down
25 changes: 12 additions & 13 deletions src/Codec/Xlsx/Parser.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
Expand All @@ -26,7 +26,7 @@ import Control.Exception (Exception)
#ifdef USE_MICROLENS
import Lens.Micro
#else
import Control.Lens hiding ((<.>), element, views)
import Control.Lens hiding (element, views, (<.>))
#endif
import Control.Monad (join, void)
import Control.Monad.Except (catchError, throwError)
Expand Down Expand Up @@ -59,8 +59,7 @@ import Codec.Xlsx.Types.Internal
import Codec.Xlsx.Types.Internal.CfPair
import Codec.Xlsx.Types.Internal.CommentTable as CommentTable
import Codec.Xlsx.Types.Internal.ContentTypes as ContentTypes
import Codec.Xlsx.Types.Internal.CustomProperties
as CustomProperties
import Codec.Xlsx.Types.Internal.CustomProperties as CustomProperties
import Codec.Xlsx.Types.Internal.DvPair
import Codec.Xlsx.Types.Internal.FormulaData
import Codec.Xlsx.Types.Internal.Relationships as Relationships
Expand Down Expand Up @@ -116,9 +115,9 @@ toXlsxEitherBase parseSheet bs = do
CustomProperties customPropMap <- getCustomProperties ar
return $ Xlsx sheets (getStyles ar) names customPropMap dateBase

data WorksheetFile = WorksheetFile { wfName :: Text
data WorksheetFile = WorksheetFile { wfName :: Text
, wfState :: SheetState
, wfPath :: FilePath
, wfPath :: FilePath
}
deriving (Show, Generic)

Expand Down Expand Up @@ -246,7 +245,7 @@ extractSheetFast ar sst contentTypes caches wf = do
liftEither :: Either Text a -> Parser a
liftEither = left (\t -> InvalidFile filePath t)
justNonEmpty v@(Just (_:_)) = v
justNonEmpty _ = Nothing
justNonEmpty _ = Nothing
collectRows = foldr collectRow (M.empty, M.empty, M.empty)
collectRow ::
( Int
Expand Down Expand Up @@ -325,15 +324,15 @@ extractSheetFast ar sst contentTypes caches wf = do
vConverted =
case contentBs <$> vNode of
Nothing -> return Nothing
Just c -> Just <$> fromAttrBs c
Just c -> Just <$> fromAttrBs c
mFormulaData <- mapM fromXenoNode fNode
d <-
case t of
("s" :: ByteString) -> do
si <- vConverted
case sstItem sst =<< si of
Just xlTxt -> return $ Just (xlsxTextToCellValue xlTxt)
Nothing -> throwError "bad shared string index"
Nothing -> throwError "bad shared string index"
"inlineStr" -> mapM (fmap xlsxTextToCellValue . fromXenoNode) isNode
"str" -> fmap CellText <$> vConverted
"n" -> fmap CellDouble <$> vConverted
Expand Down Expand Up @@ -510,7 +509,7 @@ extractCellValue sst t cur
si <- vConverted "shared string"
case sstItem sst si of
Just xlTxt -> return $ xlsxTextToCellValue xlTxt
Nothing -> fail "bad shared string index"
Nothing -> fail "bad shared string index"
| t == "inlineStr" =
cur $/ element (n_ "is") >=> fmap xlsxTextToCellValue . fromCursor
| t == "str" = CellText <$> vConverted "string"
Expand All @@ -524,7 +523,7 @@ extractCellValue sst t cur
return (T.concat $ c $/ content)
case fromAttrVal vContent of
Right (val, _) -> return $ val
_ -> fail $ "bad " ++ typeStr ++ " cell value"
_ -> fail $ "bad " ++ typeStr ++ " cell value"

-- | Get xml cursor from the specified file inside the zip archive.
xmlCursorOptional :: Zip.Archive -> FilePath -> Parser (Maybe Cursor)
Expand Down
26 changes: 13 additions & 13 deletions src/Codec/Xlsx/Parser/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Codec.Xlsx.Parser.Internal
( ParseException(..)
, n_
Expand Down Expand Up @@ -90,7 +90,7 @@ maybeAttribute :: FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute name cursor =
case attribute name cursor of
[attr] -> Just <$> runReader fromAttrVal attr
_ -> [Nothing]
_ -> [Nothing]

fromElementValue :: FromAttrVal a => Name -> Cursor -> [a]
fromElementValue name cursor =
Expand All @@ -100,34 +100,34 @@ maybeElementValue :: FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeElementValue name cursor =
case cursor $/ element name of
[cursor'] -> maybeAttribute "val" cursor'
_ -> [Nothing]
_ -> [Nothing]

maybeElementValueDef :: FromAttrVal a => Name -> a -> Cursor -> [Maybe a]
maybeElementValueDef name defVal cursor =
case cursor $/ element name of
[cursor'] -> Just . fromMaybe defVal <$> maybeAttribute "val" cursor'
_ -> [Nothing]
_ -> [Nothing]

maybeBoolElementValue :: Name -> Cursor -> [Maybe Bool]
maybeBoolElementValue name cursor = maybeElementValueDef name True cursor

maybeFromElement :: FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement name cursor = case cursor $/ element name of
[cursor'] -> Just <$> fromCursor cursor'
_ -> [Nothing]
_ -> [Nothing]

attrValIs :: (Eq a, FromAttrVal a) => Name -> a -> Axis
attrValIs n v c =
case fromAttribute n c of
[x] | x == v -> [c]
_ -> []
_ -> []

contentOrEmpty :: Cursor -> [Text]
contentOrEmpty c =
case c $/ content of
[t] -> [t]
[] -> [""]
_ -> error "invalid item: more than one text node encountered"
[] -> [""]
_ -> error "invalid item: more than one text node encountered"

readSuccess :: a -> Either String (a, Text)
readSuccess x = Right (x, T.empty)
Expand All @@ -144,7 +144,7 @@ defaultReadFailure = Left "invalid text"
runReader :: T.Reader a -> Text -> [a]
runReader reader t = case reader t of
Right (r, leftover) | T.null leftover -> [r]
_ -> []
_ -> []

-- | Add sml namespace to name
n_ :: Text -> Name
Expand Down
30 changes: 15 additions & 15 deletions src/Codec/Xlsx/Parser/Internal/Fast.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
module Codec.Xlsx.Parser.Internal.Fast
( FromXenoNode(..)
, collectChildren
Expand Down Expand Up @@ -36,7 +36,7 @@ import Control.Arrow (second)
import Control.Exception (Exception, throw)
import Control.Monad (ap, forM, join, liftM)
import Data.Bifunctor (first)
import Data.Bits ((.|.), shiftL)
import Data.Bits (shiftL, (.|.))
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Unsafe as SU
Expand Down Expand Up @@ -84,7 +84,7 @@ toChildCollector :: Either Text a -> ChildCollector a
toChildCollector unlifted =
case unlifted of
Right a -> return a
Left e -> ChildCollector $ \_ -> Left e
Left e -> ChildCollector $ \_ -> Left e

collectChildren :: Node -> ChildCollector a -> Either Text a
collectChildren n c = snd <$> runChildCollector c (children n)
Expand All @@ -108,7 +108,7 @@ childList :: ByteString -> ChildCollector [Node]
childList nm = do
mNode <- maybeChild nm
case mNode of
Just n -> (n:) <$> childList nm
Just n -> (n:) <$> childList nm
Nothing -> return []

maybeFromChild :: (FromXenoNode a) => ByteString -> ChildCollector (Maybe a)
Expand All @@ -121,13 +121,13 @@ fromChild nm = do
n <- requireChild nm
case fromXenoNode n of
Right a -> return a
Left e -> ChildCollector $ \_ -> Left e
Left e -> ChildCollector $ \_ -> Left e

fromChildList :: (FromXenoNode a) => ByteString -> ChildCollector [a]
fromChildList nm = do
mA <- maybeFromChild nm
case mA of
Just a -> (a:) <$> fromChildList nm
Just a -> (a:) <$> fromChildList nm
Nothing -> return []

maybeParse :: ByteString -> (Node -> Either Text a) -> ChildCollector (Maybe a)
Expand Down Expand Up @@ -170,7 +170,7 @@ toAttrParser :: Either Text a -> AttrParser a
toAttrParser unlifted =
case unlifted of
Right a -> return a
Left e -> AttrParser $ \_ -> Left e
Left e -> AttrParser $ \_ -> Left e

maybeAttrBs :: ByteString -> AttrParser (Maybe ByteString)
maybeAttrBs attrName = AttrParser $ go id
Expand All @@ -186,7 +186,7 @@ requireAttrBs nm = do
mVal <- maybeAttrBs nm
case mVal of
Just val -> return val
Nothing -> attrError $ "attribute " <> T.pack (show nm) <> " is required"
Nothing -> attrError $ "attribute " <> T.pack (show nm) <> " is required"

unexpectedAttrBs :: Text -> ByteString -> Either Text a
unexpectedAttrBs typ val =
Expand All @@ -208,7 +208,7 @@ fromAttrDef nm defVal = fromMaybe defVal <$> maybeAttr nm
parseAttributes :: Node -> AttrParser a -> Either Text a
parseAttributes n attrParser =
case runAttrParser attrParser (attributes n) of
Left e -> Left e
Left e -> Left e
Right (_, a) -> return a

class FromAttrBs a where
Expand Down Expand Up @@ -353,8 +353,8 @@ contentBs :: Node -> ByteString
contentBs n = BS.concat . map toBs $ contents n
where
toBs (Element _) = BS.empty
toBs (Text bs) = bs
toBs (CData bs) = bs
toBs (Text bs) = bs
toBs (CData bs) = bs

contentX :: Node -> Either Text Text
contentX = replaceEntititesBs . contentBs
6 changes: 3 additions & 3 deletions src/Codec/Xlsx/Parser/Internal/Memoize.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeApplications #-}

-- | I rewrote: https://hackage.haskell.org/package/unliftio-0.2.20/docs/src/UnliftIO.Memoize.html#Memoized
-- for monad trans basecontrol
Expand All @@ -12,10 +12,10 @@ module Codec.Xlsx.Parser.Internal.Memoize
) where

import Control.Applicative as A
import Control.Exception
import Control.Monad (join)
import Control.Monad.IO.Class
import Data.IORef
import Control.Exception

-- | A \"run once\" value, with results saved. Extract the value with
-- 'runMemoized'. For single-threaded usage, you can use 'memoizeRef' to
Expand Down
8 changes: 4 additions & 4 deletions src/Codec/Xlsx/Parser/Internal/PivotTable.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RecordWildCards #-}
module Codec.Xlsx.Parser.Internal.PivotTable
( parsePivotTable
, parseCache
Expand Down Expand Up @@ -104,6 +104,6 @@ fillCacheFieldsFromRecords fields recs =
if null (cfItems field)
then field {cfItems = mapMaybe recToCellValue recVals}
else field
recToCellValue (CacheText t) = Just $ CellText t
recToCellValue (CacheText t) = Just $ CellText t
recToCellValue (CacheNumber n) = Just $ CellDouble n
recToCellValue (CacheIndex _) = Nothing
recToCellValue (CacheIndex _) = Nothing
Loading

0 comments on commit c175e17

Please sign in to comment.