Safe Haskell | None |
---|---|
Language | Haskell2010 |
Colonnade.Decoding
- contramapContent :: forall c1 c2 f a. Contravariant f => (c2 -> c1) -> Decolonnade f c1 a -> Decolonnade f c2 a
- headless :: (content -> Either String a) -> Decolonnade Headless content a
- headed :: content -> (content -> Either String a) -> Decolonnade Headed content a
- indexed :: Int -> (content -> Either String a) -> Decolonnade (Indexed Headless) content a
- maxIndex :: forall f c a. Decolonnade (Indexed f) c a -> Int
- uncheckedRunWithRow :: Int -> Decolonnade (Indexed f) content a -> Vector content -> Either (DecolonnadeRowError f content) a
- uncheckedRun :: forall content a f. Decolonnade (Indexed f) content a -> Vector content -> Either (DecolonnadeCellErrors f content) a
- headlessToIndexed :: forall c a. Decolonnade Headless c a -> Decolonnade (Indexed Headless) c a
- length :: forall f c a. Decolonnade f c a -> Int
- headedToIndexed :: forall content a. Eq content => Vector content -> Decolonnade Headed content a -> Either (HeadingErrors content) (Decolonnade (Indexed Headed) content a)
- prettyError :: (c -> String) -> DecolonnadeRowError f c -> String
- prettyRowError :: (content -> String) -> RowError f content -> (String, [String])
- prettyCellErrors :: (c -> String) -> DecolonnadeCellErrors f c -> [String]
- prettyHeadingErrors :: (c -> String) -> HeadingErrors c -> [String]
- columnNumToLetters :: Int -> String
Documentation
contramapContent :: forall c1 c2 f a. Contravariant f => (c2 -> c1) -> Decolonnade f c1 a -> Decolonnade f c2 a Source #
Converts the content type of a Decolonnade
. The
constraint means that Contravariant
ff
can be Headless
but not Headed
.
uncheckedRunWithRow :: Int -> Decolonnade (Indexed f) content a -> Vector content -> Either (DecolonnadeRowError f content) a Source #
This function uses unsafeIndex
to access
elements of the Vector
.
uncheckedRun :: forall content a f. Decolonnade (Indexed f) content a -> Vector content -> Either (DecolonnadeCellErrors f content) a Source #
This function does not check to make sure that the indicies in
the Decolonnade
are in the Vector
.
headlessToIndexed :: forall c a. Decolonnade Headless c a -> Decolonnade (Indexed Headless) c a Source #
length :: forall f c a. Decolonnade f c a -> Int Source #
Arguments
:: Eq content | |
=> Vector content | Headers in the source document |
-> Decolonnade Headed content a | Decolonnade that contains expected headers |
-> Either (HeadingErrors content) (Decolonnade (Indexed Headed) content a) |
Maps over a Decolonnade
that expects headers, converting these
expected headers into the indices of the columns that they
correspond to.
prettyError :: (c -> String) -> DecolonnadeRowError f c -> String Source #
This adds one to the index because text editors consider line number to be one-based, not zero-based.
prettyCellErrors :: (c -> String) -> DecolonnadeCellErrors f c -> [String] Source #
prettyHeadingErrors :: (c -> String) -> HeadingErrors c -> [String] Source #
columnNumToLetters :: Int -> String Source #