{-# LANGUAGE FlexibleInstances #-}--------------------------------------------------------------------------------moduleParsers.NanoParsec(Parseable,Parser,item,some,many,sepBy,sepBy1,satisfy,oneOf,chainl,chainl1,char,string,token,reserved,spaces,runParser)where--------------------------------------------------------------------------------importqualifiedData.ByteStringasBSimportData.String(IsString)importControl.Applicative.Alternative(Alternative(empty,(<|>)))importControl.Monad.Plus(MonadPlus(mzero,mplus))---------------------------------------------------------------------------------- NanoParsec:-- http://dev.stephendiehl.com/fun/002_parsers.html#nanoparsecnewtypeParsersa=Parser{parse::s->[(a,s)]}class(Eqa,IsStringa)=>Parseableawherenil::a->Boolhd::a->Chartl::a->ainstanceParseableStringwherenil=(==[])hd=headtl=tailinstanceParseableBS.ByteStringwherenil=BS.nullhd=toEnum.fromIntegral.BS.headtl=BS.tail--------------------------------------------------------------------------------instance(Parseables)=>Functor(Parsers)wherefmapf(Parsercs)=Parser$\s->[(fa,b)|(a,b)<-css]instance(Parseables)=>Applicative(Parsers)wherepure=return(Parsercs1)<*>(Parsercs2)=Parser$\s->[(fa,s2)|(f,s1)<-cs1s,(a,s2)<-cs2s1]instance(Parseables)=>Monad(Parsers)wherereturn=unit(>>=)=bindinstance(Parseables)=>MonadPlus(Parsers)wheremzero=failuremplus=combineinstance(Parseables)=>Alternative(Parsers)whereempty=mzero(<|>)=option--------------------------------------------------------------------------------bind::(Parseables)=>Parsersa->(a->Parsersb)->Parsersbbindpf=Parser$\s->concatMap(\(a,s')->parse(fa)s')$parsepsunit::(Parseables)=>a->Parsersaunita=Parser$\s->[(a,s)]combine::(Parseables)=>Parsersa->Parsersa->Parsersacombinepq=Parser$\s->parseps++parseqsfailure::(Parseables)=>Parsersafailure=Parser$\_->[]option::(Parseables)=>Parsersa->Parsersa->Parsersaoptionpq=Parser$\s->caseparsepsof[ ]->parseqsres->res--------------------------------------------------------------------------------item::(Parseables)=>ParsersCharitem=Parser$\s->casenilsofTrue->[]False->[(hds,tls)]---------------------------------------------------------------------------------- | One or more.some::(Alternativef)=>fa->f[a]somev=some_vwheremany_v=some_v<|>pure[]some_v=(:)<$>v<*>many_v-- | Zero or more.many::(Alternativef)=>fa->f[a]manyv=many_vwheremany_v=some_v<|>pure[]some_v=(:)<$>v<*>many_v-- | One or more.sepBy1::(Alternativef)=>fa->fb->f[a]sepBy1psep=(:)<$>p<*>(many$sep*>p)-- | Zero or more.sepBy::(Alternativef)=>fa->fb->f[a]sepBypsep=sepBy1psep<|>pure[]--------------------------------------------------------------------------------satisfy::(Parseables)=>(Char->Bool)->ParsersCharsatisfyp=item`bind`\c->ifpcthenunitcelseParser$\_->[]--------------------------------------------------------------------------------oneOf::(Parseables)=>[Char]->ParsersCharoneOfs=satisfy$flipelemschainl::(Parseables)=>Parsersa->Parsers(a->a->a)->a->Parsersachainlpopa=(p`chainl1`op)<|>returnachainl1::(Parseables)=>Parsersa->Parsers(a->a->a)->Parsersap`chainl1`op=do{a<-p;resta}whereresta=(dof<-opb<-prest(fab))<|>returna--------------------------------------------------------------------------------char::(Parseables)=>Char->ParsersCharcharc=satisfy(c==)string::(Parseables)=>String->ParsersStringstring[]=return[]string(c:cs)=do{_<-charc;_<-stringcs;return(c:cs)}token::(Parseables)=>Parsersa->Parsersatokenp=do{a<-p;_<-spaces;returna}reserved::(Parseables)=>String->ParsersStringreserveds=token(strings)spaces::(Parseables)=>ParsersStringspaces=many$oneOf" \n\r"--------------------------------------------------------------------------------runParser::(Parseables)=>Parsersa->s->EitherStringarunParserms=ps$parsemswhereps[ ]=Left"Parser error."ps(x:_)=auxxauxx|nil$rest=Right$fst$x|not.nil$rest=Left$"Parser didn't consume entire stream."|otherwise=Left$"Parser error."whererest=sndx
{-# LANGUAGE OverloadedStrings #-}--------------------------------------------------------------------------------moduleParsers.URL.Internal(uri)where--------------------------------------------------------------------------------importControl.Applicative.Alternative(Alternative((<|>)))importParsers.NanoParsecimportParsers.URL.Types--------------------------------------------------------------------------------dataOptional=OPathString(MaybeOptional)|OQueryQuery(MaybeOptional)|OFragmentStringderivingShow--------------------------------------------------------------------------------scheme'::(Parseables)=>ParsersSchemescheme'=do-- tdammers, #haskell freenode, on how to avoid backtracking:-- do { string "http"; optional "https" (string "s" >> pure "https") }s<-string"https"<|>string"http"_<-reserved":"return$auxswhereaux"https"=HTTPSaux"http"=HTTPaux_______=NotSupporteduserinfo'::(Parseables)=>Parsers(MaybeString)userinfo'=dou<-somenoseparator_<-reserved"@"return$Justuwherenoseparator=satisfy('@'/=)host'::(Parseables)=>ParsersStringhost'=doh<-somenoseparatorsreturn$hwherenoseparators=satisfy$\c->':'/=c&&'/'/=cport'::(Parseables)=>Parsers(MaybeInt)port'=do_<-reserved":"p<-somenoseparatorreturn$Just$readpwherenoseparator=satisfy('/'/=)authority'::(Parseables)=>ParsersAuthorityauthority'=do_<-reserved"//"u<-userinfo'<|>returnNothingh<-host'p<-port'<|>returnNothingreturn$Authorityuhpnooseparators::(Parseables)=>ParsersCharnooseparators=satisfy$\c->':'/=c&&'/'/=c&&'?'/=c&&'&'/=c&&'='/=c&&'#'/=cpath'::(Parseables)=>ParsersStringpath'=do_<-some$reserved"/"p<-manynooseparatorsreturn$popath::(Parseables)=>Parsers(MaybeOptional)opath=dop<-path'o<-optionalreturn$Just$OPathpoquery'::(Parseables)=>ParsersQueryquery'=do_<-reserved"?"p<-pair`sepBy`char'&'return$Querypwheremightm=doa<-mreturn$Just$apair=dokey<-somenooseparators___<-reserved"="val<-(might$somenooseparators)<|>returnNothingreturn(key,val)oquery::(Parseables)=>Parsers(MaybeOptional)oquery=doq<-query'o<-optionalreturn$Just$OQueryqofragment'::(Parseables)=>ParsersStringfragment'=do_<-reserved"#"p<-manynooseparatorsreturn$pofragment::(Parseables)=>Parsers(MaybeOptional)ofragment=doq<-fragment'return$Just$OFragmentqoptional::(Parseables)=>Parsers(MaybeOptional)optional=doo<-opath<|>oquery<|>ofragment<|>returnNothingreturn$ouri::(Parseables)=>ParsersURIuri=dos<-scheme'a<-authority'o<-optionalreturn$auxsaowhereauxsao=URIsapqfwhere(p,q,f)=opt(Nothing,Nothing,Nothing)oopt(p,q,f)(Justo)=caseoofOPathp'mo->opt(Justp',q,f)moOQueryq'mo->opt(p,Justq',f)moOFragmentf'->(p,q,Justf')opt(p,q,f)(Nothing)=(p,q,f)
#!/usr/bin/envstack{- stack
--resolver lts-11.7
--install-ghc
runghc
--package bytestring
--package monadplus
--
-Wall -Werror
-}--------------------------------------------------------------------------------{-# LANGUAGE OverloadedStrings #-}--------------------------------------------------------------------------------moduleMain(main)where--------------------------------------------------------------------------------importqualifiedData.ByteStringasBSimportqualifiedParsers.URLasURL--------------------------------------------------------------------------------main::IO()--------------------------------------------------------------------------------main=doputStrLn$show$URL.parseurlputStrLn""putStrLn$show$URL.parseurl'where-- Call the parse on a regular stringurl::Stringurl="https://[email protected]:8433/foo?bar=42&baz=#qux"-- But also call it on a ByteStringurl'::BS.ByteStringurl'="https://[email protected]:8433/foo?bar=42&baz=#qux"
Output:
Note: Output has been prettyfied to fit in this code snippet.