netrc-0.2.0.1: Parser for .netrc files
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.NetRc

Description

Provides parser for $HOME/.netrc files

The implemented grammar is approximately:

NETRC := (WS|<comment>)* (ENTRY (WS+ <comment>*)+)* ENTRY?

ENTRY := 'machine' WS+ <value> WS+ ((account|username|password) WS+ <value>)*
       | 'default' WS+ (('account'|'username'|'password') WS+ <value>)*
       | 'macdef' <value> LF (<line> LF)* LF

WS := (LF|SPC|TAB)

<line>  := !LF+
<value> := !WS+
<comment> := '#' !LF* LF

As an extension to the .netrc-format as described in .e.g. netrc(5), #-style comments are tolerated. Comments are currently only allowed before, between, and after machine/default/macdef entries. Be aware though that such #-comment are not supported by all .netrc-aware applications, including ftp(1).

Synopsis

Types

data NetRc Source #

Represents (semantic) contents of a .netrc file

Constructors

NetRc 

Fields

  • nrHosts :: [NetRcHost]

    machine/default entries

    Note: If it exists, the default entry ought to be the last entry, otherwise it can cause later entries to become invisible for some implementations (e.g. ftp(1))

  • nrMacros :: [NetRcMacDef]

    Non-associated macdef entries

    Note: macdef entries not associated with host-entries are invisible to some applications (e.g. ftp(1)).

Instances

Instances details
Data NetRc Source # 
Instance details

Defined in Network.NetRc

Methods

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

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

toConstr :: NetRc -> Constr #

dataTypeOf :: NetRc -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NetRc Source # 
Instance details

Defined in Network.NetRc

Associated Types

type Rep NetRc :: Type -> Type #

Methods

from :: NetRc -> Rep NetRc x #

to :: Rep NetRc x -> NetRc #

Show NetRc Source # 
Instance details

Defined in Network.NetRc

Methods

showsPrec :: Int -> NetRc -> ShowS #

show :: NetRc -> String #

showList :: [NetRc] -> ShowS #

NFData NetRc Source # 
Instance details

Defined in Network.NetRc

Methods

rnf :: NetRc -> () #

Eq NetRc Source # 
Instance details

Defined in Network.NetRc

Methods

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

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

Ord NetRc Source # 
Instance details

Defined in Network.NetRc

Methods

compare :: NetRc -> NetRc -> Ordering #

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

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

(>) :: NetRc -> NetRc -> Bool #

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

max :: NetRc -> NetRc -> NetRc #

min :: NetRc -> NetRc -> NetRc #

type Rep NetRc Source # 
Instance details

Defined in Network.NetRc

type Rep NetRc = D1 ('MetaData "NetRc" "Network.NetRc" "netrc-0.2.0.1-5531Cl6Upps1iL2ond6LyW" 'False) (C1 ('MetaCons "NetRc" 'PrefixI 'True) (S1 ('MetaSel ('Just "nrHosts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [NetRcHost]) :*: S1 ('MetaSel ('Just "nrMacros") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [NetRcMacDef])))

data NetRcHost Source #

machine and default entries describe remote accounts

Invariant: fields must not contain any TABs, SPACE, or LFs.

Constructors

NetRcHost 

Fields

Instances

Instances details
Data NetRcHost Source # 
Instance details

Defined in Network.NetRc

Methods

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

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

toConstr :: NetRcHost -> Constr #

dataTypeOf :: NetRcHost -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NetRcHost Source # 
Instance details

Defined in Network.NetRc

Associated Types

type Rep NetRcHost :: Type -> Type #

Show NetRcHost Source # 
Instance details

Defined in Network.NetRc

NFData NetRcHost Source # 
Instance details

Defined in Network.NetRc

Methods

rnf :: NetRcHost -> () #

Eq NetRcHost Source # 
Instance details

Defined in Network.NetRc

Ord NetRcHost Source # 
Instance details

Defined in Network.NetRc

type Rep NetRcHost Source # 
Instance details

Defined in Network.NetRc

data NetRcMacDef Source #

macdef entries defining ftp macros

Constructors

NetRcMacDef 

Fields

  • nrmName :: !ByteString

    Name of macdef entry

    Invariant: must not contain any TABs, SPACE, or LFs

  • nrmBody :: !ByteString

    Raw macdef body

    Invariant: must not contain null-lines, i.e. consecutive LFs

Instances

Instances details
Data NetRcMacDef Source # 
Instance details

Defined in Network.NetRc

Methods

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

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

toConstr :: NetRcMacDef -> Constr #

dataTypeOf :: NetRcMacDef -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NetRcMacDef Source # 
Instance details

Defined in Network.NetRc

Associated Types

type Rep NetRcMacDef :: Type -> Type #

Show NetRcMacDef Source # 
Instance details

Defined in Network.NetRc

NFData NetRcMacDef Source # 
Instance details

Defined in Network.NetRc

Methods

rnf :: NetRcMacDef -> () #

Eq NetRcMacDef Source # 
Instance details

Defined in Network.NetRc

Ord NetRcMacDef Source # 
Instance details

Defined in Network.NetRc

type Rep NetRcMacDef Source # 
Instance details

Defined in Network.NetRc

type Rep NetRcMacDef = D1 ('MetaData "NetRcMacDef" "Network.NetRc" "netrc-0.2.0.1-5531Cl6Upps1iL2ond6LyW" 'False) (C1 ('MetaCons "NetRcMacDef" 'PrefixI 'True) (S1 ('MetaSel ('Just "nrmName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "nrmBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)))

Formatters

netRcToByteString :: NetRc -> ByteString Source #

Format NetRc into a ByteString

This is currently just a convenience wrapper around netRcToBuilder

Parsers

parseNetRc :: SourceName -> ByteString -> Either ParseError NetRc Source #

Convenience wrapper for netRcParsec parser

This is basically just

parseNetRc = parse (netRcParsec <* eof)

This wrapper is mostly useful for avoiding to have to import Parsec modules (and to build-depend explicitly on parsec).

Utilities

readUserNetRc :: IO (Maybe (Either ParseError NetRc)) Source #

Reads and parses default $HOME/.netrc

Returns Nothing if $HOME variable undefined and/or if .netrc if missing. Throws standard IO exceptions in case of other filesystem-errors.

Note: This function performs no permission sanity-checking on the .netrc file