-- Copyright (c) 2019 Herbert Valerio Riedel -- -- This file is free software: you may copy, redistribute and/or modify it -- under the terms of the GNU General Public License as published by the -- Free Software Foundation, either version 2 of the License, or (at your -- option) any later version. -- -- This file is distributed in the hope that it will be useful, but -- WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU -- General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program (see `LICENSE`). If not, see -- . {-# LANGUAGE Trustworthy #-} -- | -- Copyright: © Herbert Valerio Riedel 2019 -- SPDX-License-Identifier: GPL-2.0-or-later -- --String representation of -- -- * LDAPv3 search 'Filter's as defined by -- * LDAPv3 'DistinguishedName's as defined by -- -- @since 0.1.0 module LDAPv3.StringRepr ( StringRepr ( asParsec , asBuilder , renderShortText ) , renderText , renderString , parseShortText , parseText , parseString -- * Distinguished Names , DistinguishedName(DistinguishedName) , rfc4514coreAttributes ) where import Common hiding (Option, many, option, some, (<|>)) import qualified Data.Text.Short as TS import Text.Parsec as P import LDAPv3.AttributeDescription () import LDAPv3.DistinguishedName (DistinguishedName (..), rfc4514coreAttributes) import LDAPv3.SearchFilter () import LDAPv3.StringRepr.Class -- | Convenience 'StringRepr' operation for rendering as 'Text' -- -- @since 0.1.0 renderText :: StringRepr a => a -> Text renderText = TS.toText . renderShortText -- | Convenience 'StringRepr' operation for rendering as plain-old 'String' -- -- @since 0.1.0 renderString :: StringRepr a => a -> String renderString = TS.toString . renderShortText -- | Convenience 'StringRepr' operation for parsing from 'Text' -- -- @since 0.1.0 parseText :: StringRepr a => Text -> Maybe a parseText = either (const Nothing) Just . parse (asParsec <* eof) "" -- | Convenience 'StringRepr' operation for parsing from 'ShortText' -- -- @since 0.1.0 parseShortText :: StringRepr a => ShortText -> Maybe a parseShortText = either (const Nothing) Just . parse (asParsec <* eof) "" . TS.toString -- | Convenience 'StringRepr' operation for parsing from plain-old 'String' -- -- @since 0.1.0 parseString :: StringRepr a => String -> Maybe a parseString = either (const Nothing) Just . parse (asParsec <* eof) ""