| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Network.NetRc
Contents
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* LFAs 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
- data NetRc = NetRc {
- nrHosts :: [NetRcHost]
- nrMacros :: [NetRcMacDef]
- data NetRcHost = NetRcHost {
- nrhName :: !ByteString
- nrhLogin :: !ByteString
- nrhPassword :: !ByteString
- nrhAccount :: !ByteString
- nrhMacros :: [NetRcMacDef]
- data NetRcMacDef = NetRcMacDef {
- nrmName :: !ByteString
- nrmBody :: !ByteString
- netRcToBuilder :: NetRc -> Builder
- netRcToByteString :: NetRc -> ByteString
- netRcParsec :: Parser NetRc
- parseNetRc :: SourceName -> ByteString -> Either ParseError NetRc
- readUserNetRc :: IO (Maybe (Either ParseError NetRc))
Types
Represents (semantic) contents of a .netrc file
Constructors
| NetRc | |
Fields
| |
Instances
| Data NetRc Source # | |
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 # 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 # | |
| Show NetRc Source # | |
| NFData NetRc Source # | |
Defined in Network.NetRc | |
| Eq NetRc Source # | |
| Ord NetRc Source # | |
| type Rep NetRc Source # | |
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]))) | |
machine and default entries describe remote accounts
Invariant: fields must not contain any TABs, SPACE, or LFs.
Constructors
| NetRcHost | |
Fields
| |
Instances
| Data NetRcHost Source # | |
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 # | |
| Show NetRcHost Source # | |
| NFData NetRcHost Source # | |
Defined in Network.NetRc | |
| Eq NetRcHost Source # | |
| Ord NetRcHost Source # | |
| type Rep NetRcHost Source # | |
Defined in Network.NetRc type Rep NetRcHost = D1 ('MetaData "NetRcHost" "Network.NetRc" "netrc-0.2.0.1-5531Cl6Upps1iL2ond6LyW" 'False) (C1 ('MetaCons "NetRcHost" 'PrefixI 'True) ((S1 ('MetaSel ('Just "nrhName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "nrhLogin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)) :*: (S1 ('MetaSel ('Just "nrhPassword") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: (S1 ('MetaSel ('Just "nrhAccount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "nrhMacros") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [NetRcMacDef]))))) | |
data NetRcMacDef Source #
macdef entries defining ftp macros
Constructors
| NetRcMacDef | |
Fields
| |
Instances
Formatters
netRcToBuilder :: NetRc -> Builder Source #
Construct a ByteString Builder
netRcToByteString :: NetRc -> ByteString Source #
Format NetRc into a ByteString
This is currently just a convenience wrapper around netRcToBuilder
Parsers
netRcParsec :: Parser NetRc Source #
Text.Parsec.ByteString Parser for .netrc grammar
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