hnix-0.5.1: Haskell implementation of the Nix language

Safe HaskellNone
LanguageHaskell2010

Nix.Atoms

Synopsis

Documentation

data NAtom Source #

Atoms are values that evaluate to themselves. This means that they appear in both the parsed AST (in the form of literals) and the evaluated form.

Constructors

NInt Integer

An integer. The c nix implementation currently only supports integers that fit in the range of Int64.

NFloat Float

A floating point number

NBool Bool

Booleans.

NNull

Null values. There's only one of this variant.

Instances

Eq NAtom Source # 

Methods

(==) :: NAtom -> NAtom -> Bool #

(/=) :: NAtom -> NAtom -> Bool #

Data NAtom Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NAtom -> c NAtom #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NAtom #

toConstr :: NAtom -> Constr #

dataTypeOf :: NAtom -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NAtom) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NAtom) #

gmapT :: (forall b. Data b => b -> b) -> NAtom -> NAtom #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NAtom -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NAtom -> r #

gmapQ :: (forall d. Data d => d -> u) -> NAtom -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NAtom -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NAtom -> m NAtom #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NAtom -> m NAtom #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NAtom -> m NAtom #

Ord NAtom Source # 

Methods

compare :: NAtom -> NAtom -> Ordering #

(<) :: NAtom -> NAtom -> Bool #

(<=) :: NAtom -> NAtom -> Bool #

(>) :: NAtom -> NAtom -> Bool #

(>=) :: NAtom -> NAtom -> Bool #

max :: NAtom -> NAtom -> NAtom #

min :: NAtom -> NAtom -> NAtom #

Read NAtom Source # 
Show NAtom Source # 

Methods

showsPrec :: Int -> NAtom -> ShowS #

show :: NAtom -> String #

showList :: [NAtom] -> ShowS #

Generic NAtom Source # 

Associated Types

type Rep NAtom :: * -> * #

Methods

from :: NAtom -> Rep NAtom x #

to :: Rep NAtom x -> NAtom #

Hashable NAtom Source # 

Methods

hashWithSalt :: Int -> NAtom -> Int #

hash :: NAtom -> Int #

NFData NAtom Source # 

Methods

rnf :: NAtom -> () #

Serialise NAtom Source # 
type Rep NAtom Source # 

atomText :: NAtom -> Text Source #

Translate an atom into its nix representation.