{- CAO Compiler Copyright (C) 2014 Cryptography and Information Security Group, HASLab - INESC TEC and Universidade do Minho This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program 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. If not, see . -} {-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveTraversable #-} {- Module : $Header$ Description : CAO language literals Copyright : (C) 2014 Cryptography and Information Security Group, HASLab - INESC TEC and Universidade do Minho License : GPL Maintainer : Paulo Silva Stability : experimental Portability : non-portable -} module Language.CAO.Common.Literal where import Data.Foldable (Foldable) import Data.Traversable (Traversable) import Language.CAO.Common.Outputable import Language.CAO.Common.Representation import Language.CAO.Common.Polynomial import Language.CAO.Semantics.Bits (bitsToString) -- | Bit strings are stored in the reversed order. data Literal id -- | Boolean literals = BLit !Bool -- | Integer literals | ILit !Integer -- | Bit strings | BSLit !Sign ![Bool] -- | Polynomial literals | PLit !(Pol id) deriving (Show, Read, Functor, Foldable, Traversable, Eq, Ord) instance PP id => PP (Literal id) where ppr = pprLit pprLit :: PP id => Literal id -> CDoc pprLit (BLit True) = text "true" pprLit (BLit False) = text "false" pprLit (ILit i) = integer i pprLit (BSLit sig s) = text (signPrefix sig) <> text (bitsToString s) pprLit (PLit p) = brackets $ ppr p instance PP id => StringRepresentation (Literal id) where toString (ILit i) = intString i toString (PLit p) = toString p toString l = showPpr l -------------------------------------------------------------------------------- -- | Signal of a bit string data Sign = U -- ^ Unsigned | S -- ^ Signed deriving (Show, Read, Eq, Ord) instance PP Sign where ppr U = text "unsigned" ppr S = text "signed" signPrefix :: Sign -> String signPrefix s = case s of U -> "0b" S -> "1b"