Safe Haskell | None |
---|---|
Language | Haskell2010 |
Nix.Atoms
Documentation
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 |
NFloat Float | A floating point number |
NBool Bool | Booleans. |
NNull | Null values. There's only one of this variant. |
Instances
Eq NAtom Source # | |
Data NAtom Source # | |
Defined in Nix.Atoms 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 # 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 # | |
Read NAtom Source # | |
Show NAtom Source # | |
Generic NAtom Source # | |
Hashable NAtom Source # | |
ToJSON NAtom Source # | |
Defined in Nix.Expr.Types | |
FromJSON NAtom Source # | |
Binary NAtom Source # | |
NFData NAtom Source # | |
Serialise NAtom Source # | |
type Rep NAtom Source # | |
Defined in Nix.Atoms type Rep NAtom = D1 (MetaData "NAtom" "Nix.Atoms" "hnix-0.6.1-1597pjcbiB2Cib3HzwJZxT" False) ((C1 (MetaCons "NInt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)) :+: C1 (MetaCons "NFloat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))) :+: (C1 (MetaCons "NBool" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :+: C1 (MetaCons "NNull" PrefixI False) (U1 :: Type -> Type))) |