{-# LANGUAGE GADTs #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

{-# OPTIONS_GHC -Wall -Werror #-}

module Siphon.Types
  ( Siphon(..)
  , Indexed(..)
  , SiphonError(..)
  , RowError(..)
  , CellError(..)
  ) where

import Data.Vector (Vector)
import Control.Exception (Exception)
import Data.Text (Text)

data CellError = CellError
  { CellError -> Int
cellErrorColumn :: !Int
  , CellError -> Text
cellErrorContent :: !Text
  } deriving (Int -> CellError -> ShowS
[CellError] -> ShowS
CellError -> String
(Int -> CellError -> ShowS)
-> (CellError -> String)
-> ([CellError] -> ShowS)
-> Show CellError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CellError] -> ShowS
$cshowList :: [CellError] -> ShowS
show :: CellError -> String
$cshow :: CellError -> String
showsPrec :: Int -> CellError -> ShowS
$cshowsPrec :: Int -> CellError -> ShowS
Show,ReadPrec [CellError]
ReadPrec CellError
Int -> ReadS CellError
ReadS [CellError]
(Int -> ReadS CellError)
-> ReadS [CellError]
-> ReadPrec CellError
-> ReadPrec [CellError]
-> Read CellError
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CellError]
$creadListPrec :: ReadPrec [CellError]
readPrec :: ReadPrec CellError
$creadPrec :: ReadPrec CellError
readList :: ReadS [CellError]
$creadList :: ReadS [CellError]
readsPrec :: Int -> ReadS CellError
$creadsPrec :: Int -> ReadS CellError
Read,CellError -> CellError -> Bool
(CellError -> CellError -> Bool)
-> (CellError -> CellError -> Bool) -> Eq CellError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CellError -> CellError -> Bool
$c/= :: CellError -> CellError -> Bool
== :: CellError -> CellError -> Bool
$c== :: CellError -> CellError -> Bool
Eq)

newtype Indexed a = Indexed
  { Indexed a -> Int
indexedIndex :: Int
  } deriving (Indexed a -> Indexed a -> Bool
(Indexed a -> Indexed a -> Bool)
-> (Indexed a -> Indexed a -> Bool) -> Eq (Indexed a)
forall a. Indexed a -> Indexed a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Indexed a -> Indexed a -> Bool
$c/= :: forall a. Indexed a -> Indexed a -> Bool
== :: Indexed a -> Indexed a -> Bool
$c== :: forall a. Indexed a -> Indexed a -> Bool
Eq,Eq (Indexed a)
Eq (Indexed a)
-> (Indexed a -> Indexed a -> Ordering)
-> (Indexed a -> Indexed a -> Bool)
-> (Indexed a -> Indexed a -> Bool)
-> (Indexed a -> Indexed a -> Bool)
-> (Indexed a -> Indexed a -> Bool)
-> (Indexed a -> Indexed a -> Indexed a)
-> (Indexed a -> Indexed a -> Indexed a)
-> Ord (Indexed a)
Indexed a -> Indexed a -> Bool
Indexed a -> Indexed a -> Ordering
Indexed a -> Indexed a -> Indexed a
forall a. Eq (Indexed a)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Indexed a -> Indexed a -> Bool
forall a. Indexed a -> Indexed a -> Ordering
forall a. Indexed a -> Indexed a -> Indexed a
min :: Indexed a -> Indexed a -> Indexed a
$cmin :: forall a. Indexed a -> Indexed a -> Indexed a
max :: Indexed a -> Indexed a -> Indexed a
$cmax :: forall a. Indexed a -> Indexed a -> Indexed a
>= :: Indexed a -> Indexed a -> Bool
$c>= :: forall a. Indexed a -> Indexed a -> Bool
> :: Indexed a -> Indexed a -> Bool
$c> :: forall a. Indexed a -> Indexed a -> Bool
<= :: Indexed a -> Indexed a -> Bool
$c<= :: forall a. Indexed a -> Indexed a -> Bool
< :: Indexed a -> Indexed a -> Bool
$c< :: forall a. Indexed a -> Indexed a -> Bool
compare :: Indexed a -> Indexed a -> Ordering
$ccompare :: forall a. Indexed a -> Indexed a -> Ordering
$cp1Ord :: forall a. Eq (Indexed a)
Ord,(a -> b) -> Indexed a -> Indexed b
(forall a b. (a -> b) -> Indexed a -> Indexed b)
-> (forall a b. a -> Indexed b -> Indexed a) -> Functor Indexed
forall a b. a -> Indexed b -> Indexed a
forall a b. (a -> b) -> Indexed a -> Indexed b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Indexed b -> Indexed a
$c<$ :: forall a b. a -> Indexed b -> Indexed a
fmap :: (a -> b) -> Indexed a -> Indexed b
$cfmap :: forall a b. (a -> b) -> Indexed a -> Indexed b
Functor,Int -> Indexed a -> ShowS
[Indexed a] -> ShowS
Indexed a -> String
(Int -> Indexed a -> ShowS)
-> (Indexed a -> String)
-> ([Indexed a] -> ShowS)
-> Show (Indexed a)
forall a. Int -> Indexed a -> ShowS
forall a. [Indexed a] -> ShowS
forall a. Indexed a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Indexed a] -> ShowS
$cshowList :: forall a. [Indexed a] -> ShowS
show :: Indexed a -> String
$cshow :: forall a. Indexed a -> String
showsPrec :: Int -> Indexed a -> ShowS
$cshowsPrec :: forall a. Int -> Indexed a -> ShowS
Show,ReadPrec [Indexed a]
ReadPrec (Indexed a)
Int -> ReadS (Indexed a)
ReadS [Indexed a]
(Int -> ReadS (Indexed a))
-> ReadS [Indexed a]
-> ReadPrec (Indexed a)
-> ReadPrec [Indexed a]
-> Read (Indexed a)
forall a. ReadPrec [Indexed a]
forall a. ReadPrec (Indexed a)
forall a. Int -> ReadS (Indexed a)
forall a. ReadS [Indexed a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Indexed a]
$creadListPrec :: forall a. ReadPrec [Indexed a]
readPrec :: ReadPrec (Indexed a)
$creadPrec :: forall a. ReadPrec (Indexed a)
readList :: ReadS [Indexed a]
$creadList :: forall a. ReadS [Indexed a]
readsPrec :: Int -> ReadS (Indexed a)
$creadsPrec :: forall a. Int -> ReadS (Indexed a)
Read)

