{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module TextShow.Data.Version (showbVersion) where
import Data.List (intersperse)
import Data.Text.Lazy.Builder (Builder, fromString, singleton)
import Data.Version (Version(..))
import Prelude ()
import Prelude.Compat
import TextShow.Classes (TextShow(..))
import TextShow.Data.Char ()
import TextShow.Data.Integral ()
import TextShow.Data.List ()
import TextShow.TH.Internal (deriveTextShow)
showbVersion :: Version -> Builder
showbVersion :: Version -> Builder
showbVersion (Version [Int]
branch [String]
tags)
= forall a. Monoid a => [a] -> a
mconcat (forall a. a -> [a] -> [a]
intersperse (Char -> Builder
singleton Char
'.') forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. TextShow a => a -> Builder
showb [Int]
branch) forall a. Semigroup a => a -> a -> a
<>
forall a. Monoid a => [a] -> a
mconcat (forall a b. (a -> b) -> [a] -> [b]
map ((Char -> Builder
singleton Char
'-' forall a. Semigroup a => a -> a -> a
<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
fromString) [String]
tags)
{-# INLINE showbVersion #-}
$(deriveTextShow ''Version)