aip-0.1.3: Aeronautical Information Package (AIP)

Safe HaskellNone
LanguageHaskell2010

Data.Aviation.Aip.PerHref

Documentation

newtype PerHref f a Source #

Constructors

PerHref (Href -> FilePath -> FilePath -> (String -> AipCon ()) -> f a) 
Instances
MonadTrans PerHref Source # 
Instance details

Defined in Data.Aviation.Aip.PerHref

Methods

lift :: Monad m => m a -> PerHref m a #

Monad f => Monad (PerHref f) Source # 
Instance details

Defined in Data.Aviation.Aip.PerHref

Methods

(>>=) :: PerHref f a -> (a -> PerHref f b) -> PerHref f b #

(>>) :: PerHref f a -> PerHref f b -> PerHref f b #

return :: a -> PerHref f a #

fail :: String -> PerHref f a #

Functor f => Functor (PerHref f) Source # 
Instance details

Defined in Data.Aviation.Aip.PerHref

Methods

fmap :: (a -> b) -> PerHref f a -> PerHref f b #

(<$) :: a -> PerHref f b -> PerHref f a #

Applicative f => Applicative (PerHref f) Source # 
Instance details

Defined in Data.Aviation.Aip.PerHref

Methods

pure :: a -> PerHref f a #

(<*>) :: PerHref f (a -> b) -> PerHref f a -> PerHref f b #

liftA2 :: (a -> b -> c) -> PerHref f a -> PerHref f b -> PerHref f c #

(*>) :: PerHref f a -> PerHref f b -> PerHref f b #

(<*) :: PerHref f a -> PerHref f b -> PerHref f a #

Alternative f => Alternative (PerHref f) Source # 
Instance details

Defined in Data.Aviation.Aip.PerHref

Methods

empty :: PerHref f a #

(<|>) :: PerHref f a -> PerHref f a -> PerHref f a #

some :: PerHref f a -> PerHref f [a] #

many :: PerHref f a -> PerHref f [a] #

MonadIO f => MonadIO (PerHref f) Source # 
Instance details

Defined in Data.Aviation.Aip.PerHref

Methods

liftIO :: IO a -> PerHref f a #

Apply f => Apply (PerHref f) Source # 
Instance details

Defined in Data.Aviation.Aip.PerHref

Methods

(<.>) :: PerHref f (a -> b) -> PerHref f a -> PerHref f b #

(.>) :: PerHref f a -> PerHref f b -> PerHref f b #

(<.) :: PerHref f a -> PerHref f b -> PerHref f a #

liftF2 :: (a -> b -> c) -> PerHref f a -> PerHref f b -> PerHref f c #

Alt f => Alt (PerHref f) Source # 
Instance details

Defined in Data.Aviation.Aip.PerHref

Methods

(<!>) :: PerHref f a -> PerHref f a -> PerHref f a #

some :: Applicative (PerHref f) => PerHref f a -> PerHref f [a] #

many :: Applicative (PerHref f) => PerHref f a -> PerHref f [a] #

Bind f => Bind (PerHref f) Source # 
Instance details

Defined in Data.Aviation.Aip.PerHref

Methods

(>>-) :: PerHref f a -> (a -> PerHref f b) -> PerHref f b #

join :: PerHref f (PerHref f a) -> PerHref f a #

Wrapped (PerHref f k) Source # 
Instance details

Defined in Data.Aviation.Aip.PerHref

Associated Types

type Unwrapped (PerHref f k) :: Type #

Methods

_Wrapped' :: Iso' (PerHref f k) (Unwrapped (PerHref f k)) #

PerHref f a ~ x => Rewrapped (PerHref g k) x Source # 
Instance details

Defined in Data.Aviation.Aip.PerHref

type Unwrapped (PerHref f k) Source # 
Instance details

Defined in Data.Aviation.Aip.PerHref

type Unwrapped (PerHref f k) = Href -> FilePath -> FilePath -> (String -> AipCon ()) -> f k

ioPerHref :: MonadIO f => (Href -> FilePath -> FilePath -> (String -> AipCon ()) -> IO a) -> PerHref f a Source #