data SiphonError = SiphonError
  { SiphonError -> Int
siphonErrorRow :: !Int
  , SiphonError -> RowError
siphonErrorCause :: !RowError
  } deriving (Int -> SiphonError -> ShowS
[SiphonError] -> ShowS
SiphonError -> String
(Int -> SiphonError -> ShowS)
-> (SiphonError -> String)
-> ([SiphonError] -> ShowS)
-> Show SiphonError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SiphonError] -> ShowS
$cshowList :: [SiphonError] -> ShowS
show :: SiphonError -> String
$cshow :: SiphonError -> String
showsPrec :: Int -> SiphonError -> ShowS
$cshowsPrec :: Int -> SiphonError -> ShowS
Show,ReadPrec [SiphonError]
ReadPrec SiphonError
Int -> ReadS SiphonError
ReadS [SiphonError]
(Int -> ReadS SiphonError)
-> ReadS [SiphonError]
-> ReadPrec SiphonError
-> ReadPrec [SiphonError]
-> Read SiphonError
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SiphonError]
$creadListPrec :: ReadPrec [SiphonError]
readPrec :: ReadPrec SiphonError
$creadPrec :: ReadPrec SiphonError
readList :: ReadS [SiphonError]
$creadList :: ReadS [SiphonError]
readsPrec :: Int -> ReadS SiphonError
$creadsPrec :: Int -> ReadS SiphonError
Read,SiphonError -> SiphonError -> Bool
(SiphonError -> SiphonError -> Bool)
-> (SiphonError -> SiphonError -> Bool) -> Eq SiphonError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SiphonError -> SiphonError -> Bool
$c/= :: SiphonError -> SiphonError -> Bool
== :: SiphonError -> SiphonError -> Bool
$c== :: SiphonError -> SiphonError -> Bool
Eq)

instance Exception SiphonError

