{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Cardano.Chain.Update.SystemTag
( SystemTag (..),
SystemTagError (..),
checkSystemTag,
systemTagMaxLength,
osHelper,
archHelper,
)
where
import Cardano.Binary
( Decoder,
DecoderError (..),
FromCBOR (..),
ToCBOR (..),
decodeListLen,
decodeWord8,
encodeListLen,
matchSize,
)
import Cardano.Prelude
import Data.Aeson (ToJSON, ToJSONKey)
import Data.Data (Data)
import qualified Data.Text as T
import Distribution.System (Arch (..), OS (..))
import Distribution.Text (display)
import Formatting (bprint, int, stext)
import qualified Formatting.Buildable as B
import NoThunks.Class (NoThunks (..))
newtype SystemTag = SystemTag
{ SystemTag -> Text
getSystemTag :: Text
}
deriving (SystemTag -> SystemTag -> Bool
(SystemTag -> SystemTag -> Bool)
-> (SystemTag -> SystemTag -> Bool) -> Eq SystemTag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SystemTag -> SystemTag -> Bool
$c/= :: SystemTag -> SystemTag -> Bool
== :: SystemTag -> SystemTag -> Bool
$c== :: SystemTag -> SystemTag -> Bool
Eq, Eq SystemTag
Eq SystemTag
-> (SystemTag -> SystemTag -> Ordering)
-> (SystemTag -> SystemTag -> Bool)
-> (SystemTag -> SystemTag -> Bool)
-> (SystemTag -> SystemTag -> Bool)
-> (SystemTag -> SystemTag -> Bool)
-> (SystemTag -> SystemTag -> SystemTag)
-> (SystemTag -> SystemTag -> SystemTag)
-> Ord SystemTag
SystemTag -> SystemTag -> Bool
SystemTag -> SystemTag -> Ordering
SystemTag -> SystemTag -> SystemTag
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
min :: SystemTag -> SystemTag -> SystemTag
$cmin :: SystemTag -> SystemTag -> SystemTag
max :: SystemTag -> SystemTag -> SystemTag
$cmax :: SystemTag -> SystemTag -> SystemTag
>= :: SystemTag -> SystemTag -> Bool
$c>= :: SystemTag -> SystemTag -> Bool
> :: SystemTag -> SystemTag -> Bool
$c> :: SystemTag -> SystemTag -> Bool
<= :: SystemTag -> SystemTag -> Bool
$c<= :: SystemTag -> SystemTag -> Bool
< :: SystemTag -> SystemTag -> Bool
$c< :: SystemTag -> SystemTag -> Bool
compare :: SystemTag -> SystemTag -> Ordering
$ccompare :: SystemTag -> SystemTag -> Ordering
$cp1Ord :: Eq SystemTag
Ord, Int -> SystemTag -> ShowS
[SystemTag] -> ShowS
SystemTag -> String
(Int -> SystemTag -> ShowS)
-> (SystemTag -> String)
-> ([SystemTag] -> ShowS)
-> Show SystemTag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SystemTag] -> ShowS
$cshowList :: [SystemTag] -> ShowS
show :: SystemTag -> String
$cshow :: SystemTag -> String
showsPrec :: Int -> SystemTag -> ShowS
$cshowsPrec :: Int -> SystemTag -> ShowS
Show, (forall x. SystemTag -> Rep SystemTag x)
-> (forall x. Rep SystemTag x -> SystemTag) -> Generic SystemTag
forall x. Rep SystemTag x -> SystemTag
forall x. SystemTag -> Rep SystemTag x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SystemTag x -> SystemTag
$cfrom :: forall x. SystemTag -> Rep SystemTag x
Generic)
deriving newtype (SystemTag -> Builder
(SystemTag -> Builder) -> Buildable SystemTag
forall p. (p -> Builder) -> Buildable p
build :: SystemTag -> Builder
$cbuild :: SystemTag -> Builder
B.Buildable)
deriving anyclass (SystemTag -> ()
(SystemTag -> ()) -> NFData SystemTag
forall a. (a -> ()) -> NFData a
rnf :: SystemTag -> ()
$crnf :: SystemTag -> ()
NFData, Context -> SystemTag -> IO (Maybe ThunkInfo)
Proxy SystemTag -> String
(Context -> SystemTag -> IO (Maybe ThunkInfo))
-> (Context -> SystemTag -> IO (Maybe ThunkInfo))
-> (Proxy SystemTag -> String)
-> NoThunks SystemTag
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy SystemTag -> String
$cshowTypeOf :: Proxy SystemTag -> String
wNoThunks :: Context -> SystemTag -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> SystemTag -> IO (Maybe ThunkInfo)
noThunks :: Context -> SystemTag -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> SystemTag -> IO (Maybe ThunkInfo)
NoThunks)
instance ToJSON SystemTag
instance ToJSONKey SystemTag
instance ToCBOR SystemTag where
toCBOR :: SystemTag -> Encoding
toCBOR = Text -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (Text -> Encoding) -> (SystemTag -> Text) -> SystemTag -> Encoding
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. SystemTag -> Text
getSystemTag
instance FromCBOR SystemTag where
fromCBOR :: Decoder s SystemTag
fromCBOR = Text -> SystemTag
SystemTag (Text -> SystemTag) -> Decoder s Text -> Decoder s SystemTag
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Text
forall a s. FromCBOR a => Decoder s a
fromCBOR
systemTagMaxLength :: Integral i => i
systemTagMaxLength :: i
systemTagMaxLength = i
10
data SystemTagError
= SystemTagNotAscii Text
| SystemTagTooLong Text
deriving (SystemTagError -> SystemTagError -> Bool
(SystemTagError -> SystemTagError -> Bool)
-> (SystemTagError -> SystemTagError -> Bool) -> Eq SystemTagError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SystemTagError -> SystemTagError -> Bool
$c/= :: SystemTagError -> SystemTagError -> Bool
== :: SystemTagError -> SystemTagError -> Bool
$c== :: SystemTagError -> SystemTagError -> Bool
Eq, Int -> SystemTagError -> ShowS
[SystemTagError] -> ShowS
SystemTagError -> String
(Int -> SystemTagError -> ShowS)
-> (SystemTagError -> String)
-> ([SystemTagError] -> ShowS)
-> Show SystemTagError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SystemTagError] -> ShowS
$cshowList :: [SystemTagError] -> ShowS
show :: SystemTagError -> String
$cshow :: SystemTagError -> String
showsPrec :: Int -> SystemTagError -> ShowS
$cshowsPrec :: Int -> SystemTagError -> ShowS
Show, Typeable SystemTagError
DataType
Constr
Typeable SystemTagError
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SystemTagError -> c SystemTagError)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SystemTagError)
-> (SystemTagError -> Constr)
-> (SystemTagError -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SystemTagError))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SystemTagError))
-> ((forall b. Data b => b -> b)
-> SystemTagError -> SystemTagError)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SystemTagError -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SystemTagError -> r)
-> (forall u.
(forall d. Data d => d -> u) -> SystemTagError -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SystemTagError -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SystemTagError -> m SystemTagError)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SystemTagError -> m SystemTagError)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SystemTagError -> m SystemTagError)
-> Data SystemTagError
SystemTagError -> DataType
SystemTagError -> Constr
(forall b. Data b => b -> b) -> SystemTagError -> SystemTagError
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SystemTagError -> c SystemTagError
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SystemTagError
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> SystemTagError -> u
forall u. (forall d. Data d => d -> u) -> SystemTagError -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SystemTagError -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SystemTagError -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SystemTagError -> m SystemTagError
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SystemTagError -> m SystemTagError
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SystemTagError
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SystemTagError -> c SystemTagError
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SystemTagError)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SystemTagError)
$cSystemTagTooLong :: Constr
$cSystemTagNotAscii :: Constr
$tSystemTagError :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> SystemTagError -> m SystemTagError
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SystemTagError -> m SystemTagError
gmapMp :: (forall d. Data d => d -> m d)
-> SystemTagError -> m SystemTagError
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SystemTagError -> m SystemTagError
gmapM :: (forall d. Data d => d -> m d)
-> SystemTagError -> m SystemTagError
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SystemTagError -> m SystemTagError
gmapQi :: Int -> (forall d. Data d => d -> u) -> SystemTagError -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SystemTagError -> u
gmapQ :: (forall d. Data d => d -> u) -> SystemTagError -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SystemTagError -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SystemTagError -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SystemTagError -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SystemTagError -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SystemTagError -> r
gmapT :: (forall b. Data b => b -> b) -> SystemTagError -> SystemTagError
$cgmapT :: (forall b. Data b => b -> b) -> SystemTagError -> SystemTagError
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SystemTagError)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SystemTagError)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SystemTagError)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SystemTagError)
dataTypeOf :: SystemTagError -> DataType
$cdataTypeOf :: SystemTagError -> DataType
toConstr :: SystemTagError -> Constr
$ctoConstr :: SystemTagError -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SystemTagError
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SystemTagError
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SystemTagError -> c SystemTagError
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SystemTagError -> c SystemTagError
$cp1Data :: Typeable SystemTagError
Data)
instance ToCBOR SystemTagError where
toCBOR :: SystemTagError -> Encoding
toCBOR SystemTagError
err = case SystemTagError
err of
SystemTagNotAscii Text
tag ->
Word -> Encoding
encodeListLen Word
2
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (Word8
0 :: Word8)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Text -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Text
tag
SystemTagTooLong Text
tag ->
Word -> Encoding
encodeListLen Word
2
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (Word8
1 :: Word8)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Text -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Text
tag
instance FromCBOR SystemTagError where
fromCBOR :: Decoder s SystemTagError
fromCBOR = do
Int
len <- Decoder s Int
forall s. Decoder s Int
decodeListLen
let checkSize :: Int -> Decoder s ()
checkSize :: Int -> Decoder s ()
checkSize Int
size = Text -> Int -> Int -> Decoder s ()
forall s. Text -> Int -> Int -> Decoder s ()
matchSize Text
"SystemTagError" Int
size Int
len
Word8
tag <- Decoder s Word8
forall s. Decoder s Word8
decodeWord8
case Word8
tag of
Word8
0 -> Int -> Decoder s ()
forall s. Int -> Decoder s ()
checkSize Int
2 Decoder s ()
-> Decoder s SystemTagError -> Decoder s SystemTagError
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> SystemTagError
SystemTagNotAscii (Text -> SystemTagError)
-> Decoder s Text -> Decoder s SystemTagError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Text
forall a s. FromCBOR a => Decoder s a
fromCBOR
Word8
1 -> Int -> Decoder s ()
forall s. Int -> Decoder s ()
checkSize Int
2 Decoder s ()
-> Decoder s SystemTagError -> Decoder s SystemTagError
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> SystemTagError
SystemTagTooLong (Text -> SystemTagError)
-> Decoder s Text -> Decoder s SystemTagError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Text
forall a s. FromCBOR a => Decoder s a
fromCBOR
Word8
_ -> DecoderError -> Decoder s SystemTagError
forall e s a. Buildable e => e -> Decoder s a
cborError (DecoderError -> Decoder s SystemTagError)
-> DecoderError -> Decoder s SystemTagError
forall a b. (a -> b) -> a -> b
$ Text -> Word8 -> DecoderError
DecoderErrorUnknownTag Text
"SystemTagError" Word8
tag
instance B.Buildable SystemTagError where
build :: SystemTagError -> Builder
build = \case
SystemTagNotAscii Text
tag ->
Format Builder (Text -> Builder) -> Text -> Builder
forall a. Format Builder a -> a
bprint (Format (Text -> Builder) (Text -> Builder)
"SystemTag, " Format (Text -> Builder) (Text -> Builder)
-> Format Builder (Text -> Builder)
-> Format Builder (Text -> Builder)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format Builder (Text -> Builder)
forall r. Format r (Text -> r)
stext Format Builder (Text -> Builder)
-> Format Builder Builder -> Format Builder (Text -> Builder)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format Builder Builder
", contains non-ascii characters") Text
tag
SystemTagTooLong Text
tag ->
Format Builder (Text -> Int -> Builder) -> Text -> Int -> Builder
forall a. Format Builder a -> a
bprint
(Format (Text -> Int -> Builder) (Text -> Int -> Builder)
"SystemTag, " Format (Text -> Int -> Builder) (Text -> Int -> Builder)
-> Format Builder (Text -> Int -> Builder)
-> Format Builder (Text -> Int -> Builder)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format (Int -> Builder) (Text -> Int -> Builder)
forall r. Format r (Text -> r)
stext Format (Int -> Builder) (Text -> Int -> Builder)
-> Format Builder (Int -> Builder)
-> Format Builder (Text -> Int -> Builder)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format (Int -> Builder) (Int -> Builder)
", exceeds limit of " Format (Int -> Builder) (Int -> Builder)
-> Format Builder (Int -> Builder)
-> Format Builder (Int -> Builder)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format Builder (Int -> Builder)
forall a r. Integral a => Format r (a -> r)
int)
Text
tag
(Int
forall i. Integral i => i
systemTagMaxLength :: Int)
checkSystemTag :: MonadError SystemTagError m => SystemTag -> m ()
checkSystemTag :: SystemTag -> m ()
checkSystemTag (SystemTag Text
tag)
| Text -> Int
T.length Text
tag Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
forall i. Integral i => i
systemTagMaxLength = SystemTagError -> m ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (SystemTagError -> m ()) -> SystemTagError -> m ()
forall a b. (a -> b) -> a -> b
$ Text -> SystemTagError
SystemTagTooLong Text
tag
| (Char -> Bool) -> Text -> Bool
T.any (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Char -> Bool
isAscii) Text
tag = SystemTagError -> m ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (SystemTagError -> m ()) -> SystemTagError -> m ()
forall a b. (a -> b) -> a -> b
$ Text -> SystemTagError
SystemTagNotAscii Text
tag
| Bool
otherwise = () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
osHelper :: OS -> Text
osHelper :: OS -> Text
osHelper OS
sys = case OS
sys of
OS
Windows -> Text
"win"
OS
OSX -> Text
"macos"
OS
Linux -> Text
"linux"
OS
_ -> String -> Text
forall a b. ConvertText a b => a -> b
toS (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ OS -> String
forall a. Pretty a => a -> String
display OS
sys
archHelper :: Arch -> Text
archHelper :: Arch -> Text
archHelper Arch
archt = case Arch
archt of
Arch
I386 -> Text
"32"
Arch
X86_64 -> Text
"64"
Arch
_ -> String -> Text
forall a b. ConvertText a b => a -> b
toS (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Arch -> String
forall a. Pretty a => a -> String
display Arch
archt