data RowError
  = RowErrorParse
    -- ^ Error occurred parsing the document into cells
  | RowErrorDecode !(Vector CellError)
    -- ^ Error decoding the content
  | RowErrorSize !Int !Int
    -- ^ Wrong number of cells in the row
  | RowErrorHeaders !(Vector (Vector CellError)) !(Vector Text) !(Vector Int)
    -- ^ Three parts:
    --   (a) Multiple header cells matched the same expected cell, 
    --   (b) Headers that were missing, 
    --   (c) Missing headers that were lambdas. They cannot be
    --   shown so instead their positions in the 'Siphon' are given.
  | RowErrorHeaderSize !Int !Int
    -- ^ Not enough cells in header, expected, actual
  | RowErrorMalformed !Int
    -- ^ Error decoding unicode content, column number
  deriving (Int -> RowError -> ShowS
[RowError] -> ShowS
RowError -> String
(Int -> RowError -> ShowS)
-> (RowError -> String) -> ([RowError] -> ShowS) -> Show RowError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RowError] -> ShowS
$cshowList :: [RowError] -> ShowS
show :: RowError -> String
$cshow :: RowError -> String
showsPrec :: Int -> RowError -> ShowS
$cshowsPrec :: Int -> RowError -> ShowS
Show,ReadPrec [RowError]
ReadPrec RowError
Int -> ReadS RowError
ReadS [RowError]
(Int -> ReadS RowError)
-> ReadS [RowError]
-> ReadPrec RowError
-> ReadPrec [RowError]
-> Read RowError
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RowError]
$creadListPrec :: ReadPrec [RowError]
readPrec :: ReadPrec RowError
$creadPrec :: ReadPrec RowError
readList :: ReadS [RowError]
$creadList :: ReadS [RowError]
readsPrec :: Int -> ReadS RowError
$creadsPrec :: Int -> ReadS RowError
Read,RowError -> RowError -> Bool
(RowError -> RowError -> Bool)
-> (RowError -> RowError -> Bool) -> Eq RowError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RowError -> RowError -> Bool
$c/= :: RowError -> RowError -> Bool
== :: RowError -> RowError -> Bool
$c== :: RowError -> RowError -> Bool
Eq)

-- | This just actually a specialization of the free applicative.
--   Check out @Control.Applicative.Free@ in the @free@ library to
--   learn more about this. The meanings of the fields are documented
--   slightly more in the source code. Unfortunately, haddock does not
--   play nicely with GADTs.
data Siphon f c a where
  SiphonPure ::
       !a -- function
    -> Siphon f c a
  SiphonAp ::
       !(f c) -- header
    -> !(c -> Maybe a) -- decoding function
    -> !(Siphon f c (a -> b)) -- next decoding
    -> Siphon f c b

instance Functor (Siphon f c) where
  fmap :: (a -> b) -> Siphon f c a -> Siphon f c b
fmap a -> b
f (SiphonPure a
a) = b -> Siphon f c b
forall a (f :: * -> *) c. a -> Siphon f c a
SiphonPure (a -> b
f a
a)
  fmap a -> b
f (SiphonAp f c
h c -> Maybe a
c Siphon f c (a -> a)
apNext) = f c -> (c -> Maybe a) -> Siphon f c (a -> b) -> Siphon f c b
forall (f :: * -> *) c a b.
f c -> (c -> Maybe a) -> Siphon f c (a -> b) -> Siphon f c b
SiphonAp f c
h c -> Maybe a
c ((a -> b
f (a -> b) -> (a -> a) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((a -> a) -> a -> b) -> Siphon f c (a -> a) -> Siphon f c (a -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Siphon f c (a -> a)
apNext)

instance Applicative (Siphon f c) where
  pure :: a -> Siphon f c a
pure = a -> Siphon f c a
forall a (f :: * -> *) c. a -> Siphon f c a
SiphonPure
  SiphonPure a -> b
f <*> :: Siphon f c (a -> b) -> Siphon f c a -> Siphon f c b
<*> Siphon f c a
y = (a -> b) -> Siphon f c a -> Siphon f c b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f Siphon f c a
y
  SiphonAp f c
h c -> Maybe a
c Siphon f c (a -> a -> b)
y <*> Siphon f c a
z = f c -> (c -> Maybe a) -> Siphon f c (a -> b) -> Siphon f c b
forall (f :: * -> *) c a b.
f c -> (c -> Maybe a) -> Siphon f c (a -> b) -> Siphon f c b
SiphonAp f c
h c -> Maybe a
c ((a -> a -> b) -> a -> a -> b
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((a -> a -> b) -> a -> a -> b)
-> Siphon f c (a -> a -> b) -> Siphon f c (a -> a -> b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Siphon f c (a -> a -> b)
y Siphon f c (a -> a -> b) -> Siphon f c a -> Siphon f c (a -> b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Siphon f c a
z)